; SHELL.ASM
; Copyright 1992, Alfred J. Heyman and Spectrum Research, Inc.


.286P

public _shell, _hookup, _swapvects, _storevects, _acadshell
public _save_psp, _save_dta, _new_dta, _restore_dta, _shelldir
public _new_psp, _restore_psp, _saveblocks, _save_cur_blks
public _rest_old_blks, _rest_cur_blks, _program, _cmdline, _acadname
public _write_swap, _read_swap, _install23, _install24, _lockname
public _runname, _swapfile, _adr_afus, _cadr_afus, _shutdown
public _swap_open, _swap_reopen, _swap_close, _swap_reset, _swap_zap
public _setretry, _clrretry, _malloc256, _rollout, _rollin, _clear_cmdln
public _getakey, _get_retcode, _install15, _uninstall15, _fin
public _f88_i15, _geti21, _ts_enable, _clr_tskip, _biggestl
public _detect, _hook19, _unhook19, _cli, _sti, _nmi
public _file_handle, _release_all, _enable_a20, _restore_ps2r
public _ems_open, _ems_close, _emm_load_flag,_emm_loaded, _emm_use_flag
public _gen_swapname, _test_acadl, _botmsg, _copyright2, _thisprog
public _run_acad, _get_box_id, _machine, _getenva, _get_run_name
public __acrtused, __anchkstk, _stub, _psp_ascii, _orig_psp, _get_psp

extrn _main:        proc
extrn _exec:        proc
extrn _clearwindow: proc
extrn _gotoxy:      proc
extrn _setcolor:    proc
extrn _sprintstr:   proc

extrn _abortmsg:    far
extrn _FNAMEX:      far
extrn _EXTX:        far

;--------------;
; DEFINITIONS  ;
;--------------;

DOSCALL MACRO
         CALL DOS               ;Call dos far.
ENDM

BREAK MACRO
IF1
%OUT Hard Break Inserted
ENDIF
INT 2
ENDM

.MODEL compact
.DATA

stack    db   64 dup ("*STACK**")    ;64*8=512
endstack dw   0

ostacko  dw   0                 ;Stack pointers.
ostacks  dw   0

aostacko dw   0                 ;Stack pointers.
aostacks dw   0

o01o     dw   0
o01s     dw   0
o03o     dw   0
o03s     dw   0

o21o     dw   0                 ;Old interrupt 21 offset
o21s     dw   0

orig_dtao dw   0                ;Original DTA
orig_dtas dw   0
_orig_psp dw   0                ;Original PSP

old_dtao dw   0
old_dtas dw   0
old_psp  dw   0

ts_ss    dw   0                 ;Storage for registers during stack switch.
ts_sp    dw   0

;--------------
envseg    dw   0                ;Parameter block passed to EXEC.
cmdoff    dw   80h
cmdseg    dw   0
fcb1ofs   dw   5ch
fcb1seg   dw   0
fcb2ofs   dw   6ch
fcb2seg   dw   0

;--------------

exspace        db   "BIGSHELL="
ems_name       db   "BSHL"
_psp_ascii     db  "    ",0,0

retry          db   0
tripskip       dw   1
fattributes    dw   0

bs_ds          dw   0           ;Data  segment of bigshell C code.
bs_es          dw   0           ;Extra segment of bigshell C code.

writetop       dw   0
writestart     dw   0
mcbtype        db   0           ;4D or 5A.

;----------------------------------------------------------------------
; These memory allocation blocks are stored as they were
; when we were first loaded. (Before AutoCAD was executed).
;----------------------------------------------------------------------

blk_b4us db 16 dup (0)          ;Copy of block before us.
adr_b4us dw 0                   ;Segment Address of block before us.

blk_afus db 16 dup (0)          ;Copy of block after us.
_adr_afus dw 0                  ;Segment address of block after us.

;----------------------------------------------------------------------
; These memory allocation blocks are stored as they exist
; when autocad tries to shell out.
;----------------------------------------------------------------------

cadr_b4us       dw 0               ;Segment Address of block before us.
cblk_b4us       db 16 dup (0)      ;Copy of block before us.

_machine        dw    0            ;11h=Vectra. 20h=PS2.
_cadr_afus      dw    0            ;Segment address of block after us.
cblk_afus       db    16 dup (0)   ;Copy of block after us.
memtop          dw    0a000h

_file_handle    dw    0ffffh       ;Dos Handle for swap file.
_cmdline        db    80h dup (0)  ;buffer for command line.
_thisprog       db    80 dup (0)   ;This program.
_program        db    80 dup (0)   ;Name of program to run.
_runname        db    80 dup (0)   ;Program run name.
_shelldir       db    80 dup (0)   ;Swap Shell directory.
_swapfile       db    80 dup (0)   ;Swap file name.
_acadname       db    28 dup (0)   ;Name of ACAD to run.

errexx          db "ERROR: EXECUTION FAILED",0
executing       db "EXECUTING: ",0

_lockname       db    80 dup (0)   ;Name of lock file.
locksize        dw    0            ;Size of lock file.

gdt             db    6 dup (0)
idt             db    6 dup (0)


;EMS 4.0 Function 24, Move/Exchange Memory Region.

db "EMM_TABLE"

_biggestl       dw   0
_biggesth       dw   0

_swap_size_l    dw   0          ;Biggest EMS size used.
_swap_size_h    dw   0

region_len_l    dw   0          ;Length of Memory Region to move.
region_len_h    dw   0
Src_mem_type    db   0          ;Memory Type, 0=Conventional, 1=EMS.
src_handle      dw   0          ;Handle Number, 0=N/A (Conventional Memory).
src_init_ofs    dw   0          ;Source Memory Initial Offset.
src_init_seg    dw   0          ;Source Memory Initial Segment or page.
dest_mem_type   db   0          ;Destination Memory Type, 0=Conventional, 1=EMS.
dest_handle     dw   0          ;Destination Memory Handle. 0=N/A (Conventional).
dest_init_ofs   dw   0          ;Destination Memory Offset.
dest_init_seg   dw   0          ;Destination Memory Segment or page.

ems_handle      dw   0          ;Handle of EMM memory that we use here.
ems_offset      dw   0          ;Current offset into 16K EMM page.
ems_segment     dw   0          ;Current page into 16K EMM page.
ems_start_pgf   dw   0          ;Number of initial paragraphs allocated.
_emm_load_flag  dw   0          ;0=Not Loaded, 1=Loaded.
_emm_use_flag   dw   0          ;0=Dont Use, 1=Do Use.

;----------------------------------------------------------------------

.CODE

;----------------------------------------------------------------------
                 DB  64 dup ("*ISTACK*")
i_stack:

_vector_table:   db  1024 dup (0)   ;Interrupt vector table.

esize            dw  0              ;Stored amount of extended memory avail.
o15o             dw  0              ;Offset to old INT 15 handler.
o15s             dw  0

test_int        db   0              ;Temporary var.
;revectored      dw   0              ;0=Normal 8259 IRQ vectors.
clock1          dw   0              ;Timer tick clock.
clock2          dw   0              ;NEW tick clock.

release_all     db   0              ;1=TenMenu product.
downflag        db   0              ;1=Last run through mem release code.
psp256          dw   0              ;Segment of malloced 256 bytes for PHAR-PSP.
psp256loc       dw   0

errorlevel      dw   0              ;Storage for shell programs error level.

;o08o     dw   0                     ;Old Int 08 Handler.
;o08s     dw   0
;n08o     dw   0                     ;New Int 08 Handler.
;n08s     dw   0

;------------------------------------------------------------------
;_strcpy proc
;                push bp
;                mov  bp,sp
;                pop  bp
;                ret
;_strcpy endp
;;------------------------------------------------------------------
;_strcmp proc
;                push bp
;                mov  bp,sp
;                pop  bp
;                ret
;_strcmp endp

;------------------------------------------------------------------
; This routine allocates a small STUBBY memory block.
; This was needed because the "C" version allocated one.
; The ASM version logic would need to be changed if this didn't exist!
;------------------------------------------------------------------
_stub proc
                 mov  ah,48h
                 mov  bx,1
                 int  21h
                 ret
_stub endp

;------------------------------------------------------------------
_nmi proc
                int 2
                ret
_nmi endp

;------------------------------------------------------------------
__acrtused proc
                ret
__acrtused endp
;------------------------------------------------------------------
__anchkstk proc
                ret
__anchkstk endp
;------------------------------------------------------------------
_enable_a20 proc

                CALL  AAHEnable
                ret

_enable_a20 endp

;----------------------------------------------------------------------

PS2_PORTA   equ 0092h
PS2_A20BIT  equ 00000010b

