v15i062: dmake version 3.6 (part 10/25)
Dennis Vadura
dvadura at watdragon.waterloo.edu
Mon Oct 15 11:41:36 AEST 1990
Posting-number: Volume 15, Issue 62
Submitted-by: Dennis Vadura <dvadura at watdragon.waterloo.edu>
Archive-name: dmake-3.6/part10
#!/bin/sh
# this is part 10 of a multipart archive
# do not concatenate these parts, unpack them in order with /bin/sh
# file msdos/exec.asm continued
#
CurArch=10
if test ! -r s2_seq_.tmp
then echo "Please unpack part 1 first!"
exit 1; fi
( read Scheck
if test "$Scheck" != $CurArch
then echo "Please unpack part $Scheck next!"
exit 1;
else exit 0; fi
) < s2_seq_.tmp || exit 1
echo "x - Continuing file msdos/exec.asm"
sed 's/^X//' << 'SHAR_EOF' >> msdos/exec.asm
X; 0a pointer to fcb2
X mov cx, cs
X mov [word ptr ex_cmdtail], offset cmdtail
X mov [word ptr ex_cmdtail+2], cx
X mov ax, [envseg]
X mov [ex_envseg], ax
X
X; set up registers for exec call
X; ds:dx - pointer to pathname of program to execute
X; es:bx - pointer to above parameter block
X mov dx, offset cmdpath
X mov es, cx
X mov bx, offset exec_block
X
X; Under DOS 2.x exec is notorious for clobbering registers and guarantees
X; to preserve only cs:ip.
X push ds
X mov [ex_sp], sp
X mov [ex_ss], ss
X mov [ex_error], 0 ; clear exec error code
X inc [in_exec] ; set internal flag
X mov ax, 04b00H
X int 21H
X
X; returned from exec, so restore possibly clobbered registers.
X mov ss, cs:ex_ss
X mov sp, cs:ex_sp
X pop ds
X
X; check to make certain the exec call worked.
X jnc it_worked
X
X; exec call failed. Save return code from msdos.
X mov [ex_error], ax
X jmp leave_exec
X
Xit_worked: mov ah, 04dH ; get the return code
X int 21H
X cbw
X mov [retcode], ax
X
Xleave_exec: mov [in_exec], 0 ; all done, reset in_exec flag
X cmp [swap], 0 ; check swap, if non-zero swap back in
X je no_swap_in
X call swap_in
Xno_swap_in: ret
Xdo_exec endp
X
X
X
X;==============================================================================
X; Everything past this point is overwriten with the environment and new
X; program after the currently executing program is swapped out.
X;==============================================================================
Xoverlay_code_here label word
X
X;-----------------------------------------------------------------------------
X; Figure out where we can swap to and initialize the resource we are going to
X; use. We try XMS, EMS, and a tempfile (if specified), in that order. We set
X; [cs:swap] to the correct value based on which of the resources exists.
X; If none can be used, then [cs:swap] is set to 0, and no swap takes place.
X; The exec code will still attempt to execute the child in this instance, but
X; may fail due to lack of resources. Each swap_out_* routine must provide
X; it's own clean-up handler should it not be able to write all program
X; segments to the swap resource.
Xinit_swap proc near
X mov [swap], 0
X;call init_xms
X;jnc init_done
X;call init_ems
X;jnc init_done
X call init_file
Xinit_done: ret
Xinit_swap endp
X
X
X;-----------------------------------------------------------------------------
X; This routine is used to walk the DOS alocated memory block chain and,
X; starting at address supplied in the es register. For each block it
X; calls the routine specified by the bx register with the segment length
X; in si, and it's address in di. It does not apply the routine to the
X; segment if the segment is the same as the current program's [cs:psp] value.
Xmemheader struc
X magic db ? ; either 'Z' for end or 'M' for allocated
X owner dw ? ; psp of owner block
X len dw ? ; length in paragraphs of segment
Xmemheader ends
X
Xwalk_arena_chain proc near
X mov si, word ptr es:3 ; get length
X mov di, es
X inc di
X mov ax, word ptr es:1
X cmp ax, cs:psp ; is it owned by us?
X jne walk_done ; NOPE! -- all done
X cmp di, cs:psp ; make sure we don't
X je next_block ; touch our psp
X push di
X push si
X push bx
X call bx ; handle the segment
X pop bx
X pop si
X pop di
X jc exit_walk ; if error then stop
X mov al, byte ptr es:0 ; check if at end
X cmp al, 'Z'
X je walk_done
X
Xnext_block: add di, si ; go on to next segment
X mov es, di
X jmp walk_arena_chain
Xwalk_done: clc
Xexit_walk: ret
Xwalk_arena_chain endp
X
X
X;-----------------------------------------------------------------------------
X; This routine takes a dos segment found in the di register and free's it.
Xfree_dos_segment proc near
X mov es, di ; free dos memory block
X mov ah, 49H
X int 21H
X ret
Xfree_dos_segment endp
X
X
X;-----------------------------------------------------------------------------
X; Called to invoke write_segment with proper values in the al register. Only
X; ever called from walk_arena_chain, and so al should be set to seg_alloc.
Xwrite_segment_data label near
X mov al, seg_alloc ; and fall through into write_segment
X;-----------------------------------------------------------------------------
X; This routine writes a segment as a block of data segments if the number of
X; paragraphs to write exceeds 0x0fff (rarely the case).
X; It stuffs the info into tmpseg, and then calls wheader and wseg to get the
X; data out.
X;
X; di:dx segment:offset of segment; offset is ALWAYS zero.
X; si number of paragraphs to write.
X; al mode of header to write
Xwrite_segment proc near
X push di
X push si
X xor dx,dx
X mov bx, [swap]
X call [write_header+bx]
X pop si
X pop di
X jc exit_wseg
X
Xdo_io_loop: cmp si, 0 ; are we done yet?
X je exit_wseg ; yup so leave.
X mov cx, si ; # of paragraphs to move
X cmp cx, 0fffH ; see if we have lots to move?
X jle do_io
X mov cx, 0fffH ; reset to max I/O size
X
Xdo_io: push cx ; save # of paragraphs we are writing
X shl cx, 1 ; shift cx by four to the left
X shl cx, 1
X shl cx, 1
X shl cx, 1
X push di ; save the start, and count left
X push si
X mov si, cx
X xor dx,dx
X mov al, seg_data
X mov bx, [swap]
X push bx
X call [write_header+bx]
X pop bx
X call [write_seg+bx]
X pop si
X pop di
X pop dx ; original paragraph count in dx
X jc exit_wseg ; it failed so exit.
X add di, dx ; adjust the pointers, and continue.
X sub si, dx
X jmp do_io_loop
Xexit_wseg: ret
Xwrite_segment endp
X
X
X;=============================================================================
X; THE FOLLOWING SECTION DEALS WITH ALL ROUTINES REQUIRED TO WRITE XMS RECORDS.
X;=============================================================================
Xinit_xms proc near
X ret
Xinit_xms endp
X
Xwhdr_xms proc near
X ret
Xwhdr_xms endp
X
Xwseg_xms proc near
X ret
Xwseg_xms endp
X;=============================================================================
X
X
X;=============================================================================
X; THE FOLLOWING SECTION DEALS WITH ALL ROUTINES REQUIRED TO WRITE EMS RECORDS.
X;=============================================================================
Xinit_ems proc near
X ret
Xinit_ems endp
X
Xwhdr_ems proc near
X ret
Xwhdr_ems endp
X
Xwseg_ems proc near
X ret
Xwseg_ems endp
X;=============================================================================
X
X
X;=============================================================================
X; THE FOLLOWING SECTION DEALS WITH ALL ROUTINES REQUIRED TO WRITE FILES.
X;=============================================================================
X;-----------------------------------------------------------------------------
X; Attempt to create a temporary file. If the tempfile name is NIL then return
X; with the cary flag set.
Xinit_file proc near
X mov al, [tmpname]
X or al, al
X je err_init_file
X mov dx, offset tmpname
X xor cx, cx
X mov ah, 03cH
X int 21H
X jc err_init_file ; if carry set then failure
X mov [tmphandle], ax ; init swapping
X mov [swap], swap_file
X jmp exit_init_file
Xerr_init_file: stc
Xexit_init_file: ret
Xinit_file endp
X
X
X;-----------------------------------------------------------------------------
X; This routine writes a segment header to a file.
X; The header is a seven byte record formatted as follows:
X; segment address - of data
X; offset address - of data
X; length in paragraphs - of data
X; mode - 1 => segment header (allocate seg on read)
X; 0 => subsegment, don't allocate on read.
X; Routine takes three arguments:
X; di:dx segment:offset of segment
X; si number of paragraphs to write.
X; al mode of header to write
Xwhdr_file proc near
X mov [word ptr tmpseg], di ; save the segment/offset
X mov [word ptr tmpseg+2], dx
X mov [word ptr tmpseg+4], si ; save the segment length
X mov [tmpseg+6], al
X mov dx, offset tmpseg ; write the header record out
X mov cx, 7
X mov bx, [tmphandle]
X mov ah, 040H
X int 21H
X jc exit_whdr_file ; make sure it worked
X cmp ax, 7
X je exit_whdr_file ; oh oh, disk is full!
Xerr_whdr_file: stc
Xexit_whdr_file: ret
Xwhdr_file endp
X
X
X;-----------------------------------------------------------------------------
X; Write a segment to the temporary file whose handle is in cs:tmphandle
X; Parameters for the write are assumed to be stored in the tmpseg data area.
X; function returns carry set if failed, carry clear otherwise.
Xwseg_file proc near
X push ds
X mov ds, word ptr cs:tmpseg ; Now write the whole segment
X mov dx, word ptr cs:tmpseg+2
X mov cx, word ptr cs:tmpseg+4
X mov bx, cs:tmphandle
X mov ah, 040H
X int 21H
X pop ds
X jc exit_wseg_file ; make sure it worked
X cmp ax, [word ptr tmpseg+4]
X je exit_wseg_file
Xerr_wseg_file: stc ; it failed (usually disk full)
Xexit_wseg_file: ret
Xwseg_file endp
X;=============================================================================
X
X
X;=============================================================================
X; _exec: THIS IS THE MAIN ENTRY ROUTINE TO THIS MODULE
X;=============================================================================
X; This is the main entry routine into the swap code and corresponds to the
X; following C function call:
X;
X; exec( int swap, char far *program, char far *cmdtail,
X; int environment_seg, int env_size, char far *tmpfilename );
X;
X; Exec performs the following:
X; 1. set up the local code segment copies of arguments to the exec call.
X; 2. switch to a local stack frame so that we don't clobber the user
X; stack.
X; 3. save old interrupt vectors for ctrl-brk.
X; 4. install our own handler for the ctrl-brk interrupt, our handler
X; terminates the current running ess, proc and returns with non-zero
X; status code.
X; 5. get our psp
X; 6. setup arguments for exec call
X; 7. exec the program, save result code on return.
X; 8. restore previous ctrl-brk and crit-error handler.
X; 9. restore previous ess proc stack, and segment registers.
X; 10. return from exec with child result code in AX
X; and global _Interrupted flag set to true if child execution was
X; interrupted.
X
X; NOTE: When first called the segments here assume the standard segment
X; settings.
X assume cs:@code, ds:DGROUP,es:DGROUP,ss:DGROUP
X
X public _exec
X_exec proc
X push bp ; set up the stack frame
X mov bp, sp
X push si ; save registers we shouldn't step on.
X push di
X push ds
X
X; set up for copying of parameters passed in with long pointers.
X push cs ; going to use lodsb/stosb, set up es
X pop es ; as destination.
X assume es:@code ; let the assembler know :-)
X cld ; make sure direction is right
X
X; Copy all parameters into the bottom of the code segment. After doing so we
X; will immediately switch stacks, so that the user stack is preserved intact.
X mov ax, ss:[a_swap] ; save swap
X mov es:swap, ax
X mov ax, ss:[a_env] ; save env seg to use
X mov es:envseg, ax
X mov ax, ss:[a_esiz] ; get environment's size
X mov es:envsize, ax
X
X mov di, offset cs:cmdpath ; copy the command
X lds si, ss:[a_prog] ; 65 bytes worth
X mov cx, 65
X call copy_data
X
X mov di, offset cs:cmdtail ; copy the command tail
X lds si, ss:[a_tail] ; 129 bytes worth
X mov cx, 129
X call copy_data
X
X mov di, offset cs:tmpname ; copy the temp file name
X lds si, ss:[a_tmp] ; 65 bytes worth.
X mov cx, 65
X call copy_data
X
X; Now we save the current ss:sp stack pointer and swap stack to our temporary
X; stack located in the current code segment. At the same time we reset the
X; segment pointers to point into the code segment only.
Xswap_stacks: mov ax, ss
X mov es:old_ss, ax
X mov es:old_sp, sp
X mov ax, cs
X mov ds, ax
X mov ss, ax ; set ss first, ints are then
X mov sp, offset cs:exec_sp ; disabled for this instr too
X assume ds:@code, ss:@code ; let the assembler know :-)
X
X; Now we save the old control break and critical error handler addresses.
X; We replace them by our own routines found in the resident portion of the
X; swapping exec code.
Xset_handlers: mov [interrupted], 0 ; clear interrupted flag
X mov [retcode], 0 ; clear the return code
X mov ax, 03523H ; get int 23 handler address
X int 21H
X mov cs:old_ctl_brk_off, bx
X mov cs:old_ctl_brk_seg, es
X mov dx, offset ctl_brk_handler
X mov ax, 02523H ; set int 23 handler address
X int 21H
X
X mov ax, 03524H ; get int 24 handler address
X int 21H
X mov cs:old_crit_err_off, bx
X mov cs:old_crit_err_seg, es
X mov dx, offset crit_err_handler
X mov ax, 02524H ; set int 24 handler address
X int 21H
X
X; Go and execute the child, we've set up all of it's parameters. The do_exec
X; routine will attempt to perform a swap of the code if requested to do so by
X; a non-zero value in the variable cs:swap.
X mov ah, 062H ; get the psp
X int 21H
X mov cs:psp, bx
X call do_exec
X
X; We're back from the exec, so fix things up the way they were.
X; Restore the old control-break and critical-error handlers.
X lds dx, cs:old_ctl_brk
X mov ax, 02523H
X int 21H
X lds dx, cs:old_crit_err
X mov ax, 02524H
X int 21H
X
X; Restore previous program stack segment registers, and data segment.
X mov ax, cs:old_ss
X mov ss, ax ; mov into ss first, that way
X mov sp, cs:old_sp ; no interrupts in this instr.
X pop ds
X
X; Tell the assembler we have swaped segments again.
X assume ds:DGROUP,es:DGROUP,ss:DGROUP
X
X; Set the global Interrupted flag so that parent can tell it was interrupted.
X mov ax, seg DGROUP:_Interrupted
X mov es, ax
X mov ax, cs:interrupted
X mov es:_Interrupted, ax
X
X; Set the global errno value to reflect the success/failure of the DOS
X; exec call.
X mov ax, seg DGROUP:_errno
X mov es, ax
X mov ax, cs:ex_error
X mov es:_errno, ax
X
X; Fetch the child's return code, pop rest of stuff off of the stack
X; and return to the caller.
X mov ax, cs:retcode
X pop di
X pop si
X pop bp
X ret
X_exec endp
X
Xend
SHAR_EOF
echo "File msdos/exec.asm is complete"
chmod 0440 msdos/exec.asm || echo "restore of msdos/exec.asm fails"
echo "x - extracting msdos/dirlib.h (Text)"
sed 's/^X//' << 'SHAR_EOF' > msdos/dirlib.h &&
X/* DIRLIB.H by M. J. Weinstein Released to public domain 1-Jan-89 */
X
X#ifndef _DIRLIB_h_
X#define _DIRLIB_h_
X
X#include <stdio.h>
X#include "stdmacs.h"
X
X#define MAXNAMLEN 15
X
Xstruct direct {
X long d_ino;
X unsigned short d_reclen;
X unsigned short d_namlen;
X char d_name[MAXNAMLEN+1];
X};
X
Xtypedef struct {
X char fcb[21];
X char attr;
X short time;
X short date;
X long size;
X char name[13];
X} DTA;
X
Xtypedef struct {
X DTA dd_dta; /* disk transfer area for this dir. */
X short dd_stat; /* status return from last lookup */
X char dd_name[1]; /* full name of file -- struct is extended */
X} DIR;
X
Xextern DIR *opendir ANSI((char *));
Xextern struct direct *readdir ANSI((DIR *));
Xextern long telldir ANSI((DIR *));
Xextern void seekdir ANSI((DIR *, long));
Xextern void closedir ANSI((DIR *));
Xextern DTA *findfirst ANSI((char *, DTA *));
Xextern DTA *findnext ANSI((DTA *));
X
X#define rewinddir(dirp) seekdir(dirp,0L)
X#endif
SHAR_EOF
chmod 0440 msdos/dirlib.h || echo "restore of msdos/dirlib.h fails"
echo "x - extracting msdos/dirbrk.c (Text)"
sed 's/^X//' << 'SHAR_EOF' > msdos/dirbrk.c &&
X/* RCS -- $Header: /u2/dvadura/src/generic/dmake/src/msdos/RCS/dirbrk.c,v 1.1 90/10/06 12:05:21 dvadura Exp $
X-- SYNOPSIS -- define the directory separator string.
X--
X-- DESCRIPTION
X-- Define this string for any character that may appear in a path name
X-- and can be used as a directory separator.
X--
X-- AUTHOR
X-- Dennis Vadura, dvadura at watdragon.uwaterloo.ca
X-- CS DEPT, University of Waterloo, Waterloo, Ont., Canada
X--
X-- COPYRIGHT
X-- Copyright (c) 1990 by Dennis Vadura. All rights reserved.
X--
X-- This program is free software; you can redistribute it and/or
X-- modify it under the terms of the GNU General Public License
X-- (version 1), as published by the Free Software Foundation, and
X-- found in the file 'LICENSE' included with this distribution.
X--
X-- This program is distributed in the hope that it will be useful,
X-- but WITHOUT ANY WARRANTY; without even the implied warrant of
X-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
X-- GNU General Public License for more details.
X--
X-- You should have received a copy of the GNU General Public License
X-- along with this program; if not, write to the Free Software
X-- Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
X--
X-- LOG
X-- $Log: dirbrk.c,v $
X * Revision 1.1 90/10/06 12:05:21 dvadura
X * dmake Release, Version 3.6
X *
X*/
X
X#include "extern.h"
X#include <ctype.h>
X
X/* dos uses /, \, and : */
Xchar* DirBrkStr = "/\\:";
X
X/*
X** Return TRUE if the name is the full specification of a path name to a file
X** starting at the root of the file system, otherwise return FALSE
X*/
Xint
XIf_root_path(name)
Xchar *name;
X{
X return( (strchr(DirBrkStr, *name) != NIL(char)) ||
X (isalpha(*name) && name[1] == ':') );
X}
SHAR_EOF
chmod 0440 msdos/dirbrk.c || echo "restore of msdos/dirbrk.c fails"
echo "x - extracting msdos/config.mk (Text)"
sed 's/^X//' << 'SHAR_EOF' > msdos/config.mk &&
X# This is an OS specific configuration file
X# It assumes that OBJDIR, TARGET and DEBUG are previously defined.
X# It defines CFLAGS, LDARGS, CPPFLAGS, STARTUPFILE, LDOBJS
X# It augments SRC, OBJDIR, TARGET, CFLAGS, LDLIBS
X#
X
X# Memory model to compile for
X# set to s - small, m - medium, c - compact, l - large
XMODEL = c
X
XSTARTUPFILE = $(OS)/startup.mk
X
XCPPFLAGS = $(CFLAGS)
XLDOBJS = $(CSTARTUP) $(OBJDIR)/{$(<:f)}
XLDARGS = @$(LDTMPOBJ),$(TARGET),NUL.MAP$(LDTAIL)
XLDTAIL = ,@$(LDTMPLIB)$(LDFLAGS) NUL.DEF
XLDTMPOBJ = <+$(LDOBJS:s,/,\\,:t"+\n")\n+>
XLDTMPLIB = <+$(LDLIBS:s,/,\\,:t"+\n")\n+>
X
X# Debug flags
XDB_CFLAGS = -DDBUG -v
XDB_LDFLAGS = /v
XDB_LDLIBS =
X
X# NO Debug flags
XNDB_CFLAGS =
XNDB_LDFLAGS =
XNDB_LDLIBS =
X
X# Local configuration modifications for CFLAGS.
XCFLAGS += -I$(OS)
X
X# Common MSDOS source files.
X# Define NOSWAP to non-null for the swap code to be excluded on making.
X.IF $(NOSWAP) == $(NULL)
X SWP_SRC = find.c spawn.c
X ASRC += exec.asm
X.END
X
XOS_SRC += ruletab.c dirbrk.c runargv.c arlib.c _chdir.c switchar.c rmprq.c\
X $(SWP_SRC)
XSRC += $(OS_SRC)
X.SETDIR=$(OS) : $(ASRC) $(OS_SRC)
X
X# Provide our own %$O : %$S rule.
X%$O : %$S
X $(AS) $(ASFLAGS) $(<:s,/,\,);
X mv $(@:f) $(OBJDIR)
X
X# Set source dirs so that we can find files named in this
X# config file.
X.SOURCE.h : $(OS)
X
X# See if we modify anything in the lower levels.
X.IF $(OSRELEASE) != $(NULL)
X .INCLUDE .IGNORE : $(OS)$(DIRSEPSTR)$(OSRELEASE)$(DIRSEPSTR)config.mk
X.END
X
X# Set the proper macros based on whether we are making the debugging version
X# or not.
X.IF $(DEBUG)
X CFLAGS += $(DB_CFLAGS)
X LDFLAGS += $(DB_LDFLAGS)
X LDLIBS += $(DB_LDLIBS)
X
X SILENT := $(.SILENT)
X .SILENT := yes
X TARGET := db$(TARGET)
X OBJDIR := $(OBJDIR).dbg
X .SILENT := $(SILENT)
X
X SRC += dbug.c malloc.c
X HDR += db.h
X
X .SOURCE.c : common
X .SOURCE.h : common
X.ELSE
X CFLAGS += $(NDB_CFLAGS)
X LDFLAGS += $(NDB_LDFLAGS)
X LDLIBS += $(NDB_LDLIBS)
X.END
SHAR_EOF
chmod 0640 msdos/config.mk || echo "restore of msdos/config.mk fails"
echo "x - extracting msdos/arlib.c (Text)"
sed 's/^X//' << 'SHAR_EOF' > msdos/arlib.c &&
X/* RCS -- $Header: /u2/dvadura/src/generic/dmake/src/msdos/RCS/arlib.c,v 1.1 90/10/06 12:05:19 dvadura Exp $
X-- SYNOPSIS -- Library access code.
X--
X-- DESCRIPTION
X-- This implementation uses the library timestamp inplace of the
X-- library member timestamp.
X--
X-- AUTHOR
X-- Dennis Vadura, dvadura at watdragon.uwaterloo.ca
X-- CS DEPT, University of Waterloo, Waterloo, Ont., Canada
X--
X-- COPYRIGHT
X-- Copyright (c) 1990 by Dennis Vadura. All rights reserved.
X--
X-- This program is free software; you can redistribute it and/or
X-- modify it under the terms of the GNU General Public License
X-- (version 1), as published by the Free Software Foundation, and
X-- found in the file 'LICENSE' included with this distribution.
X--
X-- This program is distributed in the hope that it will be useful,
X-- but WITHOUT ANY WARRANTY; without even the implied warrant of
X-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
X-- GNU General Public License for more details.
X--
X-- You should have received a copy of the GNU General Public License
X-- along with this program; if not, write to the Free Software
X-- Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
X--
X-- LOG
X-- $Log: arlib.c,v $
X * Revision 1.1 90/10/06 12:05:19 dvadura
X * dmake Release, Version 3.6
X *
X*/
X
X#include "extern.h"
X#include "stdmacs.h"
X#include "vextern.h"
X
Xtime_t
Xseek_arch(name, lib)
Xchar* name;
Xchar* lib;
X{
X static int warned = FALSE;
X
X if (!warned && !(Glob_attr&A_SILENT))
X warned = TRUE,
X Warning("Can't extract library member timestamp;\n\
X using library timestamp instead.");
X return (Do_stat(lib, NULL, NULL));
X}
X
Xint
Xtouch_arch(name, lib)
Xchar* name;
Xchar* lib;
X{
X static int warned = FALSE;
X
X if (!warned && !(Glob_attr&A_SILENT))
X warned = TRUE,
X Warning("Can't update library member timestamp;\n\
X touching library instead.");
X return (Do_touch(lib, NULL, NULL));
X}
X
SHAR_EOF
chmod 0440 msdos/arlib.c || echo "restore of msdos/arlib.c fails"
echo "x - extracting msdos/_chdir.c (Text)"
sed 's/^X//' << 'SHAR_EOF' > msdos/_chdir.c &&
X/* RCS -- $Header: /u2/dvadura/src/generic/dmake/src/msdos/RCS/_chdir.c,v 1.1 90/10/06 12:05:17 dvadura Exp $
X-- SYNOPSIS -- Change directory.
X--
X-- DESCRIPTION
X-- Under DOS change the current drive as well as the current directory.
X--
X-- AUTHOR
X-- Dennis Vadura, dvadura at watdragon.uwaterloo.ca
X-- CS DEPT, University of Waterloo, Waterloo, Ont., Canada
X--
X-- COPYRIGHT
X-- Copyright (c) 1990 by Dennis Vadura. All rights reserved.
X--
X-- This program is free software; you can redistribute it and/or
X-- modify it under the terms of the GNU General Public License
X-- (version 1), as published by the Free Software Foundation, and
X-- found in the file 'LICENSE' included with this distribution.
X--
X-- This program is distributed in the hope that it will be useful,
X-- but WITHOUT ANY WARRANTY; without even the implied warrant of
X-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
X-- GNU General Public License for more details.
X--
X-- You should have received a copy of the GNU General Public License
X-- along with this program; if not, write to the Free Software
X-- Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
X--
X-- LOG
X-- $Log: _chdir.c,v $
X * Revision 1.1 90/10/06 12:05:17 dvadura
X * dmake Release, Version 3.6
X *
X*/
X
X#include <dos.h>
X#include "sysintf.h"
X#include "vextern.h"
X
X#undef chdir /* sysintf.h defines it to _chdir for DOS */
X
Xint
X_chdir(path)
Xchar *path;
X{
X int res;
X
X res = chdir(path);
X
X#if defined(OS2)
X if (res != -1 && path[1] == ':' && *path != *Pwd) {
X unsigned new_drive;
X unsigned max_drives;
X
X /* for OS2 we must change drive without using intdos() */
X new_drive = (*path & ~0x20) - 'A' + 1;
X _dos_setdrive(new_drive, &max_drives);
X }
X#else
X if (res != -1 && path[1] == ':' && *path != *Pwd) {
X union REGS reg;
X
X /* we must change the logged drive, since the chdir worked. */
X reg.h.ah = 0x0E;
X reg.h.dl = (*path & ~0x20) - 'A';
X intdos(®, ®);
X }
X#endif /* OS2 */
X return (res);
X}
X
SHAR_EOF
chmod 0440 msdos/_chdir.c || echo "restore of msdos/_chdir.c fails"
echo mkdir - man
mkdir man
echo "x - extracting man/dmake.tf (Text)"
sed 's/^X//' << 'SHAR_EOF' > man/dmake.tf &&
X.\" Copyright (c) 1990 Dennis Vadura, All rights reserved.
X.\"
X.ds TB "0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.2i +0.5i +0.5i +2.0i
X.de Ip
X.fi
X.nr Ip \w\\$1
X.IP "\\$1" \\n(Ipu
X\\$2
X.nf
X..
X.de Is
X.nr )I \w\\$1u
X..
X.de Ii
X.in \\n()Ru
X.nr )E 1
X.ns
X.ne 1.1v
X.it 1 }N
X.di ]B
X\&\\$1
X..
X.TH DMAKE p "UW" "Version 3.50" "Unsupported Software"
X.SH NAME
X\fBdmake\fR \- maintain program groups, or interdependent files
X.SH SYNOPSIS
X.B dmake
X[-AeEhiknpqersStTuvVx] [-P#] [macro[*][+][:]=\fIvalue\fP] [-f file] [target ...]
X.SH DESCRIPTION
X.PP
X.B dmake
Xexecutes commands found in an external file called a
X.I makefile
Xto update one or more target names.
XEach target may depend on zero or more prerequisite targets.
XIf any of the target's prerequisites is newer than the target or if the target
Xitself does not exist, then
X.B dmake
Xwill attempt to make the target.
X.PP
XIf no
X.B \-f
Xcommand line option is present then
X.B dmake
Xsearches for an existing
X.I makefile
Xfrom the list of prerequisites specified for the special target \fI.MAKEFILES\fR
X(see the STARTUP section for more details).
XIf "-" is the name of the file specified to the
X.B -f
Xflag then \fBdmake\fR uses standard input as the source of the makefile text.
X.PP
XAny macro definitions (arguments with embedded
X.Q "="
Xsigns) that appear on the command line are processed first
Xand supercede definitions for macros of the same name found
Xwithin the makefile. In general it is impossible for definitions found
Xinside the makefile to redefine a macro defined on the command line, see the
XMACROS section for an exception.
X.PP
XIf no
X.I target
Xnames are specified on the command line, then \fBdmake\fR uses the first
Xnon-special target found in the makefile as the default target.
XSee the
X.B "SPECIAL TARGETS"
Xsection for the list of special targets and their function.
X\fBdmake\fR is a re-implementation of the UNIX Make utility with
Xsignificant enhancements. Makefiles written for most previous
Xversions of
X.I make
Xwill be handled correctly by
X.B dmake.
XKnown differences between \fBdmake\fR and other versions of make
Xare discussed in the
X.B COMPATIBILITY
Xsection found at the end of this document.
X.SH OPTIONS
X.IP "\fB\-A\fR"
XEnable AUGMAKE special inference rule transformations (see the
X.Q "PERCENT(%) RULES"
Xsection), these are set to off by default.
X.IP "\fB\-e\fR"
XRead the environment and define all strings of the
Xform '\fBENV-VAR\fP=\fIevalue\fP'
Xdefined within as macros whose name is \fBENV-VAR\fP,
Xand whose value is '\fIevalue\fP'.
XThe environment is processed prior to processing the user
Xspecified makefile thereby allowing definitions in the makefile to override
Xdefinitions in the environment.
X.IP "\fB\-E\fR"
XSame as -e, except that the environment is processed after the
Xuser specified makefile has been processed
X(thus definitions in the environment override definitions in the makefile).
XThe -e and -E options are mutually exclusive.
XIf both are given the latter one takes effect.
X.IP "\fB\-f file\fR"
XUse \fBfile\fR as the source for the makefile text.
XOnly one \fB\-f\fR option is allowed.
X.IP "\fB\-h\fR"
XPrint the command summary for \fBdmake\fR.
X.IP "\fB\-i\fR"
XTells \fBdmake\fR to ignore errors, and continue making other targets.
XThis is equivalent to the .IGNORE attribute or macro.
X.IP "\fB\-k\fR"
XCauses \fBdmake\fR to ignore errors caused by command execution and to make
Xall targets not depending on targets that could not be made.
XOrdinarily \fBdmake\fR stops after a command returns a non-zero status,
Xspecifying \fB\-k\fR causes \fBdmake\fR to ignore the error
Xand continue to make as much as possible.
X.IP "\fB\-n\fR"
XCauses \fBdmake\fR to print out what it would have executed,
Xbut does not actually execute the commands. A special check is made for
Xthe string "$(MAKE)" inside a recipe line, if found, the line is expanded
Xand invoked, thereby enabling recursive makes to give a full
Xdescription of all that they will do.
XThe check for "$(MAKE)" is disabled inside group recipes.
X.IP "\fB\-p\fR"
XPrint out a version of the digested makefile in human readable form.
X(useful for debugging, but cannot be re-read by \fBdmake\fP)
X.IP "\fB\-P#\fR"
XOn systems that support multi-processing cause \fBdmake\fP to use \fI#\fP
Xconcurrent child processes to make targets. See the
X.Q "MULTI PROCESSING"
Xsection for more information.
X.IP "\fB\-q\fR"
XCheck and see if the target is up to date. Exits with code 0 if up to date,
X1 otherwise.
X.IP "\fB\-r\fR"
XTells \fBdmake\fR not to read the initial startup makefile, see STARTUP
Xsection for more details.
X.IP "\fB\-s\fR"
XTells \fBdmake\fR to do all its work silently and not echo the commands it is
Xexecuting to stdout (also suppresses warnings).
XThis is equivalent to the .SILENT attribute or macro.
X.IP "\fB\-S\fR"
XForce sequential execution of recipes on architectures which support
Xconcurrent makes. For backward compatibility with old makefiles that have
Xnasty side-effect prerequisite dependencies.
X.IP "\fB\-t\fR"
XCauses \fBdmake\fR to touch the targets and bring them up to date
Xwithout executing any commands.
X.IP "\fB\-T\fR"
XTells \fBdmake\fP to not perform transitive closure on the inference graph.
X.IP "\fB\-u\fR"
XForce an unconditional update. (ie. do everything that would
Xbe done if everything that a target depended on was out of date)
X.IP "\fB\-v\fR"
XVerbose flag, when making targets print to stdout what we are going to make
Xand what we think it's timestamp is.
X.IP "\fB\-V\fR"
XPrint the version of \fBdmake\fR, and values of builtin macros.
X.IP "\fB\-x\fR"
XUpon processing the user makefile export all non-internally defined macros
Xto the user's environment. This option together with the -e option
Xallows SYSV AUGMAKE recursive makes to function as expected.
X.SH INDEX
XHere is a list of the sections that follow and a short description of each.
XPerhaps you won't have to read the whole man page to find
Xwhat you need.
X.IP \fBSTARTUP\fP 1.9i
XDescribes \fBdmake\fP initialization.
X.IP \fBSYNTAX\fP 1.9i
XDescribes the syntax of makefile expressions.
X.IP \fBATTRIBUTES\fP 1.9i
XDescribes the notion of attributes and how they are used when
Xmaking targets.
X.IP \fBMACROS\fP 1.9i
XDefining and expanding macros.
X.IP "\fBRULES AND TARGETS" 1.9i
XHow to define targets and their prerequisites.
X.IP \fBRECIPES\fP 1.9i
XHow to tell \fBdmake\fP how to make a target.
X.IP "\fBTEXT DIVERSIONS\fP" 1.9i
XHow to use text diversions in recipes and macro expansions.
X.IP "\fBSPECIAL TARGETS\fP" 1.9i
XSome targets are special.
X.IP "\fBSPECIAL MACROS\fP" 1.9i
XMacros used by \fBdmake\fP to alter the processing of the makefile,
Xand those defined by \fBdmake\fP for the user.
X.IP "\fBCONTROL MACROS\fP" 1.9i
XItemized list of special control macros.
X.IP "\fBRUN-TIME MACROS\fP" 1.9i
XDiscussion of special run-time macros such as $@ and $<.
X.IP "\fBFUNCTION MACROS\fP" 1.9i
XGNU style function macros, only $(mktmp ...) for now.
X.IP "\fBDYNAMIC PREREQUISITES\fP" 1.9i
XProcessing of prerequisites which contain macro expansions in their name.
X.IP "\fBBINDING TARGETS\fP" 1.9i
XThe rules that \fBdmake\fP uses to bind
Xa target to an existing file in the file system.
X.IP "\fBPERCENT(%) RULES\fP" 1.9i
XSpecification of recipes to be used by the inference algorithm.
X.IP "\fBMAKING INFERENCES\fP" 1.9i
XThe rules that \fBdmake\fP uses when inferring how to make a target which
Xhas no explicit recipe. This and the previous section are really a single
Xsection in the text.
X.IP "\fBMAKING TARGETS\fP" 1.9i
XHow \fBdmake\fP makes targets other than libraries.
X.IP "\fBMAKING LIBRARIES\fP" 1.9i
XHow \fBdmake\fP makes libraries.
X.IP "\fBMULTI PROCESSING\fP" 1.9i
XDiscussion of \fBdmake's\fP parallel make facilities for architectures that
Xsupport them.
X.IP "\fBCONDITIONALS\fP" 1.9i
XConditional expressions which control the processing of the makefile.
X.IP "\fBEXAMPLES\fP" 1.9i
XSome hopefully useful examples.
X.IP "\fBCOMPATIBILITY\fP" 1.9i
XHow \fBdmake\fP compares with previous versions of make.
X.IP "\fBLIMITS\fP" 1.9i
XLimitations of \fBdmake\fP.
X.IP \fBPORTABILITY\fP 1.9i
XComments on writing portable makefiles.
X.IP \fBFILES\fP 1.9i
XFiles used by \fBdmake\fP.
X.IP "\fBSEE ALSO\fP" 1.9i
XOther related programs, and man pages.
X.IP "\fBAUTHOR\fP" 1.9i
XThe guy responsible for this thing.
X.IP \fBBUGS\fP 1.9i
XHope not.
X.SH STARTUP
XWhen
X.B dmake
Xbegins execution it first processes the command line and then processes
Xan initial startup-makefile.
XThis is followed by an attempt to locate and process a user supplied makefile.
XThe startup file defines the default values of all required control macros
Xand the set of default rules for making inferences.
XWhen searching for the startup makefile,
X.B dmake
Xsearches the following locations, in order, until a startup file is located:
X.LP
X.RS
X.IP 1.
XThe location given as the value of the macro MAKESTARTUP defined on the
Xcommand line.
X.IP 2.
XThe location given as the value of the environment variable MAKESTARTUP
Xdefined in the current environment.
X.IP 3.
XThe location given as the value of the macro MAKESTARTUP defined internally
Xwithin \fBdmake\fP.
X.RE
X.LP
XThe above search is disabled by specifying the -r option on the command line.
XAn error is issued if a startup makefile cannot be found and the -r
Xoption was not specified.
XA user may substitute a custom startup file by defining
Xthe MAKESTARTUP environment variable or by redefining the
XMAKESTARTUP macro on the command line.
XTo determine where
X.B dmake
Xlooks for the default startup file, check your environment or issue the command
X\fI"dmake -V"\fP.
X.PP
XA similar search is performed to locate a default user makefile when no
X\fB-f\fP command line option is specified.
XThe special target .MAKEFILES is defined by default.
XThis target's prerequisite list specifies the names of files and the order that
X\fBdmake\fP will use to search for them when attempting to locate the default
Xmakefile.
XA typical definition for this target is:
X.RS
X.sp
X\&.MAKEFILES : makefile.mk Makefile makefile
X.sp
X.RE
X\fBdmake\fP will first look for makefile.mk and then the others.
XIf a prerequisite
Xcannot be found \fBdmake\fP will try to make it before going on to the next
Xprerequisite. For example, makefile.mk can be checked out of an RCS file
Xif the proper rules for doing so are defined in the startup file.
X.SH SYNTAX
XThis section is a summary of the syntax of makefile statements.
XThe description is given in a style similar to BNF, where { } enclose
Xitems that may appear zero or more times, and [ ] enclose items that
Xare optional. Alternative productions for a left hand side are indicated
Xby '->', and newlines are significant. All symbols in \fBbold\fP type
Xare text or names representing text supplied by the user.
X.sp 2
X.RS
X.Ip "Makefile" "\(-> { Statement }"
X.Ip "Statement" "\(-> Macro-Definition"
X\(-> Conditional
X\(-> Rule-Definition
X\(-> Attribute-Definition
X.Ip "Macro-Definition" "\(-> \fBMACRO = LINE\fP"
X\(-> \fBMACRO *= LINE\fP
X\(-> \fBMACRO := LINE\fP
X\(-> \fBMACRO *:= LINE\fP
X\(-> \fBMACRO += LINE\fP
X\(-> \fBMACRO +:= LINE\fP
X.Ip "Conditional \(-> " "\fB\&.IF\fR expression"
X Makefile
X[ \fB.ELSE\fR
X Makefile ]
X\fB\&.END\fR
X.Ip expression "\(-> \fBLINE\fR"
X\(-> \fBSTRING == LINE\fR
X\(-> \fBSTRING != LINE\fR
X.sp
X.Ip "Rule-Definition \(-> " "target-definition"
X [ recipe ]
X.PP
Xtarget-definition \(-> targets [attrs] op { \fBPREREQUISITE\fP } [\fB;\fR rcp-line]
X.Ip "targets" "\(-> target { targets }"
X\(-> \fB"\fRtarget\fB"\fR { targets }
X.Ip "target" "\(-> special-target"
X\(-> \fBTARGET\fR
X.Ip "attrs" "\(-> attribute { attrs }"
X\(-> \fB"\fRattribute\fB"\fR { attrs }
X.Ip "op" "\(-> \fB:\fR { modifier }"
X.Ip "modifier" "\(-> \fB:\fR"
X\(-> \fB^\fR
X\(-> \fB!\fR
X\(-> \fB-\fR
X.Ip "recipe" "\(-> { \fBTAB\fR rcp-line }"
X\(-> [\fB@\fR][\fB%\fR][\fB-\fR] \fB[
X.Is "recipe \(-> "
X.Ii " "
X \fR{ \fBLINE\fR }
X.Ii " "
X\fB]\fR
X.Ip "rcp-line" "\(-> [\fB@\fR][\fB%\fR][\fB-\fR][\fB+\fR] \fBLINE\fR"
X.sp
X.Ip Attribute-Definition "\(-> attrs \fB:\fR targets"
X.sp
X.Ip "attribute" "\(-> \fB.EPILOG\fR"
X\(-> \fB.IGNORE\fR
X\(-> \fB.LIBRARY\fR
X\(-> \fB.MKSARGS\fR
X\(-> \fB.NOINFER\fR
X\(-> \fB.PRECIOUS\fR
X\(-> \fB.PROLOG\fR
X\(-> \fB.SETDIR=\fIpath\fP\fR
X\(-> \fB.SILENT\fR
X\(-> \fB.SEQUENTIAL\fR
X\(-> \fB.SWAP\fR
X\(-> \fB.USESHELL\fR
X\(-> \fB.SYMBOL\fR
X\(-> \fB.UPDATEALL\fR
X.Ip "special-target" "\(-> \fB.ERROR\fR"
X\(-> \fB.EXPORT\fR
X\(-> \fB.GROUPEPILOG\fR
X\(-> \fB.GROUPPROLOG\fR
X\(-> \fB.IMPORT\fR
X\(-> \fB.INCLUDE\fR
X\(-> \fB.INCLUDEDIRS\fR
X\(-> \fB.MAKEFILES\fR
X\(-> \fB.REMOVE\fR
X\(-> \fB.SOURCE\fR
X\(-> \fB.SOURCE.\fIsuffix\fR
X\(-> .\fIsuffix1\fR.\fIsuffix2\fR
X.fi
X.RE
X.sp 1
X.PP
XWhere, \fBTAB\fP represents a <tab> character, \fBSTRING\fP represents an
Xarbitrary sequence of characters, and
X\fBLINE\fP represents a
Xpossibly empty sequence of characters terminated by a non-escaped
X(not immediately preceded by a backslash '\\') new-line character.
X\fBMACRO\fP, \fBPREREQUISITE\fP,
Xand \fBTARGET\fP each represent a string of characters not
Xincluding space or tab which respectively form the name of a macro,
Xprerequisite or target.
XThe name may itself be a macro expansion expression.
XA \fBLINE\fP can be continued over several physical lines by terminating it with
Xa single backslash character. Comments are initiated by the
Xpound '\fB#\fR' character and extend to the end of line.
XAll comment text is discarded, a '#' may be placed into the makefile text
Xby escaping it with '\\' (ie. \\# translates to # when
Xit is parsed).
XA group of continued lines may be commented out by placing a single # at the
Xstart of the first line of the group.
XA continued line may not span more than one makefile.
X.PP
X\fBwhite space\fP is defined to be any combination of
X<space>, <tab>, and the sequence \\<nl>
Xwhen \\<nl> is used to terminate a LINE.
XWhen processing \fBmacro\fP definition lines,
Xany amount of white space is allowed on either side of the macro operator
X(=, *=, :=, *:=, += or +:=), and
Xwhite space is stripped from both before and after the macro
Xvalue string.
XThe sequence \\<nl> is treated as
Xwhite space during recipe expansion
Xand is deleted from the final recipe string.
XYou must escape the \\<nl> with a \\ in order to get a \\ at the end
Xof a recipe line.
XThe \\<nl> sequence is deleted from macro values when they are expanded.
X.PP
XWhen processing \fBtarget\fP definition lines,
Xthe recipe for a target must, in general, follow the first definition
Xof the target (See the RULES AND TARGETS section for an exception), and
SHAR_EOF
echo "End of part 10"
echo "File man/dmake.tf is continued in part 11"
echo "11" > s2_seq_.tmp
exit 0
More information about the Comp.sources.misc
mailing list