home *** CD-ROM | disk | FTP | other *** search
Text File | 1992-01-29 | 40.0 KB | 1,319 lines |
- Newsgroups: comp.sources.misc
- From: dvadura@plg.waterloo.edu (Dennis Vadura)
- Subject: v27i124: dmake - dmake Version 3.8, Part23/41
- Message-ID: <1992Jan28.214411.19408@sparky.imd.sterling.com>
- X-Md4-Signature: 4de588d65345833e6b8d6b75f2153c38
- Date: Tue, 28 Jan 1992 21:44:11 GMT
- Approved: kent@sparky.imd.sterling.com
-
- Submitted-by: dvadura@plg.waterloo.edu (Dennis Vadura)
- Posting-number: Volume 27, Issue 124
- Archive-name: dmake/part23
- Environment: Atari-ST, Coherent, Mac, MSDOS, OS/2, UNIX
- Supersedes: dmake: Volume 19, Issue 22-58
-
- ---- Cut Here and feed the following to sh ----
- # this is dmake.shar.23 (part 23 of a multipart archive)
- # do not concatenate these parts, unpack them in order with /bin/sh
- # file dmake/msdos/exec.asm continued
- #
- if test ! -r _shar_seq_.tmp; then
- echo 'Please unpack part 1 first!'
- exit 1
- fi
- (read Scheck
- if test "$Scheck" != 23; then
- echo Please unpack part "$Scheck" next!
- exit 1
- else
- exit 0
- fi
- ) < _shar_seq_.tmp || exit 1
- if test -f _shar_wnt_.tmp; then
- sed 's/^X//' << 'SHAR_EOF' >> 'dmake/msdos/exec.asm' &&
- X call write_segment
- X jc abort_swap_out
- X
- ; We have now saved the portion of the program segment that will not remain
- ; resident during the exec. We should now walk the DOS allocation chain and
- ; write out all other segments owned by the current process.
- save_segments: mov ax, [psp]
- X dec ax
- X mov es, ax
- X mov bx, offset write_segment_data
- X call walk_arena_chain
- X jc abort_swap_out
- X
- ; Now we must walk the chain of allocated memory blocks again and free
- ; all those that are owned by the current process, except the one that is
- ; the current process' psp.
- free_segments: mov ax, [psp]
- X dec ax
- X mov es,ax
- X mov bx, offset free_dos_segment
- X call walk_arena_chain
- X jnc resize_program
- X jmp abort_exec_free ; can't fix it up now.
- X
- ; We now resize the program to the size specified by cs:rootsize. This will
- ; free most of the memory taken up by the current program segment.
- resize_program: mov es, [psp] ; es is segment to resize.
- X mov bx, [rootsize] ; bx is size of segment.
- X mov ah, 04aH ; resize memory block
- X int 21H
- X jnc swap_out_ok
- X jmp abort_exec_resize ; disaster
- swap_out_ok: ret
- X
- ; The swap out failed for some reason, so free any allocated resources
- ; and set the carry bit.
- abort_swap_out: mov bx, [swap]
- X call [free_resource+bx]
- X xor ax, ax
- X mov [swap], ax ; clear the swap flag
- X stc
- X ret
- swap_out endp
- X
- X
- ;=============================================================================
- ; CODE TO SET-UP FOR AND EXEC THE CHILD PROCESS
- ;=============================================================================
- ; Actually execute the program. If cs:swap is set, this code will invoke the
- ; swap-out/swap-in code as required.
- do_exec proc near
- X cmp [swap], 0 ; does the user want to swap?
- X je no_swap_out ; nope
- X call init_swap ; figger out where to swap to
- X jc no_swap_out ; if carry set then don't swap
- X call swap_out
- X
- no_swap_out: cmp [interrupted], 0 ; were we interrupted?
- X jne leave_exec ; yep, so clean up, don't exec
- X
- ; free passed in environment block if it is non zero.
- ; This way the parent program does not need to free it.
- X mov ax, [envseg]
- X or ax, ax
- X je setup_block
- X push ax
- X mov es, ax
- X mov ah, 49H
- X int 21H
- X pop ax
- X
- ; set up the parameter block for the DOS exec call.
- ; offset contents
- ; 00 segment address of environment to be passed,
- ; 0 => use parents env.
- ; 02 pointer to command tail for new process.
- ; 06 pointer to fcb1
- ; 0a pointer to fcb2
- setup_block: mov ax, [envseg]
- X mov [ex_envseg], ax
- X mov cx, cs
- X mov [word ptr ex_cmdtail], offset cmdtail
- X mov [word ptr ex_cmdtail+2], cx
- X
- ; set up registers for exec call
- ; ds:dx - pointer to pathname of program to execute
- ; es:bx - pointer to above parameter block
- X mov dx, offset cmdpath
- X mov es, cx
- X mov bx, offset exec_block
- X
- ; Under DOS 2.x exec is notorious for clobbering registers and guarantees
- ; 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
- ; returned from exec, so restore possibly clobbered registers.
- X mov ss, cs:ex_ss
- X mov sp, cs:ex_sp
- X pop ds
- X
- ; check to make certain the exec call worked.
- X jnc it_worked
- X
- ; exec call failed. Save return code from msdos.
- X mov [ex_error], ax
- X jmp leave_exec
- X
- it_worked: mov ah, 04dH ; get the return code
- X int 21H
- X cbw
- X mov [eretcode], ax
- X
- leave_exec: cmp [swap], 0 ; check swap, if non-zero swap back in
- X je no_swap_in
- X call swap_in
- X
- ; Clear the in_exec after the swap back in. This way we are guaranteed to
- ; get parent in and the resources freed should a ^C be hit when we are reading
- ; the image in.
- no_swap_in: mov [in_exec], 0
- X ret
- do_exec endp
- X
- X
- X
- ;==============================================================================
- ; Everything past this point is overwriten with the environment and new
- ; program after the currently executing program is swapped out.
- ;==============================================================================
- overlay_code_here label word
- X
- ;-----------------------------------------------------------------------------
- ; Figure out where we can swap to and initialize the resource we are going to
- ; use. We try XMS, EMS, and a tempfile (if specified), in that order. We set
- ; [cs:swap] to the correct value based on which of the resources exists.
- ; If none can be used, then [cs:swap] is set to 0, and no swap takes place.
- ; The exec code will still attempt to execute the child in this instance, but
- ; may fail due to lack of resources. Each swap_out_* routine must provide
- ; its own clean-up handler should it not be able to write all program
- ; segments to the swap resource.
- init_swap proc near
- X mov [swap], 0
- ;call init_xms
- ;jnc init_done
- ;call init_ems
- ;jnc init_done
- X call init_file
- init_done: ret
- init_swap endp
- X
- X
- ;-----------------------------------------------------------------------------
- ; This routine is used to walk the DOS allocated memory block chain
- ; starting at address supplied in the es register. For each block it
- ; calls the routine specified by the bx register with the segment length
- ; in si, and its address in di. It does not apply the routine to the
- ; segment if the segment is the same as the current program's [cs:psp] value.
- memheader 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
- memheader ends
- X
- walk_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
- ; Stop the search if the block is NOT owned by us. Ignore our own psp block
- ; and our environment segment block.
- X cmp ax, cs:psp ; is it owned by us?
- X jne walk_done ; NOPE! -- all done
- X cmp di, cs:envseg ; skip our environment
- X je next_block
- X cmp di, cs:psp ; skip our psp
- X je next_block
- X
- ; Now save state and call the routine pointed at by [bx].
- X push di
- X push si
- X push bx
- X call bx
- 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
- next_block: add di, si ; go on to next segment
- X mov es, di
- X jmp walk_arena_chain
- walk_done: clc
- exit_walk: ret
- walk_arena_chain endp
- X
- X
- ;-----------------------------------------------------------------------------
- ; This routine takes a dos segment found in the di register and free's it.
- free_dos_segment proc near
- X mov es, di ; free dos memory block
- X mov ah, 49H
- X int 21H
- X ret
- free_dos_segment endp
- X
- X
- ;-----------------------------------------------------------------------------
- ; Called to invoke write_segment with proper values in the al register. Only
- ; ever called from walk_arena_chain, and so al should be set to seg_alloc.
- write_segment_data label near
- X mov al, seg_alloc ; and fall through into write_segment
- ;-----------------------------------------------------------------------------
- ; This routine writes a segment as a block of data segments if the number of
- ; paragraphs to write exceeds 0x0fff (rarely the case).
- ; It stuffs the info into tmpseg, and then calls wheader and wseg to get the
- ; data out.
- ;
- ; di:dx segment:offset of segment; offset is ALWAYS zero.
- ; si number of paragraphs to write.
- ; al mode of header to write
- write_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
- do_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
- do_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
- exit_wseg: ret
- write_segment endp
- X
- X
- ;=============================================================================
- ; THE FOLLOWING SECTION DEALS WITH ALL ROUTINES REQUIRED TO WRITE XMS RECORDS.
- ;=============================================================================
- init_xms proc near
- X ret
- init_xms endp
- X
- whdr_xms proc near
- X ret
- whdr_xms endp
- X
- wseg_xms proc near
- X ret
- wseg_xms endp
- ;=============================================================================
- X
- X
- ;=============================================================================
- ; THE FOLLOWING SECTION DEALS WITH ALL ROUTINES REQUIRED TO WRITE EMS RECORDS.
- ;=============================================================================
- init_ems proc near
- X ret
- init_ems endp
- X
- whdr_ems proc near
- X ret
- whdr_ems endp
- X
- wseg_ems proc near
- X ret
- wseg_ems endp
- ;=============================================================================
- X
- X
- ;=============================================================================
- ; THE FOLLOWING SECTION DEALS WITH ALL ROUTINES REQUIRED TO WRITE FILES.
- ;=============================================================================
- ;-----------------------------------------------------------------------------
- ; Attempt to create a temporary file. If the tempfile name is NIL then return
- ; with the cary flag set.
- init_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
- err_init_file: stc
- exit_init_file: ret
- init_file endp
- X
- X
- ;-----------------------------------------------------------------------------
- ; This routine writes a segment header to a file.
- ; The header is a seven byte record formatted as follows:
- ; segment address - of data
- ; offset address - of data
- ; length in paragraphs - of data
- ; mode - 1 => segment header (allocate seg on read)
- ; 0 => subsegment, don't allocate on read.
- ; Routine takes three arguments:
- ; di:dx segment:offset of segment
- ; si number of paragraphs to write.
- ; al mode of header to write
- whdr_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!
- err_whdr_file: stc
- exit_whdr_file: ret
- whdr_file endp
- X
- X
- ;-----------------------------------------------------------------------------
- ; Write a segment to the temporary file whose handle is in cs:tmphandle
- ; Parameters for the write are assumed to be stored in the tmpseg data area.
- ; function returns carry set if failed, carry clear otherwise.
- wseg_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
- err_wseg_file: stc ; it failed (usually disk full)
- exit_wseg_file: ret
- wseg_file endp
- ;=============================================================================
- X
- X
- ;=============================================================================
- ; _exec: THIS IS THE MAIN ENTRY ROUTINE TO THIS MODULE
- ;=============================================================================
- ; This is the main entry routine into the swap code and corresponds to the
- ; following C function call:
- ;
- ; exec( int swap, char far *program, char far *cmdtail, int environment_seg,
- ; char far *tmpfilename );
- ;
- ; Exec performs the following:
- ; 1. set up the local code segment copies of arguments to the exec call.
- ; 2. switch to a local stack frame so that we don't clobber the user
- ; stack.
- ; 3. save old interrupt vectors for ctrl-brk.
- ; 4. install our own handler for the ctrl-brk interrupt, our handler
- ; terminates the current running process, and returns with non-zero
- ; status code.
- ; 5. get our psp
- ; 6. setup arguments for exec call
- ; 7. exec the program, save result code on return.
- ; 8. restore previous ctrl-brk and crit-error handler.
- ; 9. restore previous process stack, and segment registers.
- ; 10. return from exec with child result code in AX
- ; and global _Interrupted flag set to true if child execution was
- ; interrupted.
- X
- ; NOTE: When first called the segments here assume the standard segment
- ; settings.
- X assume cs:@code, ds:DGROUP,es:DGROUP,ss:DGROUP
- X
- X public _exec
- _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
- ; 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
- ; Copy all parameters into the bottom of the code segment. After doing so we
- ; 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
- 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
- ; Now we save the current ss:sp stack pointer and swap stack to our temporary
- ; stack located in the current code segment. At the same time we reset the
- ; segment pointers to point into the code segment only.
- swap_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
- ; Now we save the old control break and critical error handler addresses.
- ; We replace them by our own routines found in the resident portion of the
- ; swapping exec code.
- set_handlers: mov [interrupted], 0 ; clear interrupted flag
- X mov [eretcode], 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
- ; Go and execute the child, we've set up all of its parameters. The do_exec
- ; routine will attempt to perform a swap of the code if requested to do so by
- ; a non-zero value in the variable cs:swap.
- X mov ah, 051H ; get the psp
- X int 21H
- X mov cs:psp, bx
- X call do_exec
- X
- ; We're back from the exec, so fix things up the way they were.
- ; 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
- ; 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
- ; Tell the assembler we have swaped segments again.
- X assume ds:DGROUP,es:DGROUP,ss:DGROUP
- 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
- ; Set the global errno value to reflect the success/failure of the DOS
- ; exec call.
- X mov ax, seg DGROUP:_errno
- X mov es, ax
- X mov ax, cs:ex_error
- X mov es:_errno, ax
- X
- ; Fetch the child's return code, pop rest of stuff off of the stack
- ; and return to the caller.
- X mov ax, cs:eretcode
- X pop di
- X pop si
- X pop bp
- X ret
- _exec endp
- X
- ; void do_hook_std_writes(int handle);
- ; This saves the 21h interrupt vector and changes it to point
- ; into this code. Argument is the file handle of the -C file.
- X
- X public _do_hook_std_writes
- _do_hook_std_writes proc
- X push bp
- X mov bp,sp
- X push di
- X
- X mov di, ss:[a_handle] ; handle of -C file
- X mov std_fil_handle, di
- X
- X mov ah, 51h ; request our PSP
- X int 21h
- X mov [psp], bx ; save it
- X
- X mov es, bx
- X les bx, es:[34h] ; pointer to job file table
- X mov al, es:[bx+1] ; system file # of our stdout
- X mov [our_stdout], al
- X mov al, es:[bx+di] ; system file number of -C file
- X mov std_fil_number, al
- X
- X mov ax,3521h ; request vector 21h
- X int 21h ; it's returned in ES:BX
- X mov word ptr [real_21h], bx
- X mov word ptr [real_21h+2], es
- X
- X push ds
- X mov ax,cs
- X mov ds,ax
- X lea dx,our_21h_handler ; DS:DX is the new vector
- X mov ax,2521h ; set vector 21h
- X int 21h
- X
- X pop ds
- X pop di
- X pop bp
- X ret
- _do_hook_std_writes endp
- X
- ; void do_unhook_std_writes(void);
- ; This restores the 21h interrupt vector.
- ; The saved vector is zero if it wasn't changed (no -C option).
- X
- X public _do_unhook_std_writes
- _do_unhook_std_writes proc
- X push ds
- X
- X lds dx, [real_21h] ; put saved vector into DS:DX
- X mov ax, ds
- X or ax, dx
- X jz unhook_return ; zero means we didn't hook 21h
- X
- X mov ax,2521h ; set vector 21h
- X simulate_21h
- X
- unhook_return: pop ds
- X ret
- _do_unhook_std_writes endp
- end
- SHAR_EOF
- chmod 0640 dmake/msdos/exec.asm ||
- echo 'restore of dmake/msdos/exec.asm failed'
- Wc_c="`wc -c < 'dmake/msdos/exec.asm'`"
- test 37235 -eq "$Wc_c" ||
- echo 'dmake/msdos/exec.asm: original size 37235, current size' "$Wc_c"
- rm -f _shar_wnt_.tmp
- fi
- # ============= dmake/msdos/exec.h ==============
- if test -f 'dmake/msdos/exec.h' -a X"$1" != X"-c"; then
- echo 'x - skipping dmake/msdos/exec.h (File already exists)'
- rm -f _shar_wnt_.tmp
- else
- > _shar_wnt_.tmp
- sed 's/^X//' << 'SHAR_EOF' > 'dmake/msdos/exec.h' &&
- #ifndef _EXEC_h_
- #define _EXEC_h_
- X
- #ifndef ANSI
- #if defined(__STDC__) || defined(__TURBOC__)
- #define ANSI(x) x
- #else
- #define ANSI(x) ()
- #endif
- #endif
- X
- extern int exec ANSI((int, char far *, char far *, unsigned int, char far *));
- X
- #ifndef MK_FP
- #define MK_FP(seg,ofs) \
- X ((void far *) (((unsigned long)(seg) << 16) | (unsigned)(ofs)))
- #endif
- X
- #endif
- SHAR_EOF
- chmod 0640 dmake/msdos/exec.h ||
- echo 'restore of dmake/msdos/exec.h failed'
- Wc_c="`wc -c < 'dmake/msdos/exec.h'`"
- test 351 -eq "$Wc_c" ||
- echo 'dmake/msdos/exec.h: original size 351, current size' "$Wc_c"
- rm -f _shar_wnt_.tmp
- fi
- # ============= dmake/msdos/exec.uue ==============
- if test -f 'dmake/msdos/exec.uue' -a X"$1" != X"-c"; then
- echo 'x - skipping dmake/msdos/exec.uue (File already exists)'
- rm -f _shar_wnt_.tmp
- else
- > _shar_wnt_.tmp
- sed 's/^X//' << 'SHAR_EOF' > 'dmake/msdos/exec.uue' &&
- begin 640 exec.obj
- M@!``#DU31$]37&5X96,N87-M;(@?````5'5R8F\@07-S96UB;&5R("!697)S
- M:6]N(#(N-;2(%@!`Z4!SIA8.35-$3U-<97AE8RYA<VW&B`,`0.E,E@(``&B(
- M`P!`H926$``)15A%0U]415A4!$-/1$5IF`<`2!`(`@,!^Y8,``5?1$%4001$
- M051!PI@'`$@"``0%`0V6"``&1$=23U50BYH$``;_`EN,"0`&7V5R<FYO`."0
- M$P`!`@Q?26YT97)R=7!T960```!9D!P```$57V1O7W5N:&]O:U]S=&1?=W)I
- M=&5S^0<`<I`,```!!5]E>&5CUP8`?9`:```!$U]D;U]H;V]K7W-T9%]W<FET
- M97.N!P"DB`0`0*(!D:`&``&8````P:(.``%<`24``0`!`````0#*H@X``8@!
- M00`!``$````!`(*@!0`!R0&0`*`(``',`0````"*H.P``=0!97AE8SH@1F%I
- M;'5R92!R96%D:6YG(&AE861E<B!B;&]C:PT*)&5X96,Z($9A:6QU<F4@<F5A
- M9&EN9R!S96=M96YT(&1A=&$-"B1E>&5C.B!&86EL=7)E(&]N(')E<VEZ90T*
- M)&5X96,Z($9A:6QU<F4@=&\@9G)E92!A(&)L;V-K#0HD97AE8SH@4')O9W)A
- M;2!S=V%P(&9A:6QU<F4-"B1E>&5C.B!-96UO<GD@8FQO8VMS(&1O;B=T(&UA
- M=&-H#0HDD&@&:P:-!FD&;`:S!@,$!P0+!`0$"`0J!`8$"@1@!`4$"012!*N<
- M20#$Q%0!Q,94`<3(5`'$RE0!Q,Q4`<3.5`'$T%0!Q-)4`<345`'$UE0!Q-A4
- M`<3:5`'$W%0!Q-Y4`<3@5`'$XE0!Q.14`<3F5`%?H`P``<H"7`$``%P!``#-
- MG`D`S`!4`<P$5`$5H-`#`=8"``"<@/Q`=0J#^P%T"X/[`G0&G2[_+LP!4%%2
- M4U155E<>!HOL+HL^T`&T49PN_Q[,`2X['HP`=&R.PR;%'C0`BW8,B@`N.@;3
- M`75CB@$N.@;2`71*N``SG"[_'LP!B_(KTK@!,YPN_Q[,`2Z+'HP`M%"<+O\>
- MS`&+WXY>`HM6#K1`G"[_'LP!C,.T4)PN_Q[,`8O6N`$SG"[_'LP!ZQ".7@*+
- M5@Z+W[1`G"[_'LP!!Q]?7EV#Q`);6EE8G2[_+LP!@\0&6%M96EY?71\'58OL
- MAT8$`AT8&7;@%`,_X+O\&D@`N@SZ8``!T`?G/NM0!ZQR0NOD!ZQ:0NAX"
- MZQ"0NC@"ZPJ0NG4"ZP20NE@"4HL>C@#_E[`"C,B.V%JT"<TAN/],S2'1Z7,!
- MI/.EP\/#P\/#P\/#NH$!N0<`BQ[*`;0_S2%S`NNF/0<`=`<+P'0"ZYOYPQXN
- MCAZ!`2Z+%H,!+HL.A0$NBQ[*`;0_S2$?<P+K@3L&A0%T`^EX_\.+'LH!,\F+
- MT;@`0LTAPXL>R@&T/LTANH@!M$'-(<.+'I8`N`%8S2&+'HX`_Y>V`HX&C`"+
- M'H0`M$K-(7,#Z4__BQZ.`/^7I`)R**"'`3P`=.\\`743BQZ%`;1(S2%R!CL&
- M@0%TV^DA_XL>C@#_EZH"Z\Z+'HX`_Y>P`L.X`%C-(:.6`(L^C`",RRO?B\=(
- MCL`FBS8#`(DVA`"XW071Z-'HT>C1Z`/8*_,#^XD>A@")/H@`L`#H$P%R,:&,
- M`$B.P+L:!NC!`'(CH8P`2([`NQ,&Z+,`<P/IJ_Z.!HP`BQZ&`+1*S2%S`^F4
- M_L.+'HX`_Y>P`C/`HXX`^<.#/HX``'0(Z'D`<@/H<_^#/I(``'5<H8H`"\!T
- M"%".P+1)S2%8H8H`H\0"C,G'!L8"VP")#L@"NIH`CL&[Q`(>B2;4`HP6T@+'
- M!M8"``#_!I@`N`!+S2$NCA;2`BZ+)M0"'W,&H]8"ZPF0M$W-(9BCD`"#/HX`
- M`'0#Z*G^QP:8````P\<&C@```.B6`,,FBS8#`(S'1R:A`0`N.P:,`'4F+CL^
- MB@!T&2X[/HP`=!)75E/_TUM>7W(/)J```#Q:=`8#_H['Z\?XPX['M$G-(<.P
- M`5=6,]*+'HX`_Y>8`EY?<CJ#_@!T-8O.@?G_#WX#N?\/4='AT>'1X='A5U:+
- M\3/2L`*+'HX`4_^7F`);_Y>>`EY?6G(&`_HK\NO&P\/#P\/#PZ"(`0K`=!>Z
- MB`$SR;0\S2%R#*/*`<<&C@`$`.L"D/G#B3Z!`8D6@P&)-H4!HH<!NH$!N0<`
- M$)R9`<065`'$)U0!Q"]4`<0T5`'$1U0!Q%!4`<1;5`'$:%0!Q&U4`<1U5`'$
- MA50!Q(]4`<2:5`'$K%0!Q+Y4`<3A5`'$YE0!Q.Y4`<3T5`'$^E0!Q0!4`<4&
- M5`'%#%0!Q1%4`<455`'%-E0!Q3U4`<585`'%750!Q6)4`<5G5`'%=%0!Q7Y4
- M`<6,5`'%DU0!Q9Q4`<6E5`'%J50!Q:U4`<6Q5`'%OE0!Q<)4`<7'5`'%TU0!
- MQ=U4`<865`'&/%0!QDI4`<7F5`'%ZE0!Q?!4`<7T5`'%_50!Q@%4`<835`'&
- M*%0!QBQ4`<8V5`'&1%0!QE94`<9:5`'&:%0!QFQ4`<9Q5`'&=U0!QH94`<:,
- M5`'&FU0!QIY4`<:D5`'&IE0!QJI4`<:M5`'&LE0!QK=4`<:[5`'&OU0!QL54
- M`<;/5`'&U%0!QMI4`<;E5`'&Z50!QO-4`<;Z5`''$50!QQA4`<<?5`''3%0!
- MQU!4`<=Y5`''?E0!QX-4`<>85`''GU0!QZI4`<>N5`''N50!Q[U4`<?!5`''
- MQ%0!Q\=4`1>@<@$!H@:+'LH!M$#-(7(&/0<`=`'YPQXNCAZ!`2Z+%H,!+HL.
- MA0$NBQ[*`;1`S2$?<@<[!H4!=`'YPU6+[%97'@X'_(M&!B:CC@"+1A`FHXH`
- MOYH`Q78(N4$`Z`']O]L`Q78,N8$`Z/7\OX@!Q782N4$`Z.G\C-`FHX``)HDF
- M@@",R([8CM"\@`#'!I(```#'!I````"X(S7-(2Z)'KP"+HP&O@*ZLP.X(R7-
- M(;@D-<TA+HD>P`(NC`;"`KJ6`[@D)<TAM%'-(2Z)'HP`Z-_]+L46O`*X(R7-
- M(2[%%L`"N"0ES2$NH8``CM`NBR:"`!^X``".P"ZAD@`FHP``N```CL`NH=8"
- M)J,``"ZAD`!?7EW+58OL5XM^!BZ)/M`!M%'-(2Z)'HP`CL,FQ!XT`":*1P$N
- MHM,!)HH!+J+2`;@A-<TA+HD>S`$NC`;.`1Z,R([8NM@"N"$ES2$?7UW+'B[%
- M%LP!C-@+PG0)N"$EG"[_'LP!'\M6G+$`Q`)4`<055`'$&E0!Q!]4`<0D5`'$
- M+U0!Q$-4`<1*5`'$350!Q%E4`<1E5`'$=%0!Q'E4`<2"5`'$AE0!Q(Q4`<28
- M5`'$G50!Q*!4`<2O5`'$M%0!Q+=4`<3%5`'$S50!Q-=4`<3@5`'$YU0!R.L4
- M`0+$\50!Q/44`0+(^!8!`<3^5`'%`A8!`<4&5`'%%E0!Q1]4`<4N5`'%-50!
- CQ3]4`<5$5`'%3%0!Q5M4`<5J5`&-H`8``@````!8B@(``'14
- `
- end
- SHAR_EOF
- chmod 0640 dmake/msdos/exec.uue ||
- echo 'restore of dmake/msdos/exec.uue failed'
- Wc_c="`wc -c < 'dmake/msdos/exec.uue'`"
- test 3671 -eq "$Wc_c" ||
- echo 'dmake/msdos/exec.uue: original size 3671, current size' "$Wc_c"
- rm -f _shar_wnt_.tmp
- fi
- # ============= dmake/msdos/find.c ==============
- if test -f 'dmake/msdos/find.c' -a X"$1" != X"-c"; then
- echo 'x - skipping dmake/msdos/find.c (File already exists)'
- rm -f _shar_wnt_.tmp
- else
- > _shar_wnt_.tmp
- sed 's/^X//' << 'SHAR_EOF' > 'dmake/msdos/find.c' &&
- /*
- X Directory Access Library
- X
- X FIND.C taken from DIRLIB.C by M. J. Weinstein
- X Released to public domain 1-Jan-89
- X
- X The author may be contacted at:
- X matt@cs.ucla.edu -or- POB 84524, L.A., CA 90073
- X
- X Modified by dvadura@watdragon.edu to work with dmake.
- X (nuked the DOS version 2 code, since dmake needs version
- X 3.0 or greater to function).
- X */
- X
- X
- /*
- X * revision history:
- X *
- X * VER MM/DD/YY COMMENTS
- X * ---- -------- --------
- X * 0.99 02/24/86 Beta release to INTERNET
- X */
- X
- #include <stdlib.h>
- #include <ctype.h>
- #include <errno.h>
- #include <string.h>
- #include <alloc.h>
- #include <dos.h>
- #include "dirlib.h"
- X
- #ifndef MK_FP
- #define MK_FP(seg,ofs) ((void far *) \
- X (((unsigned long)(seg) << 16) | (unsigned)(ofs)))
- #endif
- #ifndef FP_SEG
- #define FP_SEG(fp) ((unsigned)((unsigned long)(fp) >> 16))
- #endif
- #ifndef FP_OFF
- #define FP_OFF(fp) ((unsigned)(fp))
- #endif
- X
- int _err;
- static DTA far *_getsetdta ANSI((DTA far *));
- X
- /*
- X * get/set dta address
- X */
- X
- static DTA far *
- _getsetdta(newdta)
- DTA far *newdta;
- {
- X DTA far *olddta;
- X union REGS r;
- X struct SREGS s;
- X
- X /* get old dta */
- X r.h.ah = 0x2f;
- X intdos(&r, &r);
- X segread(&s);
- X olddta = (DTA far *) MK_FP(s.es, r.x.bx);
- X
- X /* conditionally set new dta */
- X if (newdta) {
- X r.h.ah = 0x1a;
- X s.ds = FP_SEG(newdta);
- X r.x.dx = FP_OFF(newdta);
- X intdosx(&r, &r, &s);
- X }
- X
- X return olddta;
- }
- X
- /*
- X * dos findfirst
- X */
- X
- DTA *
- findfirst(name, dta)
- char *name;
- DTA *dta;
- {
- X union REGS r;
- X struct SREGS s;
- X DTA far *dtasave;
- X char far *nmp = (char far *)name;
- X
- X dtasave = _getsetdta((DTA far *)dta);
- X
- X /* do directory lookup */
- X segread(&s);
- X r.h.ah = 0x4e;
- X r.x.cx = 0x10;
- X r.x.dx = FP_OFF(nmp);
- X s.ds = FP_SEG(nmp);
- X intdosx(&r, &r, &s);
- X /* restore dta */
- X _getsetdta(dtasave);
- X _err = r.x.ax;
- X if (r.x.cflag)
- X return (DTA *) 0;
- X
- X return dta;
- }
- X
- /*
- X * dos findnext
- X */
- X
- DTA *
- findnext(dta)
- DTA *dta;
- {
- X union REGS r;
- X DTA far *dtasave;
- X
- X dtasave = _getsetdta((DTA far *)dta);
- X
- X /* do directory lookup */
- X r.h.ah = 0x4f;
- X intdos(&r, &r);
- X /* restore old dta */
- X _getsetdta(dtasave);
- X _err = r.x.ax;
- X if (r.x.cflag)
- X return (DTA *) 0;
- X
- X return dta;
- }
- SHAR_EOF
- chmod 0640 dmake/msdos/find.c ||
- echo 'restore of dmake/msdos/find.c failed'
- Wc_c="`wc -c < 'dmake/msdos/find.c'`"
- test 2140 -eq "$Wc_c" ||
- echo 'dmake/msdos/find.c: original size 2140, current size' "$Wc_c"
- rm -f _shar_wnt_.tmp
- fi
- # ============= dmake/msdos/mscdos/config.h ==============
- if test ! -d 'dmake/msdos/mscdos'; then
- mkdir 'dmake/msdos/mscdos'
- fi
- if test -f 'dmake/msdos/mscdos/config.h' -a X"$1" != X"-c"; then
- echo 'x - skipping dmake/msdos/mscdos/config.h (File already exists)'
- rm -f _shar_wnt_.tmp
- else
- > _shar_wnt_.tmp
- sed 's/^X//' << 'SHAR_EOF' > 'dmake/msdos/mscdos/config.h' &&
- /* RCS -- $Header: /u2/dvadura/src/generic/dmake/src/msdos/mscdos/config.h,v 1.1 1992/01/24 03:27:25 dvadura Exp $
- -- SYNOPSIS -- Configurarion include file.
- --
- -- DESCRIPTION
- -- There is one of these for each specific machine configuration.
- -- It can be used to further tweek the machine specific sources
- -- so that they compile.
- --
- -- AUTHOR
- -- Dennis Vadura, dvadura@watdragon.uwaterloo.ca
- -- CS DEPT, University of Waterloo, Waterloo, Ont., Canada
- --
- -- COPYRIGHT
- -- Copyright (c) 1990 by Dennis Vadura. All rights reserved.
- --
- -- This program is free software; you can redistribute it and/or
- -- modify it under the terms of the GNU General Public License
- -- (version 1), as published by the Free Software Foundation, and
- -- found in the file 'LICENSE' included with this distribution.
- --
- -- This program is distributed in the hope that it will be useful,
- -- but WITHOUT ANY WARRANTY; without even the implied warrant of
- -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
- -- GNU General Public License for more details.
- --
- -- You should have received a copy of the GNU General Public License
- -- along with this program; if not, write to the Free Software
- -- Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
- --
- -- LOG
- -- $Log: config.h,v $
- X * Revision 1.1 1992/01/24 03:27:25 dvadura
- X * dmake Version 3.8, Initial revision
- X *
- */
- X
- #if defined (_MSC_VER)
- # if _MSC_VER < 500
- X Force a compile-time blowup.
- X Do not define define _MSC_VER for MSC compilers ealier than 5.0.
- # endif
- #endif
- X
- /* define this for configurations that don't have the coreleft function
- X * so that the code compiles. To my knowledge coreleft exists only on
- X * Turbo C, but it is needed here since the function is used in many debug
- X * macros. */
- #define coreleft() 0L
- X
- /* MSC Version 4.0 doesn't understand SIGTERM, later versions do. */
- #ifndef SIGTERM
- # define SIGTERM SIGINT
- #endif
- X
- /* Fixes unimplemented line buffering for MSC 5.x and 6.0.
- X * MSC _IOLBF is the same as _IOFBF
- X */
- #if defined(MSDOS) && defined (_MSC_VER)
- # undef _IOLBF
- # define _IOLBF _IONBF
- #endif
- X
- /* in alloc.h: size_t is redefined
- X * defined in stdio.h which is included by alloc.h
- X */
- #if defined(MSDOS) && defined (_MSC_VER)
- # define _TYPES_
- #endif
- X
- /* in sysintf.c: SIGQUIT is used, this is not defined in MSC */
- #ifndef SIGQUIT
- # define SIGQUIT SIGTERM
- #endif
- X
- /* MSC doesn't seem to care about CONST */
- #define CONST
- X
- #ifndef MSDOS
- # define MSDOS 1
- #endif
- X
- /* a small problem with pointer to voids on some unix machines needs this */
- #define PVOID void *
- SHAR_EOF
- chmod 0640 dmake/msdos/mscdos/config.h ||
- echo 'restore of dmake/msdos/mscdos/config.h failed'
- Wc_c="`wc -c < 'dmake/msdos/mscdos/config.h'`"
- test 2637 -eq "$Wc_c" ||
- echo 'dmake/msdos/mscdos/config.h: original size 2637, current size' "$Wc_c"
- rm -f _shar_wnt_.tmp
- fi
- # ============= dmake/msdos/mscdos/config.mk ==============
- if test -f 'dmake/msdos/mscdos/config.mk' -a X"$1" != X"-c"; then
- echo 'x - skipping dmake/msdos/mscdos/config.mk (File already exists)'
- rm -f _shar_wnt_.tmp
- else
- > _shar_wnt_.tmp
- sed 's/^X//' << 'SHAR_EOF' > 'dmake/msdos/mscdos/config.mk' &&
- # This is the MSC 4.0 and higher DOS configuration file for DMAKE
- # It simply modifies the values of SRC, and checks to see if
- # OSENVIRONMENT is defined. If so it includes the appropriate
- # config.mk file.
- #
- # It also sets the values of .SOURCE.c and .SOURCE.h to include the local
- # directory.
- #
- osrdir := $(OS)$(DIRSEPSTR)$(OSRELEASE)
- X
- TMPDIR :=
- .EXPORT : TMPDIR
- X
- # Definition of macros for library, and C startup code.
- X
- # The following sources are required for MSC
- OSR_SRC = tempnam.c
- .SETDIR=$(osrdir) : $(OSR_SRC)
- X
- SRC += $(OSR_SRC)
- .SOURCE.h : $(osrdir)
- X
- SET_STACK = /stack:4096
- NDB_LDFLAGS += $(SET_STACK)
- X
- # Local configuration modifications for CFLAGS
- # If you have a 286 or better, you can uncomment the following line.
- #HAVE_286 = y
- X
- .IF $(HAVE_286)
- X CFLAGS += -G2
- X ASFLAGS += -Dhave286
- .END
- X
- ASFLAGS += -t -mx $(S_$(MODEL))
- X
- # Microsoft C doesn't need tail but needs head
- LDTAIL = ;
- LDHEAD = $(LDFLAGS)
- X
- # Debugging libraries
- DB_LDFLAGS += /co /li /map $(SET_STACK)
- DB_LDLIBS +=
- X
- # NO Debug MSC flags:
- # Set the environment variable MSC_VER to be one of 4.0, 5.0, 5.1, or 6.0
- # to get these by default when you make dmake using 'dmake'.
- #
- # Setting MSC_VER to one of the above sets the variable _MSC_VER appropriately
- # and sets the flags appropriately.
- X
- .IMPORT .IGNORE : MSC_VER
- MSC_VER *= 6.0 # If unset, assume 6.0 by default.
- X
- .IF $(MSC_VER) == 4.0
- X CFLAGS += -I$(osrdir) $(C_$(MODEL):s/A/m/)
- X CFLAGS += -DM_I86=1 # 5.0+ define this automatically
- # CFLAGS += -D__STDC__=1 # 5.0, 5.1, but not 6.0 do this automatically
- X NDB_CFLAGS +=
- X DB_CFLAGS += -Zi
- .ELSE
- X DB_CFLAGS += -Zi
- X CFLAGS += -I$(osrdir) $(C_$(MODEL))
- X .IF $(MSC_VER) != 6.0
- X # For 5.0 and 5.1, we define _MSC_VER=500 or 510
- X CFLAGS += -D_MSC_VER=$(MSC_VER:s,.,,)0
- X NDB_CFLAGS += -Oscl -Gs
- X .ELSE
- X # Microsoft C 6.0 auto defines _MSC_VER=600, but not __STDC__
- X CFLAGS += -D__STDC__=1 # incredibly not auto done by 6.0
- X NDB_CFLAGS += -Osecgl -Gs
- X
- X # Redefine rule for making our objects, we don't need mv
- X %$O : %.c ;% $(CC) -c $(CFLAGS) -Fo$@ $<
- X .END
- X NDB_LDFLAGS += /exe /packc /batch
- X NDB_LDLIBS +=
- .END
- X
- # See if we modify anything in the lower levels.
- .IF $(OSENVIRONMENT) != $(NULL)
- X .INCLUDE .IGNORE : $(osrdir)$(DIRSEPSTR)$(OSENVIRONMENT)$(DIRSEPSTR)config.mk
- .END
- X
- C_s =
- C_m = -AM
- C_c = -AC
- C_l = -AL
- X
- S_s = -Dmsmall
- S_m = -Dmmedium
- S_c = -Dmcompact
- S_l = -Dmlarge
- SHAR_EOF
- chmod 0640 dmake/msdos/mscdos/config.mk ||
- echo 'restore of dmake/msdos/mscdos/config.mk failed'
- Wc_c="`wc -c < 'dmake/msdos/mscdos/config.mk'`"
- test 2471 -eq "$Wc_c" ||
- echo 'dmake/msdos/mscdos/config.mk: original size 2471, current size' "$Wc_c"
- rm -f _shar_wnt_.tmp
- fi
- # ============= dmake/msdos/mscdos/lib.rsp ==============
- if test -f 'dmake/msdos/mscdos/lib.rsp' -a X"$1" != X"-c"; then
- echo 'x - skipping dmake/msdos/mscdos/lib.rsp (File already exists)'
- rm -f _shar_wnt_.tmp
- else
- > _shar_wnt_.tmp
- sed 's/^X//' << 'SHAR_EOF' > 'dmake/msdos/mscdos/lib.rsp' &&
- X
- SHAR_EOF
- chmod 0640 dmake/msdos/mscdos/lib.rsp ||
- echo 'restore of dmake/msdos/mscdos/lib.rsp failed'
- Wc_c="`wc -c < 'dmake/msdos/mscdos/lib.rsp'`"
- test 1 -eq "$Wc_c" ||
- echo 'dmake/msdos/mscdos/lib.rsp: original size 1, current size' "$Wc_c"
- rm -f _shar_wnt_.tmp
- fi
- # ============= dmake/msdos/mscdos/libswp.rsp ==============
- if test -f 'dmake/msdos/mscdos/libswp.rsp' -a X"$1" != X"-c"; then
- echo 'x - skipping dmake/msdos/mscdos/libswp.rsp (File already exists)'
- rm -f _shar_wnt_.tmp
- else
- > _shar_wnt_.tmp
- sed 's/^X//' << 'SHAR_EOF' > 'dmake/msdos/mscdos/libswp.rsp' &&
- X
- SHAR_EOF
- chmod 0640 dmake/msdos/mscdos/libswp.rsp ||
- echo 'restore of dmake/msdos/mscdos/libswp.rsp failed'
- Wc_c="`wc -c < 'dmake/msdos/mscdos/libswp.rsp'`"
- test 1 -eq "$Wc_c" ||
- echo 'dmake/msdos/mscdos/libswp.rsp: original size 1, current size' "$Wc_c"
- rm -f _shar_wnt_.tmp
- fi
- # ============= dmake/msdos/mscdos/mk40.bat ==============
- if test -f 'dmake/msdos/mscdos/mk40.bat' -a X"$1" != X"-c"; then
- echo 'x - skipping dmake/msdos/mscdos/mk40.bat (File already exists)'
- rm -f _shar_wnt_.tmp
- else
- > _shar_wnt_.tmp
- sed 's/^X//' << 'SHAR_EOF' > 'dmake/msdos/mscdos/mk40.bat' &&
- md objects
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 infer.c
- copy infer.obj objects
- del infer.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 make.c
- copy make.obj objects
- del make.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 stat.c
- copy stat.obj objects
- del stat.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 expand.c
- copy expand.obj objects
- del expand.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 dmstring.c
- copy dmstring.obj objects
- del dmstring.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 hash.c
- copy hash.obj objects
- del hash.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 dag.c
- copy dag.obj objects
- del dag.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 dmake.c
- copy dmake.obj objects
- del dmake.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 path.c
- copy path.obj objects
- del path.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 imacs.c
- copy imacs.obj objects
- del imacs.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 sysintf.c
- copy sysintf.obj objects
- del sysintf.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 parse.c
- copy parse.obj objects
- del parse.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 getinp.c
- copy getinp.obj objects
- del getinp.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 quit.c
- copy quit.obj objects
- del quit.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 state.c
- copy state.obj objects
- del state.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 basename.c
- copy basename.obj objects
- del basename.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 dmdump.c
- copy dmdump.obj objects
- del dmdump.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 macparse.c
- copy macparse.obj objects
- del macparse.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 rulparse.c
- copy rulparse.obj objects
- del rulparse.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 percent.c
- copy percent.obj objects
- del percent.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 function.c
- copy function.obj objects
- del function.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 msdos\ruletab.c
- copy ruletab.obj objects
- del ruletab.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 msdos\dirbrk.c
- copy dirbrk.obj objects
- del dirbrk.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 msdos\runargv.c
- copy runargv.obj objects
- del runargv.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 msdos\arlib.c
- copy arlib.obj objects
- del arlib.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 msdos\_chdir.c
- copy _chdir.obj objects
- del _chdir.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 msdos\switchar.c
- copy switchar.obj objects
- del switchar.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 msdos\rmprq.c
- copy rmprq.obj objects
- del rmprq.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 msdos\tee.c
- copy tee.obj objects
- del tee.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 msdos\mscdos\tempnam.c
- copy tempnam.obj objects
- del tempnam.obj
- copy msdos\mscdos\startup.mk startup.mk
- link /stack:4096 @msdos\mscdos\obj.rsp,dmake.exe,NUL.MAP;
- SHAR_EOF
- chmod 0640 dmake/msdos/mscdos/mk40.bat ||
- echo 'restore of dmake/msdos/mscdos/mk40.bat failed'
- Wc_c="`wc -c < 'dmake/msdos/mscdos/mk40.bat'`"
- test 3032 -eq "$Wc_c" ||
- echo 'dmake/msdos/mscdos/mk40.bat: original size 3032, current size' "$Wc_c"
- rm -f _shar_wnt_.tmp
- fi
- # ============= dmake/msdos/mscdos/mk40swp.bat ==============
- if test -f 'dmake/msdos/mscdos/mk40swp.bat' -a X"$1" != X"-c"; then
- echo 'x - skipping dmake/msdos/mscdos/mk40swp.bat (File already exists)'
- rm -f _shar_wnt_.tmp
- else
- > _shar_wnt_.tmp
- sed 's/^X//' << 'SHAR_EOF' > 'dmake/msdos/mscdos/mk40swp.bat' &&
- md objects
- masm -t -mx -Dmlarge msdos\exec.asm;
- mv exec.obj objects
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 infer.c
- copy infer.obj objects
- del infer.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 make.c
- copy make.obj objects
- del make.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 stat.c
- copy stat.obj objects
- del stat.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 expand.c
- copy expand.obj objects
- del expand.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 dmstring.c
- copy dmstring.obj objects
- del dmstring.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 hash.c
- copy hash.obj objects
- del hash.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 dag.c
- copy dag.obj objects
- del dag.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 dmake.c
- copy dmake.obj objects
- del dmake.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 path.c
- copy path.obj objects
- del path.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 imacs.c
- copy imacs.obj objects
- del imacs.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 sysintf.c
- copy sysintf.obj objects
- del sysintf.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 parse.c
- copy parse.obj objects
- del parse.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 getinp.c
- copy getinp.obj objects
- del getinp.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 quit.c
- copy quit.obj objects
- del quit.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 state.c
- copy state.obj objects
- del state.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 basename.c
- copy basename.obj objects
- del basename.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 dmdump.c
- copy dmdump.obj objects
- del dmdump.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 macparse.c
- copy macparse.obj objects
- del macparse.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 rulparse.c
- copy rulparse.obj objects
- del rulparse.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 percent.c
- copy percent.obj objects
- del percent.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 function.c
- copy function.obj objects
- del function.obj
- cl -c -I. -Imsdos -Imsdos\mscdos -mL -DM_I86=1 msdos\ruletab.c
- copy ruletab.obj objects
- SHAR_EOF
- true || echo 'restore of dmake/msdos/mscdos/mk40swp.bat failed'
- fi
- echo 'End of part 23, continue with part 24'
- echo 24 > _shar_seq_.tmp
- exit 0
- exit 0 # Just in case...
-