_restore_ps2r proc

               in   al,PS2_PORTA        ;Get PS2 A20 line value.
               test al,PS2_A20BIT       ;Test A20 line.
               jnz  rpx                 ;Jump out if on already.

               or   al,PS2_PORTA        ;Set A20 on.
               out  PS2_PORTA,al        ;Turn on PS2 A20 Line.

               xor   cx,cx
      rp1:     in    al,PS2_PORTA
               test  al,PS2_A20BIT
               loopz rp1

      rpx:     ret

_restore_ps2r endp


;*--------------------------------------------------------------------------*
;*									    *
;*  AT_A20Handler -					    HARDWARE DEP.   *
;*									    *
;*	Enable/Disable the A20 line on non-PS/2 machines		    *
;*									    *
;*  ARGS:   AX = 0 for Disable, 1 for Enable				    *
;*  RETS:   AX = 1 for success, 0 otherwise				    *
;*  REGS:   AX, CX and Flags clobbered					    *
;*									    *
;*--------------------------------------------------------------------------*

AT_A20Handler proc


AAHEnable:  call    Sync8042	; Make sure the Keyboard Controller is Ready
	    jnz     short AAHErr

	    mov	    al,0D1h	; Send D1h
	    out	    64h,al
	    call    Sync8042
	    jnz     short AAHErr

	    mov	    al,0DFh	; Send DFh
	    out	    60h,al
	    call    Sync8042
	    jnz     short AAHErr

	    ; Wait for the A20 line to settle down (up to 20usecs)
	    mov	    al,0FFh	; Send FFh (Pulse Output Port NULL)
	    out	    64h,al
	    call    Sync8042
	    
AAHExit:
AAHErr:     ret
	    
AT_A20Handler endp


;*--------------------------------------------------------------------------*

Sync8042    proc

	    xor	    cx,cx
S8InSync:   in	    al,64h
	    and	    al,2
	    loopnz  S8InSync
	    ret

Sync8042    endp

;----------------------------------------------------------------------

_fin proc
                push bp
                mov  bp,sp
                mov  ax,[bp+4]          ;Get error level.
                mov  ah,4ch
                call dos
                pop  bp
                ret
_fin endp

;----------------------------------------------------------------------

_release_all proc

              mov cs:release_all,1
              ret

_release_all endp

;----------------------------------------------------------------------

_cli proc
         cli
         ret
_cli endp

;----------------------------------------------------------------------

_sti proc
         sti
         ret
_sti endp

;----------------------------------------------------------------------

_malloc256  proc

         mov  ah,48h            ;Malloc.
         mov  bx,10h            ;256 bytes.
         int  21h               ;Call DOS.
         mov  cs:psp256,ax      ;Save the pointer.
         mov  cs:psp256loc,ax   ;Save the location.
         ret

_malloc256 endp

;----------------------------------------------------------------------

_save_cur_blks proc

         push ds
         push es

         mov  bx,adr_b4us       ;Get block address before us.
         mov  cadr_b4us,bx      ;Store address

         push ds
         pop  es
         mov  ds,bx
         xor  si,si             ;ES:DI point to storage.
         lea  di,cblk_b4us      ;DS:SI point to block.
         mov  cx,16             ;Store 16 bytes
         cld
         rep  movsb

         add  bx,ds:[0003]      ;Add in memory used by our block.
         inc  bx                ;Add in size of block.
         mov  ds,bx
         xor  si,si             ;DS:SI points to block after us.

         lea  di,_cadr_afus
         mov  es:[di],bx        ;Store segment address of block after us.
         lea  di,cblk_afus      ;ES:DI points to storage.
         mov  cx,16
         rep  movsb

         pop  es
         pop  ds
         ret

_save_cur_blks endp



;----------------------------------------------------------------------
; Converted from C code.
;
;
; gen_swapname()
; { if(shelldir != NULL)
;     { strcpy(swapfile,shelldir);
;       if(swapfile[strlen(swapfile)]!='\\')
;         { strcat(swapfile,"\\"); };
;     };
;   _splitpath(swapfile,drive,dir,fname,ext);
;   strcpy(fname,"");  strcpy(ext,"");
;   _makepath(swapfile,drive,dir,fname,ext);
; };
;
; If SHELLDIR has anything in it, it is the SHELL_SWAP environment parm.
; If so, copy the SHELLDIR to SWAPFILE.
;
; If Not, Swapfile contains the executable file name of the program.
; Zap the filename and extension.
;----------------------------------------------------------------------
_GEN_SWAPNAME PROC

         push si
         push di
         push es

         mov  si,ds
         mov  es,si

         lea  si,_shelldir
         lea  di,_swapfile

         mov  al,[si]           ;Look at first character in shelldir.
         or   al,al             ;Set flags.
         jz   dirnull           ;Jump if string is NULL.

         cld                    ;Clear direction flag.
         mov  cx,80             ;Copy shelldir to swapfile.
         rep  movsb

         lea  si,_swapfile      ;Point back at destination.
         mov  cx,80             ;Look through 80 characters max.
         xor  ax,ax             ;Clear AX.

findnd:  mov  ah,al             ;Save previous character loaded.
         mov  al,[si]           ;Get current character.
         inc  si                ;point at next.
         or   al,al             ;Test for ZERO.
         loopnz findnd          ;Loop up again if NOT ZERO.

         dec  si                ;Point back at last character.
         cmp  ah,"\"            ;Is last character SLASH?
         jz   dirnull           ;Yes? Jump over.

         mov  al,'\'            ;Copy "\" and terminate string.
         xor  ah,ah             ;Clear AH.
         mov  [si],ax
         jmp  genx              ;Finished.

;Execution here means that SWAPFILE=C:\ACAD\ACAD.EXE or similar.

dirnull: mov  cx,80             ;Look through 80 characters MAX.
         lea  si,_swapfile      ;Point at swap file.

 findnx: mov  al,[si]           ;Get current character.
         inc  si                ;point at next.
         or   al,al             ;Test for ZERO.
         loopnz findnx          ;Loop up again if NOT ZERO.
         sub  si,2              ;Point at last character.

         mov  cx,80
         xor  ah,ah

 zapnxt: mov  al,[si]           ;Get last character.
         cmp  al,"\"            ;Is it a slash?
         jz   genx              ;Yes? Jump out.
         mov  [si],ah           ;ZAP the character.
         dec  si                ;Point at previous.
         loop zapnxt            ;Loop back and look at another.

 genx:   pop  es
         pop  di
         pop  si
         ret

_GEN_SWAPNAME ENDP


;----------------------------------------------------------------------
; Converted From C.
;
;test_acadl()
; { _splitpath(program,drive,dir,fname,ext);
;   strupr(ext);
;   if(strcmp(ext,".EXE")==0) { return(0); };
;   if(strcmp(ext,".COM")==0) { return(0); };
;   return(-1);
; };
;----------------------------------------------------------------------
_TEST_ACADL PROC

         PUSH SI
         PUSH DI

         lea  si,_program
         mov  cx,80             ;Look through 80 characters MAX.

 findnl: mov  al,[si]           ;Get current character.
         inc  si                ;point at next.
         or   al,al             ;Test for ZERO.
         loopnz findnl          ;Loop up again if NOT ZERO.
         sub  si,3              ;Point at last character.

         mov  ax,[si]           ;Get eXE or cOM.
         or   ax,2020h          ;Make lower case.
         cmp  ax,"ex"           ;Is it EXE?
         jz   xorc              ;Yes? Jump.
         cmp  ax,"mo"           ;Is it COM?
         jz   xorc              ;Yes? Jump.
         mov  ax,0ffffh         ;No? Return -1.
         jmp  nxorc

  xorc:  xor  ax,ax             ;Return 0.

 nxorc:  POP  DI
         POP  SI
         RET

_TEST_ACADL ENDP

;----------------------------------------------------------------------
; Converted From C.
;
; botmsg(msgx)
; char msgx[];
; { clearwindow(0,22,79,22,0x70);
;   gotoxy(0,22);
;   setcolor(0x70);
;   sprintstr(msgx);
;   setcolor(7);
;   gotoxy(0,23);
; };
;
;
;----------------------------------------------------------------------
_BOTMSG PROC

         push bp
         mov  bp,sp

         push 70h               ;Clearwindow(0,22,79,22,0x70);
         push 22
         push 79
         push 22
         push 0
         call _clearwindow

         push 22                ;Gotoxy(0,22);
         push 0
         call _gotoxy

         push 70h
         call _setcolor         ;Setcolor(0x70);

         push ds
         mov  ax,[bp+4]
         push ax
         call _sprintstr

         push 7                 ;Setcolor(0x70);
         call _setcolor

         push 23                ;Gotoxy(0,23);
         push 0
         call _gotoxy

         add sp,26              ;Correct the stack.

         pop  bp
         ret

_BOTMSG ENDP

;----------------------------------------------------------------------
; Converted From C.
;
; copyright2()
; {  int  retcode;
;    strcpy(runname,thisprog);
;    _splitpath(runname,drive,dir,fname,ext);    /* Generate path to AutoCAD */
;    strcpy(fname,FNAMEX);
;    strcpy(ext,EXTX);
;    _makepath(runname,drive,dir,fname,ext);
;
;    if(shell() == -1) { botmsg(abortmsg); };
;
;    retcode = get_retcode() & 255;
;    if(retcode == 241)
;     { release_all();
;       retcode--;
;     };
;    if(retcode != 240) { return(-1); };
;    return(0);
; };
;----------------------------------------------------------------------
_COPYRIGHT2 proc

        push bp
        mov  bp,sp

        push es
        mov  ax,ds
        mov  es,ax

        lea  si,_thisprog       ;STRCPY(runname,thisprog);
        lea  di,_runname
        mov  cx,80
        cld
        rep  movsb

        lea  di,_runname       ;Find end of RUNNAME.
        mov  cx,80             ;Look through 80 characters MAX.
        xor  al,al
        cld
        repnz scasb
        sub  di,2              ;Point at last character.

        std                    ;find the "\"
        mov   al,"\"
        mov   cx,13
        repnz scasb
        add   di,2

        cld
        lea  si,_FNAMEX        ;Copy FNAMEX into place (10MENU or BSHELL).
        mov  cx,6
        rep  movsb

        mov  al,"."             ;Copy a period before extension.
        stosb

        lea  si,_EXTX           ;Copy the extension.
        mov  cx,4
        rep  movsb

        call _shell             ;do the shell.
        cmp  ax,-1              ;Error?
        jnz  getret             ;No? Jump over error print.

        lea  si,_abortmsg       ;Point at abort message.
        push ds
        push si

        call _botmsg
        pop  si
        pop  ds

getret: call _get_retcode       ;Get return code.
        xor  ah,ah              ;Zap the upper part.

        cmp  ax,241             ;Does AX=252?
        jnz  cmp251             ;No? Jump over.
        call _release_all       ;Release.
        dec  ax                 ;Set up for no error.

cmp251: cmp  ax,240             ;Is retcode equal to 251?
        jz   zapax              ;Yes? OK... Jump out and clear.
        mov  ax,-1              ;No? Signal Error.
        jmp  c2x                ;Jump out... set to -1.

 zapax: xor  ax,ax              ;Clear
        jmp  c2x

 c2x:   pop  es
        pop  bp
        ret

_COPYRIGHT2 endp

;----------------------------------------------------------------------
; getenva("PATH=",&storage);
;----------------------------------------------------------------------
_getenva proc

        push bp
        mov  bp,sp
        push ds
        push es

        mov  ds,[bp+10]         ;Get data segment.
        mov  si,[bp+8]          ;Get pointer to parameter to use.
                                ;DS:SI points to parm to look for.
        mov  ah,51h
        int  21h                ;Get PSP in BX.
        mov  es,bx              ;Switch to PSP segment.
        mov  bx,[es:2ch]        ;Get ENV segment.
        mov  es,bx              ;Switch to environment segment.
        xor  di,di              ;ES:DI point to first environment parm.

        push di
        push si

        cld
cmpagn: mov  al,[si]            ;Get a byte from the sample.
        or   al,al              ;Was this the last byte of sample?
        jz   gdenv              ;Yes? Jump out.

        cmpsb                   ;Compare the first bytes.
        jz   cmpagn             ;Compare another byte if same.
;-------
nxtep:  pop  si                 ;Get SI off of the stack.
        push si                 ;Save it up there again.

 fndnx: inc  di                 ;Point to next character in env string.
        mov  ax,es:[di-1]       ;Get word pointed to by ES:DI.
        or   ax,ax              ;End of environment?
        jz   gexbad             ;Yes? Jump out.
        or   al,al              ;End of environment string?
        jnz  fndnx              ;Loop up. Get next.
        jmp  cmpagn             ;Jump up to restart search on next var.
;-------
gdenv:  pop  si                 ;ES:DI points to parameter data.
        pop  si

        mov  si,[bp+4]          ;Get destination pointer.
        mov  ds,[bp+6]

        mov  [si],di            ;Store destination address.
        mov  [si+2],es          ;Store destination segment (COMPACT MODE).
        jmp  gex
;-------
gexbad: pop  si
        pop  si

gex:    pop  es
        pop  ds
        pop  bp
        ret

_getenva endp

;----------------------------------------------------------------------
_get_run_name proc

        push ds
        push es

        mov  ax,ds
        mov  es,ax

        mov  ah,51h
        int  21h                ;Get PSP in BX.
        mov  ds,bx              ;Switch to PSP segment.
        mov  bx,[ds:2ch]        ;Get ENV segment.
        mov  ds,bx              ;Switch to environment segment.
        mov  si,0ffffh          ;ES:DI point to first environment parm.

  grn:  inc  si                 ;Increment environment pointer.
        cmp  word ptr [si],0    ;Look for end of environment.
        jnz  grn                ;End? No? Jump up again.
        add  si,4               ;Point to run name.

        cld                     ;DS:SI points to source.
        lea  di,_thisprog       ;ES:DI points to destination.
        mov  cx,80              ;Transfer 80 characters.
        rep  movsb              ;Move um now.

        pop  es
        pop  ds
        ret

_get_run_name endp

;----------------------------------------------------------------------
; Converted From C.
;
;----------------------------------------------------------------------
;run_acad()
; { setcolor(0x70);
;   gotoxy(0,21);
;   clearwindow(0,21,79,21,0x70);
;   sprintstr(" EXECUTING: ");
;   sprintstr(runname);
;   gotoxy(0,24);
;
;   if(shell() == -1)                         /* Run ACAD.EXE */
;      { clearwindow(0,22,79,22,0x70);
;        gotoxy(1,22);
;        setcolor(0x70);
;        sprintstr("ERROR: EXECUTION FAILED");
;        gotoxy(0,23);
;      };
; };
;----------------------------------------------------------------------

_RUN_ACAD PROC

        push bp

        push 70h
        call _setcolor

        push 21
        push 0
        call _gotoxy

        push 70h
        push 21
        push 79
        push 21
        push 0
        call _clearwindow

        push ds
        lea  ax,executing
        push ax
        call _sprintstr

        push ds
        lea  ax,_runname
        push ax
        call _sprintstr

        push 24
        push 0
        call _gotoxy

        add  sp,28              ;Correct the stack.
        call _shell
        cmp  ax,-1
        jnz  rax

        push 70h
        push 22
        push 79
        push 22
        push 0
        call _clearwindow

        push 22
        push 1
        call _gotoxy

        push 70h
        call _setcolor

        push ds
        lea  ax,errexx
        push ax
        call _sprintstr

        push 23
        push 0
        call _gotoxy

        add  sp,24              ;Correct the stack.

  rax:  pop  bp
        ret

_RUN_ACAD ENDP

;----------------------------------------------------------------------
; Converted From C.
;
; struct system_desc
; { int  size;
;   char model;
;   char submodel;
;   char bios_release;
;   char features;
; } far *sys_desc;
;
; get_box_id()
; { inregs.h.ah=0xc0;
;   int86x(0x15,&inregs,&outregs,&segregs);
;
;   FP_SEG(sys_desc)=segregs.es;
;   FP_OFF(sys_desc)=outregs.x.bx;
;
;   FP_SEG(hpid)=0xf000;
;   FP_OFF(hpid)=0x00f8;
;
;   if((sys_desc->features & 2)==2) { machine = 0x20; };  /* Must be a PS2 */
;   if(*hpid==0x5048)     { machine = 0x11; };
; };
;----------------------------------------------------------------------
_GET_BOX_ID PROC

        PUSH ES                 ;Save ES.

        PUSH DS                 ;UnNeeded, but what the hell.
        PUSHF                   ;Some Compaqs leave interrupts OFF here.
        MOV  AH,0C0H
        INT  15h
        POPF
        POP  DS

        mov  al,es:[bx+5]       ;Get Computer's Feature byte.
        and  al,2               ;And it.  Test for microchannel?
        jz   test4hp

        mov  ax,20h             ;Mark as a PS2.
        mov  _machine,ax
        jmp  gbix

test4hp:mov  ax,0f000h          ;Load segment of HP mark.
        mov  es,ax
        mov  bx,00f8h           ;Load offset of HP mark.
        mov  ax,es:[bx]         ;Get HP byte.
        cmp  ax,5048h           ;Test for HP.
        jnz  gbix               ;Jump if no HP.

        mov  ax,11h             ;Mark machine as HP.
        mov  _machine,ax

 gbix:  POP  ES
        RET

_GET_BOX_ID ENDP


;----------------------------------------------------------------------

COMMENT*
_rest_old_blks proc

         push ds
         push es

         cli
         mov  es,_adr_afus      ;Get address of block that was after us.
         xor  di,di             ;ES:DI point to destination.
         lea  si,blk_afus       ;DS:SI point to stored block.
         cld
         mov  cx,16
         rep  movsb

         mov  es,adr_b4us       ;Get address of block that was before us.
         xor  di,di             ;ES:DI point to destination.
         lea  si,blk_b4us       ;DS:SI point to stored block.
         cld
         mov  cx,16
         rep  movsb

         sti
         pop  es
         pop  ds
         ret

_rest_old_blks endp
*

;----------------------------------------------------------------------

_shutdown proc

          mov cs:downflag,1
          ret

_shutdown endp

;----------------------------------------------------------------------

_rest_old_blks proc

          push ax
          push bx
          push cx
          push dx
          push ds
          push es

          mov  ah,51h
          int  21h              ;Call Dos.  Get PSP in BX.

   robl:  call nextblock

   robn:  or   cx,cx            ;FREE memory, or tied to a PSP? CX=0 if Free.
          jz   robx

          cmp  cx,adr_b4us
          jc   robx

          push es
          push dx
          push cx
          push bx
          push ax

          cmp  cs:downflag,1   ;1=Final call to routine.
          jz   sdj

          cmp  cs:release_all,1 ;1=Release all memory above us.
          jz   sdj

          push ds
          mov  ds,bx
          cmp  word ptr ds:[0],20cdh     ;are first two bytes CD 20?
          pop  ds
          jnz  sdj              ;Not a psp? Then Jump over.
          mov  es,bx
          mov  ah,4ah
          mov  bx,8
          int  21h              ;Resize PSP to 128 bytes.
          jmp  isx

;---------

  sdj:    mov  es,bx
          mov  ah,49h           ;Free Allocated memory.
          int  21h              ;Call DOS.
          jmp  isx

;---------

  isx:    pop  ax
          pop  bx
          pop  cx
          pop  dx
          pop  es

    robx: cmp  al,5Ah
          jnz  robl

          pop  es
          pop  ds
          pop  dx
          pop  cx
          pop  bx
          pop  ax
          ret

_rest_old_blks endp

;----------------------------------------------------------------------

nextblock proc

          push es
          dec  bx
          mov  es,bx
          inc  bx                   ;BX points at current block.
          add  bx,word ptr es:[3]   ;Add in size of block.
          mov  es,bx
          mov  al,byte ptr es:[0]   ; AL = Type (4D or 5A).
          inc  bx                   ; BX = Data Address.
          mov  cx,word ptr es:[1]   ; CX = PSP.
          mov  dx,word ptr es:[3]   ; DX = Size.
          pop  es
          ret

nextblock endp

;----------------------------------------------------------------------

_rest_cur_blks proc

         push ds
         push es

         cli
         mov  es,_cadr_afus     ;Get address of block that was after us.
         xor  di,di             ;ES:DI point to destination.
         lea  si,cblk_afus      ;DS:SI point to stored block.
         cld
         mov  cx,16
         rep  movsb

         mov  es,cadr_b4us      ;Get address of block that was before us.
         xor  di,di             ;ES:DI point to destination.
         lea  si,cblk_b4us      ;DS:SI point to stored block.
         cld
         mov  cx,16
         rep  movsb

         sti
         pop  es
         pop  ds
         ret

_rest_cur_blks endp

;--------------------------------------------------------------------------

_getakey proc

         xor  ax,ax
         int  16h
         ret

_getakey endp

;--------------------------------------------------------------------------

dos proc

         pushf
         cli
         call dword ptr cs:o21o
         ret

dos endp

;--------------------------------------------------------------------------

_get_retcode proc

         mov  ah,4dh
         call dos
         ret

_get_retcode endp

;--------------------------------------------------------------------------

_f88_i15 proc

         mov  ah,88h
         pushf                  ;Protect against ints being turned off.
         push ds
         int  15h
         pop  ds
         popf
         mov  cs:esize,ax
         ret

_f88_i15 endp

;--------------------------------------------------------------------------
_get_psp proc

         mov  ah,51h
         int  21h
         mov  _orig_psp,bx      ;Save the original PSP
         ret

_get_psp endp

;--------------------------------------------------------------------------
_hookup  proc

         push ds
         push es

         call _get_psp

         mov  ah,2fh
         int  21h
         mov  orig_dtao,bx      ;Save original DTA
         mov  orig_dtas,es

         mov  ax,3521h          ;Store vector to INT 21.
         int  21h
         mov  o21o,bx
         mov  o21s,es

         mov  ax,3501h          ;Store vector to INT 01
         int  21h
         mov  o01o,bx
         mov  o01s,es

         mov  ax,3503h          ;Store vector to INT 03
         int  21h
         mov  o03o,bx
         mov  o03s,es

     ;;  mov  ax,3508h          ;Store vector to INT 08
     ;;  int  21h
     ;;  mov  cs:o08o,bx
     ;;  mov  cs:o08s,es

         mov  ax,cs
         mov  ds,ax
         mov  dx,offset INT21   ;Hook up to INT 21
         mov  ax,2521h
         int  21h

     ;;; mov  dx,offset INT08   ;Hook up to INT 08
     ;;; mov  ax,2508h
     ;;; int  21h

         pop  es
         pop  ds
         ret

_hookup  endp

;--------------------------------------------------------------------------

_clear_cmdln proc

         push si
         push ds
         push ax
         push bx

         mov  ah,51h
         call dos               ;Get PSP in BX.

         mov  ds,bx
         mov  si,81h
         mov  cl,ds:[80h]
         and  cx,00ffh
         jz   ccmx

 ccloop: mov  ax,[si]

         cmp  ax,"p/"           ;Clear ACS /P function.
         jz   ccsmack
         cmp  ax,"P/"
         jz   ccsmack

         cmp  ax,"R/"           ;Used to determint if we need to free
         jz   ccsmack           ;TSRLOAD memory.
         cmp  ax,"r/"
         jz   ccsmack

         cmp  ax,"9/"           ;Clear ACS /9 function.
         jnz  ccnmack

ccsmack: mov  word ptr [si],2020h
ccnmack: inc  si
         loop ccloop

 ccmx:   pop  bx
         pop  ax
         pop  ds
         pop  si
         ret


_clear_cmdln endp

;--------------------------------------------------------------------------


_ts_enable proc

         mov  tripskip,0        ;Set initial trip skip.
         ret

_ts_enable endp         



;--------------------------------------------------------------------------

_geti21  proc

         push es
         mov  ax,3521h          ;Store vector to INT 21.
         int  21h
         mov  o21o,bx
         mov  o21s,es
         pop  es
         ret

_geti21  endp

;--------------------------------------------------------------------------

_install15  proc

         push ds
         push es
         mov  ax,3515h          ;Store vector to INT 15.
         int  21h
         mov  cs:o15o,bx
         mov  cs:o15s,es

         mov  ax,cs
         mov  ds,ax
         mov  dx,offset INT15   ;Hook up to INT 15.
         mov  ax,2515h
         int  21h
         pop  es
         pop  ds
         ret

_install15  endp

;--------------------------------------------------------------------------

_uninstall15 proc

         push ds

         mov  dx,cs:o15o
         mov  ds,cs:o15s
         mov  ax,2515h
         int  21h

         pop  ds
         ret

_uninstall15 endp

;--------------------------------------------------------------------------

_setretry proc

         mov  cs:retry,1
         ret

_setretry endp

;--------------------------------------------------------------------------

_clrretry proc

         mov  cs:retry,0
         ret

_clrretry endp

;--------------------------------------------------------------------------

_clr_tskip proc

         mov  cs:tripskip,0
         ret

_clr_tskip endp


;--------------------------------------------------------------------------
; This routine swaps stored values with those in vector table.
;--------------------------------------------------------------------------
_swapvects proc

                push ds
                push es
                push si
                push di
                push cx
                push bx

                xor  ax,ax
                mov  ds,ax
                mov  si,ax                      ;ES:DI ->vector table.

                mov  ax,cs
                mov  es,ax

                mov  di,offset _vector_table    ;DS:SI ->0:0

                mov  cx,16h                     ;Swap vectors 00 - 0A.
                call swaploop

                add  si,8                       ;Skip vectors 0B & 0C.
                add  di,8

                mov  cx,4
                call swaploop                   ;Swap vectors 0D & 0E.

                add  si,4                       ;Skip vector  0F.
                add  di,4

                mov  cx,200h - 20h              ;Swap vectors 10 - FF.
                call swaploop

              ; mov  cx,200h - 12h - 2
              ; call swaploop
              ;
              ; add  si,20h                     ;Swap vectors after INT 08.
              ; add  di,20h
              ; mov  cx,512 - 20h
              ; call swaploop

            ;;; cmp  cs:revectored,0            ;Is phar lap running?
            ;;; jz   no_revect
            ;;; call swap8

no_revect:      pop  bx
                pop  cx
                pop  di
                pop  si
                pop  es
                pop  ds
                ret

_swapvects endp


swaploop:       mov  ax,ds:[si]                 ;Get data.
                mov  bx,es:[di]
                mov  ds:[si],bx
                mov  es:[di],ax                 ;Swap data.
                inc  si
                inc  si                         ;Inc pointers.
                inc  di
                inc  di
                loop swaploop                   ;Loop up.
                ret
 
;-----------------------------------------------------------------------------

_save_psp proc

                mov  ah,51h                     ;Get current PSP.
                int  21h
                mov  old_psp,bx
                ret
_save_psp endp

;-----------------------------------------------------------------------------
_save_dta proc

                push es
                mov  ah,2fh
                int  21h                        ;Get current DTA.
                mov  old_dtao,bx                ;Save DTA.
                mov  old_dtas,es
                pop  es
                ret
_save_dta endp

;-----------------------------------------------------------------------------
_new_dta proc
                push ds
                mov  ds,orig_dtas
                mov  dx,orig_dtao               ;Set DTA to us.
                mov  ah,1ah
                int  21h
                pop  ds
                ret
_new_dta endp

;-----------------------------------------------------------------------------
_new_psp proc
                mov  bx,_orig_psp
                mov  ah,50h
                int  21h
                ret
_new_psp endp

;-----------------------------------------------------------------------------
_restore_dta proc

                push ds
                mov  dx,old_dtao
                mov  ds,old_dtas
                mov  ah,1ah
                int  21h
                pop  ds
                ret

_restore_dta endp
;-----------------------------------------------------------------------------
_restore_psp proc

                mov  bx,old_psp
                mov  ah,50h
                int  21h
                ret

_restore_psp endp

;-----------------------------------------------------------------------------

_rollout proc

     ro_top:    call _swap_open         ;Open or create swap file. Handle in AX.
                mov  _file_handle,ax    ;Store file handle.
                call _write_swap        ;Write the swap file to disk.
                cmp  ax,0ffffh          ;Did write fail?
                jnz  ronxit             ;No?, then return 0.

                cmp  _emm_use_flag,1    ;Were we trying to use Expanded Memory?
                jnz  roxit              ;No? Then signal error. Return AX=FFFF.

                call _ems_close         ;Close out EMS handle.
                mov  _emm_use_flag,0    ;Signal NO EMS usage.
                call revert             ;Signal that we are reverting to file.
                jmp  ro_top             ;Try again.

     roxit:     ret                     ;Take file handle off of stack.
;---------------
     ronxit:    xor  ax,ax
                ret

_rollout endp

;-----------------------------------------------------------------------------

revert proc
                push ds
                push dx
                push ax

                mov  ax,cs
                mov  ds,ax
                mov  dx,offset revmsg
                mov  ah,9
                int  21h

                pop  ax
                pop  dx
                pop  ds
                ret

revmsg:         db   7,0dh,0ah,"OUT OF EMS! SWITCHING TO DISK",0dh,0ah,7,"$"

revert endp

;-----------------------------------------------------------------------------

_rollin  proc
                mov  ax,_file_handle    ;Get file handle.
                call _swap_reset        ;Reset handle or ems. Stack has handle.
                call _read_swap         ;Read in swap file. Stack has handle.
                cmp  ax,0ffffh          ;-1=Failed.
                jz   rix                ;Did it fail? Jump if -1.

                call _swap_reset        ;Reset file or EMS pointer again.

                call _swap_zap          ;Zap handle on stack.
                call _swap_close        ;Close handle on stack.

                push ds                 ;Push segment of swapfile name.
                lea  ax,_swapfile
                push ax                 ;Push offset of swapfile name.
                call _unlink            ;Erase swapfile.
                add  sp,4               ;adjust stack.
                xor  ax,ax

        rix:    ret                     ;Return and POP handle off of stack.

_rollin  endp

;-----------------------------------------------------------------------------

_unlink  proc
                push bp
                mov  bp,sp
                push ds
                push dx

                mov  ds,[bp+6]
                mov  dx,[bp+4]          ;DS:DX points to filename.
                mov  ah,41h             ;Delete the file.
                call dos                ;Call DOS.

                pop  dx
                pop  ds
                pop  bp
                ret
_unlink  endp

;-----------------------------------------------------------------------------
_write_swap proc

                mov  bx,_file_handle    ;Get file handle from storage.
                mov  di,_cadr_afus      ;Move starting address to buffer.
                mov  writestart,di

                mov  _swap_size_l,0     ;Clear previous swap size.
                mov  _swap_size_h,0

next_mcb:       push es
                mov  es,di              ;DI holds segment of next write.
                mov  si,di
                mov  di,es:[0003]       ;Move top to buffer
                mov  cx,es:[0001]       ;CX has owner.
                mov  al,es:[0000]       ;Get MCB type.
                inc  di
                pop  es
                add  di,si
                mov  writetop,di
                mov  mcbtype,al
                or   cx,cx              ;0000=Free.
                jnz  wsnorm             ;Not 0000? Then Write Normally.

                call w_writestart       ;Write segment to file.
                inc  writestart
                call w_writestart       ;Write the top to file.
                dec  writestart

                push ds                 ;Write the memory block to disk.
                mov  ds,writestart
                mov  dx,0
                mov  cx,16
                mov  ah,40h

                call read_write         ;Call DOS/EMM read write function.
                pop  ds
                jc   wsex               ;CY=Error. Jump out.

                jmp  wsnowrite          ;Jump over data write.

wsnorm:         call w_writestart       ;Write the segment to the file.
                jc   wsex               ;CY=Error.

                call w_writetop         ;Write the top to the file.
                jc   wsex               ;CY=Error.

                call w_data             ;Write the data now.
                jc   wsex

wsnowrite:      mov  di,writetop
                mov  writestart,di

                cmp  mcbtype,5Ah        ;Was it the final MCB?
                jz   ws1x               ;Yes? Then Jump out.

                jmp  next_mcb

wsex:           mov  ax,0ffffh
                ret

ws1x:           mov  writestart,0       ;****TEST****
                call w_writestart       ;****TEST****
                call w_writestart       ;****TEST****
                ret

_write_swap endp

;-----------------------------------------------------------------------------

w_writestart:   mov  ah,40h             ;Write the segment to the file.
                lea  dx,writestart
                mov  cx,2
                call read_write         ;Call DOS/EMM read/write function.
                ret

;-----------------------------------------------------------------------------
w_writetop:     mov  ah,40h             ;Write the top to the file.
                lea  dx,writetop
                mov  cx,2
                call read_write         ;Call DOS/EMM read/write function.
                ret

;-----------------------------------------------------------------------------
accumulate:     pushf
                push ds
                mov  cx,dgroup
                mov  ds,cx

                add  _swap_size_l,ax    ;Add bytes written to swap size.
                adc  _swap_size_h,0

                mov  cx,_swap_size_h    ;Get current swap size (high part).
                cmp  _biggesth,cx       ;Is it bigger than previous value?
                jz   acxit0             ;Same? Jump to Compare low part.
                jc   acxit3             ;Bigger? Jump to save new bigger value.
                jmp  acxit2             ;Smaller? Jump and ignore values.

   acxit0:      mov  cx,_swap_size_l    ;Get low part of current swap size.
                cmp  _biggestl,cx       ;Compare to previous saved value.
                jnc  acxit2             ;Jump out if smaller.

   acxit3:      mov  cx,_swap_size_h    ;Update biggest swap size used.
                mov  _biggesth,cx
                mov  cx,_swap_size_l
                mov  _biggestl,cx

   acxit2:      pop  ds
                popf
                ret

;-----------------------------------------------------------------------------
w_data:         mov  ah,40h             ;DOS Write.
                mov  si,writestart
                mov  cx,writetop
                call readorwrite
                ret

;-----------------------------------------------------------------------------

_read_swap proc
                mov  bx,_file_handle    ;Get dos file handle from storage.
                mov  di,_cadr_afus      ;Move starting address to buffer.
                mov  writestart,di

next_mcbr:      mov  ah,3fh
                mov  cx,2
                lea  dx,writestart      ;Get starting segment of write.

                call read_write         ;Call DOS/EMM read/write function.

                jc   rserror
                or   ax,ax              ;End of file?
                jz   rsout              ;Yes? Then jump out.
                cmp  writestart,0       ;EMS End of Data?  ****TEST****
                jz   rsout              ;                  ****TEST****

                mov  ah,3fh
                mov  cx,2
                lea  dx,writetop        ;Get final read segment address.
                call read_write         ;Call DOS/EMM read/write function.

                jc   rserror
                or   ax,ax              ;End of file?
                jz   rsout              ;Yes? Then jump out.
                cmp  writetop,0         ;EMS End of Data?      ****TEST****
                jz   rsout              ;                      ****TEST****

                mov  ah,3fh
                mov  si,writestart
                mov  cx,writetop

                call readorwrite        ;Read in the data.
                jc   rserror

                push es
                mov  di,writestart      ;Get segment of this MCB.
                mov  es,di
                mov  al,es:[0000]       ;Get MCB type.
                pop  es

                cmp  al,5Ah             ;Final one?
                jnz  next_mcbr          ;No? Jump to get another.

rsout:          clc                     ;Clear carry.
                ret                     ;Return to caller.

rserror:        mov  ax,0ffffh          ;Error condition.
                stc                     ;Set carry.
                ret

_read_swap endp

;-----------------------------------------------------------------------------
;This function handles disk io.
;
; On Entry:
;
; AH=3F=Read
;    40=Write
; CX=Beginning SEG:0000 to write data from.
; SI=Number of paragraphs to write or read.
;
;-----------------------------------------------------------------------------
readorwrite:    push es
                push ds

                mov  cs:writetop,cx
                mov  cs:writestart,si

    rloop2:     mov  cx,cs:writetop
                sub  cx,si                      ;DI = Pgphs from start to finish.

                cmp  cx,4095                    ;Compare number of paragraphs
                jc   rrsw                       ;Number of pgfs in 64K-1.
                mov  cx,4095

     rrsw:      mov  ds,si
                xor  dx,dx                      ;DS:DX points to data.

                add  si,cx                      ;SI points to next start.

                shl  cx,1
                shl  cx,1
                shl  cx,1
                shl  cx,1                       ;CX holds bytes to read.
                or   cx,cx                      ;Any data to write?
                jz   none2writ

                push ax
                call read_write                 ;Handle dos/emm read/write.
                mov  di,ax
                pop  ax
                jc   rswx

     none2writ: cmp  di,cx                      ;Fewer than attempt?
                jc   rswx                       ;Yes? Then Abort.

                or   cx,cx                      ;Compare to ZERO.
                jnz  rloop2

                clc

     rswx:      pop  ds
                pop  es
                ret


;--------------------------------------------------------------------------

_swap_reopen proc

                lea  dx,_swapfile
                mov  ah,3dh                     ;Open File.
                mov  al,82h                     ;Read,Write,NoInherit.
                call dos
                jc   sobxx                      ;Jump out on error.
                ret                             ;Return.

sobxx:          mov  ax,0ffffh
                ret

_swap_reopen endp

;--------------------------------------------------------------------------
_swap_open proc
                cmp  _emm_use_flag,1            ;Are we using Expanded Memory?
                jz   sobx                       ;Yes? Jump out.

                lea  dx,_swapfile
                mov  ah,5ah                     ;Create the Unique swapfile.
                mov  cx,0
                call dos
                jc   sobx                       ;Jump out on error.

                mov  bx,ax
                mov  ah,3eh                     ;Close the file.
                call dos

                lea  dx,_swapfile
                mov  ah,3dh                     ;Open File.
                mov  al,82h                     ;Read,Write,NoInherit.
                call dos
                jc   sobx                       ;Jump out on error.
                ret                             ;Return.

sobx:           mov  ax,0ffffh
                ret

_swap_open endp

;--------------------------------------------------------------------------

_swap_close proc

                cmp  _emm_use_flag,1            ;Are we using Expanded Memory?
                jz   scxx                       ;Yes? Jump out.

                mov  ah,3eh                     ;Close file function.
                mov  bx,_file_handle            ;Get DOS file handle.
                call dos                        ;Close the handle.
        scxx:   ret

_swap_close endp

;--------------------------------------------------------------------------
_swap_reset proc

                cmp  _emm_use_flag,1    ;Do we reset swap file, or ems.
                jz   sruemm             ;Use EMM? Jump to emm handler.

      sruf:     mov  ax,4200h
                mov  bx,_file_handle
                xor  cx,cx
                xor  dx,dx
                call dos
                ret                     ;Exit #1.

      sruemm:   xor  ax,ax
                mov  cs:ems_offset,ax
                mov  cs:ems_segment,ax
                ret                     ;Exit #2.

_swap_reset endp

;--------------------------------------------------------------------------
; Zap the swap file by writing ZERO bytes to it at current location.
;--------------------------------------------------------------------------
_swap_zap proc
                mov  ah,40h                     ;Dos Write function.
                mov  bx,_file_handle            ;Get handle.
                xor  cx,cx                      ;Write ZERO bytes.
                call dos                        ;Call DOS to write.
                ret
_swap_zap endp

;--------------------------------------------------------------------------
; This procedure sets the EMM_LOADED flag, and returns 0 or 1 for EMM-LOADED.
;--------------------------------------------------------------------------
_emm_loaded proc

                push es
                push bx

                mov  _emm_load_flag,0

                mov  ax,3567h
                int  21h                        ;Get vector to EMM.

                mov  di,0ah                     ;ES:000A points to "EMMXXXX0"
                cmp  word ptr es:[di],"ME"
                jnz  elnz
                cmp  word ptr es:[di+2],"XM"
                jnz  elnz
                cmp  word ptr es:[di+4],"XX"
                jnz  elnz
                cmp  word ptr es:[di+6],"0X"
                jnz  elnz

                mov  _emm_load_flag,1            ;EMM is loaded.
           ;;;  mov  _emm_use_flag,1             ;Use EMM.

   elnz:        mov  ax,_emm_load_flag           ;Return status.

                pop  bx
                pop  es
                ret

_emm_loaded endp

;--------------------------------------------------------------------------
; This procedure allocates and saves an EMM handle.
;--------------------------------------------------------------------------
_ems_open proc

                push bp
                mov  bp,sp
                mov  bx,[bp+4]                  ;Get number of 16K pages.
                pop  bp
                mov  ah,43h
                mov  ems_start_pgf,bx
                int  67h
                or   ah,ah                      ;AH=0 if OK.
                jnz  esbx                       ;Jump out if unsuccessful.

                mov  ems_handle,dx

                mov  ax,5301h                   ;Set name of EMM handle.
                mov  dx,ems_handle
                or   dx,dx
                jz   esxx
                lea  si,ems_name
                int  67h
                xor  ax,ax
         esxx:  ret

         esbx:  mov  ax,0ffffh                  ;Signal BAD result.
                ret


_ems_open endp

;--------------------------------------------------------------------------
; This procedure deallocates the EMM handle.
;--------------------------------------------------------------------------
_ems_close proc
                mov  ah,45h                     ;EMS DeAllocate function.
                mov  dx,ems_handle              ;Get the EMS handle.
                or   dx,dx                      ;Is it a valid handle?
                jz   ecxx                       ;No? Jump out.
                int  67h
         ecxx:  mov  ems_handle,0               ;Reset to ZERO.
                ret
_ems_close endp

;--------------------------------------------------------------------------
;--------------------------------------------------------------------------
read_write proc
                cmp  cs:_emm_use_flag,1         ;Are we using expanded memory?
                jz   erwx                       ;Yes, Jump to EMM routines.
                call dos                        ;No? Call DOS.
                ret

        erwx:   cmp  ah,40h
                jz   _ems_write
                cmp  ah,3fh
                jz   _ems_read
                ret

read_write endp

;--------------------------------------------------------------------------
; Read EMS procedure.
;
; On Entry:   AH     = 3fh ; Just for grins.
;             BX     = EMM Handle.
;             DS:DX  = Segment:Offset of Location to read from.
;             CX     = Number of bytes to read.
;
;--------------------------------------------------------------------------
_ems_read proc
                push cx
                push bx
                push si
                push ds

                mov  cs:dest_init_seg,ds
                mov  cs:dest_init_ofs,dx

                mov  cs:dest_handle,0           ;Handle N/A to conventional RAM.
                mov  cs:dest_mem_type,0         ;Conventional Memory.

                mov  cs:region_len_l,cx         ;Store length of memory move.
                mov  cs:region_len_h,0

                mov  cs:src_mem_type,1          ;Signal Move FROM EMS.
                mov  bx,cs:ems_handle           ;Get EMM Handle.
                mov  cs:src_handle,bx           ;Store EMM Handle.

                mov  dx,cs:ems_offset
                mov  bx,cs:ems_segment

                push dx
                and  dx,3fffh
                mov  cs:src_init_ofs,dx         ;Store offset into EMM page.
                pop  dx

                clc
                rcl  dx,1                       ;Multiply High part X 4 since
                rcl  bx,1                       ;Segment will be 16K page and
                                                ;Not 64K page.
                rcl  dx,1
                rcl  bx,1
                mov  cs:src_init_seg,bx         ;Store segment into page.

                mov  ax,5700h
                lea  si,cs:region_len_l
                push ds
                push cs
                pop  ds
                int  67h
                pop  ds

                add  cs:ems_offset,cx
                adc  cs:ems_segment,0

                pop  ds
                pop  si
                pop  bx
                pop  cx

                mov  ax,cx                      ;Return bytes read.
                clc

                ret
_ems_read endp

;--------------------------------------------------------------------------
; Write EMS procedure.
;
; On Entry:   AH     = 40h ; Just for grins.
;             BX     = EMM Handle.
;             DS:DX  = Segment:Offset of Location to write to from.
;             CX     = Number of bytes to read.
;
;--------------------------------------------------------------------------
_ems_write proc

                push cx
                push bx
                push si
                push ds

                mov  cs:src_init_seg,ds
                mov  cs:src_init_ofs,dx

                mov  dx,cs
                mov  ds,dx

                mov  cs:src_handle,0               ;Handle N/A to conventional RAM.
                mov  cs:src_mem_type,0             ;Conventional Memory.

                mov  cs:region_len_l,cx            ;Store length of memory move.
                mov  cs:region_len_h,0

                mov  cs:dest_mem_type,1            ;Signal Move TO EMS.
                mov  bx,cs:ems_handle
                mov  cs:dest_handle,bx             ;Store EMM Handle.

                mov  dx,cs:ems_offset
                mov  bx,cs:ems_segment

                push dx
                and  dx,3fffh
                mov  cs:dest_init_ofs,dx           ;Store offset into EMM page.
                pop  dx

                clc
                rcl  dx,1                          ;Multiply High part X 4 since
                rcl  bx,1                          ;Segment will be 16K page and
                                                   ;Not 64K page.
                rcl  dx,1
                rcl  bx,1

                mov  cs:dest_init_seg,bx           ;Store segment into page.
                mov  ax,5700h
                lea  si,cs:region_len_l

                int  67h
                or   ah,ah                         ;Get status.
                jz   ewok
                xor  cx,cx

      ewok:     add  cs:ems_offset,cx
                adc  cs:ems_segment,0

                pop  ds
                pop  si
                pop  bx

                mov  ax,cx                         ;Return bytes written.
                call accumulate                    ;Add in size of data written.

                pop  cx

                or   ax,ax                         ;Were any bytes written?
                jnz  ewx1                          ;Yes? Then Jump out.
                stc                                ;NO? Then AX=0,CY and exit.
                ret

      ewx1:     clc
                ret

_ems_write endp


;--------------------------------------------------------------------------

copy_cmd proc
                push ds
                push es

                lea  di,_cmdline        ;ES:DI points to our command line.
                mov  si,cmdoff
                mov  ds,cmdseg          ;DS:SI point to ACAD passed cmd line.
                mov  cx,80h
                cld
                rep  movsb

                pop  es
                pop  ds
                ret
copy_cmd endp

;--------------------------------------------------------------------------
copy_env proc
                push ds
                push es

                mov  es,envseg  ;Get segment of environment.
                xor  si,si      ;Initialize pointer.
                xor  cx,cx      ;Initialize count.

not_end_env:    inc  cx
                mov  ax,es:[si]
                inc  si
                or   ax,ax
                jnz  not_end_env

                add  cx,64      ;Add in extra space to be allocated.

                shr  cx,1
                shr  cx,1
                shr  cx,1
                shr  cx,1       ;Figure segment to use.

                xor  ax,ax
                mov  envseg,ax  ;ZAP environment segment for now.

                mov  ah,48h
                mov  bx,cx
                int  21h        ;Allocate space.  AX:0 points to block
                jc   envabort

                mov  envseg,ax

                mov  dx,es
                mov  ds,dx      ;DS:0 points to source.
                mov  es,ax      ;ES:0 points to destination.

                xor  si,si
                mov  di,si

copyloop:       mov  ax,[si]    ;Get a word.
                mov  es:[di],al ;Put one byte down.

                inc  si         ;Increment pointers.
                inc  di

                or   ax,ax      ;Is it final set of ZEROS?
                jnz  copyloop

copyend:        mov  si,DGROUP
                mov  ds,si      ;DS:SI points to our env setting.
                lea  si,exspace
                mov  cx,26
                rep  movsb      ;Copy the dummy into place.

envabort:       pop  es
                pop  ds
                ret

copy_env endp

;--------------------------------------------------------------------------

free_env proc
                mov  es,envseg
                mov  ah,49h
                int  21h
                ret
free_env endp

;--------------------------------------------------------------------------

INT15:          cmp  ah,88h
                jz   get_e_sz

                cmp  ax,0
                jnz  i15x
                cmp  bx,0ffffh
                jnz  i15x
                cmp  cx,0ffffh
                jnz  i15x
                mov  ax,5342h
                iret

    i15x:       jmp  dword ptr cs:o15o

get_e_sz:       mov  ax,cs:esize
                iret

;--------------------------------------------------------------------------

o21f19o         dw   0
o21f19s         dw   0
cur_drive       db   0

;---------------

_hook19:   ;    push es
           ;    push ds                      ;REMOVED IN VERSION 1.10.
           ;
           ;    mov  ah,19h
           ;    int  21h
           ;    mov  cs:cur_drive,al
           ;
           ;    mov  ax,3521h
           ;    int  21h
           ;    mov  cs:o21f19o,bx
           ;    mov  cs:o21f19s,es
           ;
           ;    mov  ax,cs
           ;    mov  ds,ax
           ;    mov  dx,offset i21f19
           ;    mov  ax,2521h
           ;    int  21h
           ;
           ;    pop  ds
           ;    pop  es
                ret

;---------------

_unhook19: ;    push ds
           ;    push es
           ;
           ;    mov  ax,2521h
           ;    mov  ds,cs:o21f19s
           ;    mov  dx,cs:o21f19o
           ;    int  21h
           ;
           ;    pop  es
           ;    pop  ds
                ret


;--------------------------------------------------------------------------
; This function returns the Error Level from
; executed shell program, to the parent program.
;--------------------------------------------------------------------------
get_elevel proc
                mov  ax,cs:errorlevel
                iret
get_elevel endp

;---------------
;
;i21f19:         cmp  ah,19h
;                jnz  i21xa
;                mov  al,cs:cur_drive
;                iret
;
;  i21xa:        cmp  ah,0eh
;                jnz  i21xb
;                mov  cs:cur_drive,dl
;
;  i21xb:        jmp  dword ptr cs:o21f19o
;
;--------------------------------------------------------------------------

i21x:    jmp  dword ptr cs:o21o

;--------

INT21:   cmp  ah,4dh            ;Retreive error level?
         jz   get_elevel        ;Yes? Get error level and return it.

         cmp  ah,4bh            ;Call to exec?
         jz   i21nx             ;Yes, then jump to continue.

         cmp  ah,48h            ;Call to malloc?
         jnz  i21x              ;No? Then jump out.
         cmp  bx,10h            ;Is it malloc of 256 bytes?
         jnz  i21x              ;No? Then jump out.

         cmp  cs:psp256,0       ;Is the memory still ours?
         jz   i21x              ;No? Then jump out.

         mov  ax,cs:psp256      ;Give it to Phar-Lap.
         mov  cs:psp256,0       ;Offically.
         sti

         PUSH BP                     ;Get previous flags off of stack.
         PUSH AX
         MOV  BP,SP
         MOV  AX,[BP+8]
         PUSH AX
         POPF                        ;Put them in place IN FLAGS.
         POP  AX
         POP  BP
         CLC

         retf 2

;--------

  i21nx: cmp  cs:tripskip,1     ;Skip this trip?
         jnz  i21go             ;Yes? Then Jump.
         jmp  i21x

  i21go: mov  cs:tripskip,1     ;Set semiphore.

         cli
         mov  cs:ts_ss,ss
         mov  cs:ts_sp,sp
         mov  sp,cs
         mov  ss,sp
         mov  sp,offset I_STACK
         sti

         push ax
         push bx
         push cx
         push dx
         push si
         push di
         push bp
         push ds
         push es

 ;;;;;;  call find_irq0

         cld

         push ds
         push es
         mov  si,DGROUP
         mov  es,si
         lea  di,_program       ;ES:DI point to buffer to hold program name.
         mov  si,dx             ;DS:SI point to program name to run.
         mov  cx,80
         rep  movsb             ;Copy name of program to run.
         pop  es
         pop  ds

         mov  si,es
         mov  ds,si
         mov  si,bx             ;DS:SI points to passed parm block.

         mov  cx,DGROUP
         mov  es,cx
         lea  di,envseg         ;ES:DI points to our parm block area.

         movsw                  ;Copy env seg, cmd ofs, cmd seg.
         movsw
         movsw

         mov  ds,cx             ;DS=ES=DGROUP

         call _exec

         pop  es
         pop  ds
         pop  bp
         pop  di
         pop  si
         pop  dx
         pop  cx
         pop  bx
         pop  ax

         cli
         mov  sp,cs:ts_ss
         mov  ss,sp
         mov  sp,cs:ts_sp
         sti

         cmp  cs:retry,1        ;If original attempt failed, try normal.
         jnz  i21done

         mov  cs:tripskip,0
         jmp  dword ptr cs:o21o ;Jump to DOS.

i21done: mov  cs:tripskip,0

         PUSH BP                ;Get previous flags off of stack.
         PUSH AX
         MOV  BP,SP
         MOV  AX,[BP+8]
         PUSH AX
         POPF                   ;Put them in place IN FLAGS.
         POP  AX
         POP  BP

         clc                    ;Return OK to AutoCAD.
         retf 2

;;;;;;;  iret                   ;Fixed in Big-Shell 2.0.

;----------------------------------------------------------------------

INT24:   mov  al,0                       ;IGNORE ERROR.
INT23:   iret

;----------------------------------------------------------------------

_shell proc

         push bp
         mov  bp,sp

         push bx
         push cx
         push dx
         push es
         push ds
         push si
         push di

         mov  bs_ds,ds          ;Save "C" Data  segment.
         mov  bs_es,es          ;Save "C" Extra segment.

         mov  ostacko,sp        ;Store the current stack.
         mov  ostacks,ss

         mov  ah,51h            ;Get psp to bx
         call dos               ;Get it.

         mov  cmdseg,bx
         mov  fcb1seg,bx
         mov  fcb2seg,bx        ;Store segments.

         push ds
         mov  ds,bx
         mov  bx,ds:[2ch]       ;Get environment segment.
         pop  ds

         mov  envseg,bx         ;Store environment segment.

         lea  dx,_runname       ;DS:DX point to run name.
         lea  bx,envseg         ;Get pointer to parameter block
         mov  ax,DGROUP
         mov  es,ax             ;ES:BX point to parameter block.

         mov  ax,4b00h
         pushf
         cli

         call dword ptr cs:o21o ;Call dos via a fake call.

         mov  ax,DGROUP
         mov  ds,ax

         jnc  noerror           ;If it returned CY as shell result:
         mov  ax,0ffffh

noerror: cli                    ;Restore stack with interrupts off.
         mov  sp,ostacks
         mov  ss,sp
         mov  sp,ostacko
         sti

         pop  di
         pop  si
         pop  ds
         pop  es
         pop  dx
         pop  cx
         pop  bx
         pop  bp
         ret

_shell endp

;--------------------------------------------------------------------------

_acadshell proc

         push bp
         mov  bp,sp

         push bx
         push cx
         push dx
         push es
         push ds
         push si
         push di

         db   0fh,0a0h ;PUSH FS
         db   0fh,0a8h ;PUSH GS

         mov  ax,ds
         mov  es,ax

         mov  aostacko,sp       ;Store the current stack.
         mov  aostacks,ss

         mov  ah,51h            ;Get psp to bx
         call dos               ;Get it.

         mov  fcb1seg,bx
         mov  fcb2seg,bx        ;Store segments.

         call copy_cmd          ;Copy command line.

         lea  bx,_cmdline       ;Store pointer to "saved" command line.
         mov  cmdoff,bx
         mov  cmdseg,ds

         cmp  envseg,0          ;Is there a valid env segment? (cadkey mod)
         jz   no_env

         call copy_env          ;Allocate space and copy environment into place.

 no_env: lea  dx,_program       ;DS:DX point to autocad shelled program name.
         lea  bx,envseg         ;Get pointer to parameter block

         mov  ax,4b00h
         pushf
         cli
         call dword ptr cs:o21o ;Call dos via a fake call

         mov  ax,DGROUP
         mov  ds,ax
         mov  es,ax

         mov  ah,4dh            ;Get the error level that program returned.
         pushf
         cli
         call dword ptr cs:o21o
         mov  cs:errorlevel,ax  ;Store it locally.

         cli                    ;Restore stack with interrupts off.
         mov  sp,aostacks
         mov  ss,sp
         mov  sp,aostacko
         sti

         cmp  envseg,0          ;Is there a valid env segment? (cadkey mod)
         jz   no_denv
         call free_env          ;Free allocated environment space.
no_denv:

         db   0fh,0a9h ;POP  GS
         db   0fh,0a1h ;POP  FS

         pop  di
         pop  si
         pop  ds
         pop  es
         pop  dx
         pop  cx
         pop  bx
         pop  bp
         ret

_acadshell   endp

;--------------------------------------------------------------------------
_install23 proc

         pushf
         push es
         cli

         xor  ax,ax
         mov  es,ax
         mov  di,8ch
         mov  ax,offset INT23
         mov  es:[di],ax        ;Store offset of NEW INT 23 handler.
         mov  ax,cs
         mov  es:[di+2],ax      ;Store segment of NEW INT 23 handler.

         pop  es
         popf
         ret

_install23 endp

;--------------------------------------------------------------------------
_install24 proc

         pushf
         push es
         cli

         xor  ax,ax
         mov  es,ax
         mov  di,90h
         mov  ax,offset INT24
         mov  es:[di],ax        ;Store offset of NEW INT 24 handler.
         mov  ax,cs
         mov  es:[di+2],ax      ;Store segment of NEW INT 24 handler.

         pop  es
         popf
         ret

_install24 endp

;--------------------------------------------------------------------------
; This routine saves vectors.
;--------------------------------------------------------------------------
_storevects proc

                push ds
                push es
                push si
                push di

                xor  ax,ax
                mov  ds,ax
                mov  si,ax                      ;ES:DI ->vector table.

                cld
                mov  ax,cs
                mov  es,ax
                mov  di,offset _vector_table    ;DS:SI ->0:0
                mov  cx,512                     ;512 words to swap.
                rep  movsw

                pop  di
                pop  si
                pop  es
                pop  ds
                ret

_storevects endp

;-------------------------------------------------------------------------
; This procedure:
;
; 1: Saves the SEG address for the Memory Control Block that holds our PSP.
; 2: Saves the SEG address of the NEXT MCB after us.
;-------------------------------------------------------------------------
_saveblocks proc

         push ds
         push es

         mov  ah,51h            ;Get PSP.
         int  21h
         dec  bx                ;Get address of block before PSP.
         mov  adr_b4us,bx       ;Store address

         push ds
         pop  es
         mov  ds,bx

         xor  si,si             ;ES:DI point to storage.
         lea  di,blk_b4us       ;DS:SI point to block.
         mov  cx,16             ;Store 16 bytes
         cld
         rep  movsb

         add  bx,ds:[0003]      ;Add in memory used by our block.
         inc  bx                ;Add in size of block.
         mov  ds,bx
         xor  si,si             ;DS:SI points to block after us.

         lea  di,_adr_afus
         mov  es:[di],bx        ;Store segment address of block after us.
         lea  di,blk_afus       ;ES:DI points to storage.
         mov  cx,16
         rep  movsb

         pop  es
         pop  ds
         ret

_saveblocks endp

;--------------------------------------------------------------------------
;
;_fill    proc
;
;         xor  ax,ax
;         push ax
;
;         mov  bx,0ffffh         ;Request max block size.
;
;fretry:  cmp  bx,0
;         jz   fillx
;
;         mov  ah,48h            ;Allocate memory.
;         int  21h               ;Call DOS.  BX holds max block size.
;         jc   fretry
;
;         push ax                ;Push block seg address onto stack.
;         jmp  fretry
;
;fillx:   mov  ah,62h
;         int  21h               ;Get PSP
;         mov  cx,bx             ;CX holds PSP segment.
;
;daloop:  pop  ax
;
;         or   ax,ax             ;Was it 0000?
;         jz   fx2               ;Yes? Then exit.
;
;         cmp  ax,cx             ;Is it above PSP?
;         jc   daloop            ;No? Jump up again.
;
;         push es
;         mov  es,ax
;         mov  ah,49h            ;Deallocate block.
;         int  21h
;         pop  es
;         jmp  daloop
;
;
;fx2:     ret
;
;
;_fill    endp
;
;
;

;--------------------------------------------------------------------------

_detect   proc

          mov  ah,62h
          int  21h
          dec  bx
          mov  es,bx
          inc  bx
          add  bx,es:[3]
          mov  es,bx

          mov  al,es:[0]
          xor  ah,ah

          ret

_detect   endp

;--------------------------------------------------------------------------
;--------------------------------------------------------------------------
_start proc
          mov  ax,DGROUP
          mov  ds,ax
          mov  es,ax
          mov  ss,ax

          lea  sp,endstack
          call _main
          mov ah,4ch
          int 21h
          ret
_start endp
end _start