BREAK MACRO
INT 2
%OUT HARD BREAK INSERTED
ENDM

PAGE 66,132

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


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

vid segment
assume cs:vid,ds:vid,es:vid,ss:vid

;Initial Defaults

MONOCHROME = 7

ULX = 0
LRX = 79
ULY = 0
LRY = 24

;SCN_BACKGND = 1    ;Screen Background color.
;SCN_FOREGND = 7    ;Screen Foreground color.
;HDR_BACKGND = 7    ;Header Background color.
;HDR_FOREGND = 4    ;Header Foreground color.

SCN_BACKGND = 0    ;Screen Background color.
SCN_FOREGND = 7    ;Screen Foreground color.
HDR_BACKGND = 7    ;Header Background color.
HDR_FOREGND = 0    ;Header Foreground color.


org 100h

start:          jmp  install

cldata:
cl_count        db   3
cl_hdr          db   "/C "
cl_command:     db   80 dup (0)

cl_cmd_src:     db   "MAINMENU.BAT",0DH

ulx_spot        db   ULX                ;Upper left X location of main screen.
uly_spot        db   ULY                ;Upper left Y locatoin of main screen.
lrx_spot        db   LRX                ;Lower right X spot.
lry_spot        db   LRY                ;Lower right Y spot.
scn_back        db   SCN_BACKGND        ;Main   screen background.
scn_fore        db   SCN_FOREGND        ;Main   screen foreground.
hdr_back        db   HDR_BACKGND        ;Header/footer screen background.
hdr_fore        db   HDR_FOREGND        ;Header/footer screen foreground.
vid_page        db   0                  ;Default video page.
ext_enable      db   1                  ;0 or 1 for extensions enabled.
io_supress      db   0                  ;0 or 1 for crt io suppression.

script          db   0
scriptseg       dw   0
scripthandle    dw   0
vid_mode        db   0

f10keymsg:      db   "Main Menu",0
f10sig:         db   "Enter selection: ",0

f2watchbuf:     db   80 dup (0)
f2w_ptr         dw   0

o10o            dw   0
o10s            dw   0
o21o            dw   0
o21s            dw   0

copystored      db   0                  ;1=Copyright stored. 0=Not.

copyline0:      db   8, 4,17h,80 dup (0)
copyline1:      db   8, 5,17h,80 dup (0)
copyline2:      db   8, 6,17h,80 dup (0)
copyline3:      db   8, 7,17h,80 dup (0)
copyline4:      db   8, 8,17h,80 dup (0)
copyline5:      db   8, 9,17h,80 dup (0)

release11       db    0                 ;0=R9,10  1=R11
autopersonal    db    0                 ;0=AutoEDMS, 1=PersonalEDMS

highoption      dw    0

leftright       db    10,10,11,12,12,12,13,13,13,13,0,2,5,8 ;L to R Xlation.



highdata:       db    6, 6,30           ;ACAD Option 0.
                db    6, 8,30           ;ACAD Option 1.
hd2:            db    6,10,30           ;ACAD Option 2.
                db    6,12,30           ;ACAD Option 3.
                db    6,13,30           ;ACAD Option 4.
                db    6,15,30           ;ACAD Option 5.
                db    6,16,30           ;ACAD Option 6.
                db    6,18,30           ;ACAD Option 7.
                db    6,20,30           ;ACAD Option 8.
                db    6,21,30  ; <------ ACAD Option 9.
                db   41,6 ,33           ;ACS  Option 10.
                db   41,10,33           ;ACS  Option 11.
                db   41,14,33           ;ACS  Option 12.
                db   41,20,33           ;ACS  Option 13.
                db    0

                ;    int&cls / ext&leave
                ;     0 / 1

op_chars:       db    0
                db    0
                db    0
                db    0
                db    0
                db    0
                db    0
                db    0
                db    0
                db    0
                db    1
                db    1
                db    1
                db    1


oldpsp          dw   0                  ;Storage for previous PSP.
stuff_buff:     db   80  dup (0)        ;Keyboard stuff buffer.
cmdname:        db   128 dup (0)        ;Command processor name.

parmblock:
environ         dw   0
commandline     dw   offset cldata
thisseg1        dw   ?
                dw   offset fcb1
thisseg2        dw   ?
                dw   offset fcb2
thisseg3        dw   ?
fcb1:           db   0,"            ",0,0,0,0
fcb2:           db   0,"            ",0,0,0,0


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

commandcom:        call commonsegs

                   mov  ax,ds
                   mov  thisseg1,ax
                   mov  thisseg2,ax
                   mov  thisseg3,ax

                   mov  cx,0000h
                   mov  dx,184fh           ;Clear the screen BLUE.
                   mov  bh,7
                   mov  ax,600h
                   call vid_bios

                   mov  ah,2
                   mov  dx,0
                   mov  bh,vid_page
                   call vid_bios

                   mov  saved_sp,sp
                   mov  saved_ss,ss

mov  ax,5100h
call dos
mov  oldpsp,bx

mov  ax,5000h
mov  bx,cs
call dos

                   mov  bx,offset parmblock    ;Point to parms to send.
                   mov  dx,offset cmdname      ;Point to name.
                   mov  ax,4b00h               ;EXEC - RUN.

                   call dos                    ;Call Dos.
                   cli
                   mov  sp,cs:saved_ss         ;Restore Registers.
                   mov  ss,sp
                   mov  sp,cs:saved_sp
                   sti

                   call commonsegs
                   pushf

push ax
push bx
mov  ax,5000h
mov  bx,cs:oldpsp
call dos
pop  bx
pop  ax

                   call scr_menu
                   popf

                   jc   exec_failure
                   ret

exec_failure:      push ax
                   mov  ah,9
                   mov  dx,offset exec_msg
                   call dos
                   pop  ax
                   ret

exec_msg:          db   "$"

saved_sp           dw   0
saved_ss           dw   0

;------------------------------------------------------------------------
scoot_buff:     push si
                push di
                push cx
                pushf
                push ds
                push es
                mov  si,cs
                mov  ds,si
                mov  es,si
                mov  si,offset stuff_buff + 1
                mov  di,offset stuff_buff
                mov  cx,80
                rep  movsb
                pop  es
                pop  ds
                popf
                pop  cx
                pop  di
                pop  si
                ret

;------------------------------------------------------------------------
highlight:      mov  dl,[si]
                mov  dh,[si+1]
                mov  cl,[si+2]
                xor  ch,ch

      nxthigh:  push cx
                push dx
                push si

                mov  ah,2
                mov  bh,vid_page        ;Move cursor.
                call vid_bios

                mov  ah,8
                mov  bh,vid_page        ;Get character.
                call vid_bios

                cmp  ah,70h
                jnz  not70

                mov  bl,1fh
                jmp  was70

     not70:     mov  bl,70h
     was70:     mov  ah,9
                mov  bh,vid_page
                push cx
                mov  cx,1
                call vid_bios
                pop  cx

                pop  si
                pop  dx
                pop  cx
                inc  si
                inc  dx
                loop nxthigh
                ret

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

run_menu:       mov  si,offset hd2
                mov  highoption,2
                call highlight

                cmp  script,0           ;Is script running?
                jnz  menu_int           ;Dump out of menu.

    keyloop:    mov  ah,0
                int  16h                ;Keyboard IO.

      rmgo:     push ax
                mov  si,offset highdata
                add  si,highoption
                add  si,highoption
                add  si,highoption
                call highlight
                pop  ax

                cmp  ax,5000h           ;Down Arrow?
                jz   dnarrow

                cmp  ax,4800h           ;Up Arrow?
                jz   uparrow

                cmp  ax,4b00h           ;Left Arrow?
                jz   lrarrow

                cmp  ax,4d00h           ;Right Arrow?
                jz   lrarrow

                cmp  al,0dh             ;Return?
                jz   menuf2

                cmp  al,"0"
                jz   qmenu
                cmp  al,"1"
                jz   qmenu
                cmp  al,"2"
                jz   qmenu
                cmp  al,"3"
                jz   qmenu
                cmp  al,"4"
                jz   qmenu
                cmp  al,"5"
                jz   qmenu
                cmp  al,"6"
                jz   qmenu
                cmp  al,"7"
                jz   qmenu
                cmp  al,"8"
                jz   qmenu
                cmp  al,"9"             ;Release 11 info
                jz   qmenu

                jmp  goodmenu

    qmenu:      sub  al,'0'
                xor  ah,ah
                mov  highoption,ax
                jmp  goodmenu

    dnarrow:    inc  highoption

                cmp  release11,0
                jnz  nof9
                cmp  highoption,9       ;KNOCK OUT OPTION 9 in RELEASE 11.
                jz   dnarrow
         nof9:
                cmp  highoption,14
                jc   goodmenu
                mov  highoption,0
                jmp  goodmenu

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

    uparrow:    dec  highoption

                cmp  release11,0
                jnz  nof9d
                cmp  highoption,9       ;KNOCK OUT OPTION 9 in RELEASE 11.
                jz   uparrow
         nof9d:

                cmp  highoption,14
                jc   goodmenu
                mov  highoption,13
                jmp  goodmenu

;---------------
   lrarrow:     mov  si,highoption
                add  si,offset leftright
                mov  al,[si]            ;Get left right translation.
                xor  ah,ah
                mov  highoption,ax
                jmp  goodmenu

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

    goodmenu:   mov  si,offset highdata
                add  si,highoption
                add  si,highoption
                add  si,highoption
                call highlight
                jmp  keyloop

    menuf2:     mov  si,offset op_chars
                add  si,highoption
                cmp  byte ptr [si],0
                jz   menu_int
                jmp  menu_ext

    menu_int:   mov  io_supress,0

                mov  cx,0
                mov  dx,184fh           ;Clear the screen.
                mov  ax,600h
                mov  bh,17h
                call vid_bios

                mov  si,offset acfnct
                call spec_print

                cmp  script,0
                jz   ns_go
                mov  script,0           ;Zap indicator.
               ;jmp  menu_exit
                ret

    ns_go:      cld
                mov  ax,highoption
                add  al,"0"
                mov  di,offset stuff_buff
                stosb
                mov  ax,0dh
                stosw
                jmp  menu_exit

    menu_ext:   mov  ax,500h
                mov  ch,0
                mov  cx,highoption      ;Stuff the option number into keyboard.
                int  16h

                call commandcom         ;Do the shell Here.

                jmp  goodmenu

    menu_exit:  ret


acfnct:         db   0,5,17h,"AutoCAD Function: ",0


;------------------------------------------------------------------------
store_print:    cmp  copystored,1
                jz   sp2

                mov  copystored,1

                mov  di,offset copyline0 + 3
                mov  dx,0000h
                mov  cx,60
                call storeline

                mov  di,offset copyline1 + 3
                mov  dx,0100h
                mov  cx,60
                call storeline

                mov  di,offset copyline2 + 3
                mov  dx,0200h
                mov  cx,60
                call storeline

                mov  di,offset copyline3 + 3
                mov  dx,0300h
                mov  cx,60
                call storeline

                mov  di,offset copyline4 + 3
                mov  dx,0400h
                mov  cx,60
                call storeline

                mov  di,offset copyline5 + 3
                mov  dx,0500h
                mov  cx,60
                call storeline

  sp2:          ret

putprint:       mov  si,offset copyline0
                call spec_print
                mov  si,offset copyline1
                call spec_print
                mov  si,offset copyline2
                call spec_print
                mov  si,offset copyline3
                call spec_print
                mov  si,offset copyline4
                call spec_print
                mov  si,offset copyline5
                call spec_print
                ret

;------------------------------------------------------------------------
storeline:
                push cx
                push dx
                push di

                mov  ah,2
                mov  bh,vid_page        ;Move cursor.
                call vid_bios

                mov  ah,8
                mov  bh,vid_page        ;Get character.
                call vid_bios

                pop  di                 ;Store in buffer.
                mov  [di],al

                pop  dx
                pop  cx
                inc  di
                inc  dx
                loop storeline
                ret

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

acs_int10:      cmp  cs:ext_enable,0    ;1 if extensions are enabled.
                jz   acs_int10x         ;Jump out if not enabled.

                cmp  ax,0600h           ;Clear screen?
                jnz  acsi10f2

                cmp  ch,dh              ;Ansi Clear EOL?
                jz   acs_int10x         ;Jump out if looks like an EOL.

                mov  cs:io_supress,0    ;Turn suppression off.
                jmp  cls

   acsi10f2:    cmp  cs:io_supress,0    ;1 if supress.
                jz   activeio
                iret

   activeio:    cmp  ah,02h             ;Move cursor?
                jnz  acsi10f9
                jmp  move

   acsi10f9:    cmp  ah,09h             ;Write char and attribute?
                jnz  acsi10fe
                jmp  writeca 

   acsi10fe:    cmp  ah,0eh             ;Teletype emulation?
                jnz  acsi10fx
                jmp  teletype

   acsi10fx:

acs_int10x:     jmp  dword ptr cs:o10o

;------------------------------------------------------------------------
writeca:        push cx
                mov  bl,cs:scn_back
                mov  cl,4
                shl  bl,cl
                or   bl,cs:scn_fore
                pop  cx
                jmp  acs_int10x

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

cls:            ;Clear lines 1 - 25 special.

                push ds                 ;Save segment registers.
                push es
                cld                     ;direction forward.

                call commonsegs


                mov  ax,600h            ;Clear black screen.
                mov  bh,7h
                mov  cx,0
                mov  dx,194fh
                call vid_bios

                ;------ Clear mid screen ------

                mov  ax,0600h           ;Clear screen.
                mov  bh,scn_back        ;Get text foreground.
                mov  cl,4
                shl  bh,cl
                or   bh,scn_fore

                mov  dh,lry_spot        ;Lower Right Y
                mov  ch,uly_spot        ;Upper Left  Y
                mov  cl,ulx_spot        ;Upper Left  X
                mov  dl,lrx_spot        ;Lower Right X
                call vid_bios           ;Do the call.

                mov  ah,2
                mov  cx,0
                mov  bh,vid_page
                call vid_bios

                pop  es
                pop  ds

                iret                    ;Return to caller.

;------------------------------------------------------------------------
;------------------------------------------------------------------------
move:           cmp  dh,0
                jnz  notop
                mov  dh,cs:uly_spot

notop:          cmp  dl,0
                jnz  noleft
                mov  dl,cs:ulx_spot

noleft:         cmp  dh,cs:lry_spot
                jle  nobottom
                call scrlup

nobottom:       cmp  dl,cs:lrx_spot
                jle  movex

                mov  dh,cs:lry_spot
                inc  dh
                mov  dl,cs:ulx_spot
                call scrlup

movex:          jmp  acs_int10x

;------------------------------------------------------------------------
;------------------------------------------------------------------------
teletype:       push ax
                push bx
                push cx
                push dx

                cmp  al,0dh             ;Is it a carriage return?
                jz   t_cr               ;Yes? Then Jump.

                cmp  al,0ah             ;Is it a line feed?
                jz   t_lf               ;Yes? Then Jump.

                cmp  al,7               ;Is it a bell?
                jz   t_bl               ;Yes? Then Jump to bell.

                cmp  al,8               ;Is it a back space?
                jz   t_bs               ;Yes? Then Jump to back space.

                mov  ah,9               ;Write character and attribute.
                mov  bh,cs:vid_page     ;Get video page.
                mov  bl,cs:scn_back     ;Get screen background.
                mov  cl,4
                shl  bl,cl
                or   bl,cs:scn_fore
                mov  cx,1               ;Repeat count is ONE.
                call vid_bios           ;Call video bios.
                call inc_cursor         ;Increment cursor position.

ttxit:          pop  dx
                pop  cx
                pop  bx
                pop  ax

                iret                    ;Return to caller.

;---------------
;Handle carriage return.
;---------------
t_cr:           mov  ah,3
                mov  bh,cs:vid_page
                call vid_bios

                mov  dl,cs:ulx_spot     ;CR returns cursor to ULX,curnty.
                mov  ah,2
                call vid_bios
                jmp  ttxit

;---------------
;Handle line feed.
;---------------

t_lf:           mov  ah,3
                mov  bh,cs:vid_page      ;Get cursor location on current page.
                call vid_bios
                inc  dh

                cmp  dh,cs:lry_spot      ;Did we just move cursor out of area?
                jle  t_cont

                call scrlup              ;Scroll screen area up by one.
                jmp  ttxit

t_cont:         mov  ah,2                ;Set cursor postion.
                mov  bh,cs:vid_page      ;Get video page.
                call vid_bios            ;Call video bios.
                jmp  ttxit

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

t_bs:           ;Handle back space.
t_bl:           ;Handle bell character.

                pop  dx
                pop  cx
                pop  bx
                pop  ax
                jmp  acs_int10x

;------------------------------------------------------------------------
;------------------------------------------------------------------------
inc_cursor:     mov  ah,3               ;Get cursor position.
                mov  bh,cs:vid_page
                call vid_bios           ;Call bios to get it, like now already.

                inc  dl                 ;Increment Relative X position.
                cmp  dl,cs:lrx_spot     ;Check Relative X for bounds.
                jle  incexit            ;If X is out of range, do a CRLF.

crlf:           mov  dl,cs:ulx_spot     ;Move cursor to left.
                inc  dh                 ;Move cursor down one.
                cmp  dh,cs:lry_spot     ;Past bottom?
                jle  incexit            ;No? Do Normal.

scrlup:         push dx
                push cx
                push ax
                mov  ah,6               ;Scroll up.
                mov  bh,cs:scn_back     ;And the attribute is.....
                mov  cl,4
                shl  bh,cl
                or   bh,cs:scn_fore
                mov  cl,cs:ulx_spot     ;X scroll starting location.
                mov  ch,cs:uly_spot     ;Y scroll starting location.
                mov  dl,cs:lrx_spot     ;X scroll ending location.
                mov  dh,cs:lry_spot     ;Y scroll ending location.
                mov  al,1               ;Scroll up one line.
                call vid_bios
                pop  ax
                pop  cx
                pop  dx
                dec  dh                 ;Left on Last Line.

incexit:        mov  bh,cs:vid_page     ;Get video page again.
                mov  ah,2               ;Set cursor location.
                call vid_bios           ;DO IT...
                ret

;------------------------------------------------------------------------
vid_bios:       cmp  cs:vid_mode,MONOCHROME
                jnz  ctxx

                cmp  ah,9
                jz   txf09
                cmp  ah,6
                jz   txf06
                jmp  ctxx

;-------------- Translate Function 06

txf06:          cmp  bh,70h             ;MONO Color Translation.
                jc   ctx1
                mov  bh,70h             ;INVERSE is Black on White.
                jmp  ctxx
ctx1:           mov  bh,7               ;NON-INVERSE is White on Black.
                jmp  ctxx

;-------------- Translate Function 09

txf09:          cmp  bl,70h             ;MONO Color Translation.
                jc   ctx2
                mov  bl,70h             ;INVERSE is Black on White.
                jmp  ctxx
ctx2:           mov  bl,7               ;NON-INVERSE is White on Black.

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

ctxx:           pushf                   ;Do a simulated INT 10 call.
                cli
                call dword ptr cs:o10o
                ret


;------------------------------------------------------------------------
commonsegs:     push ax
                mov  ax,cs
                mov  ds,ax
                mov  es,ax
                pop  ax
                ret

;------------------------------------------------------------------------
acs_int21:      cmp  ah,2               ;Is it function 2?
                jz   acs_i21f2

                cmp  ah,9               ;Is it function 9?
                jz   acs_i21f9

                cmp  ah,6
                jz   acs_i21f6          ;Is it function 6?

                cmp  ah,0fh             ;Open FCB? (script R10 maybe?)
                jz   acs_i21f0f         

                cmp  ah,10h
                jz   acs_i21f10         ;Close file FCB?

                cmp  ah,3dh             ;Open file?  (script maybe?)
                jz   acs_i21f3d

                cmp  ah,3eh             ;Close file (script maybe?)
                jz   acs_i21f3e

                jmp  acs_i21x           ;No? Then Jump out.

   acs_i21f9:   push ds
                push es
                push si
                push di
                push ax
                push cx
                push dx

                push cs
                pop  es                 ;ES=CS
                call store_pline
                push cs                 ;DS=CS
                pop  ds

                call p10test
                jnz  acsi21f9a          ;No? Then Jump.

                call zap_watch
                call scr_copy           ;Display copyright Screen.
                call _delay
                call _delay
                call _delay
                mov  io_supress,1       ;Suppress all ACAD CRT IO.
                call dispf10            ;Display ACS function 10.
                jmp  acsi21f9x          ;Get out.


   acsi21f9a:   call f10sigtest
                jnz  acsi21f9x
                call zap_watch
                call run_menu

   acsi21f9x:   call zap_watch
                pop  dx
                pop  cx
                pop  ax
                pop  di
                pop  si
                pop  es
                pop  ds
                jmp  acs_i21x

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

   acs_i21f2:   push ds
                push es
                push si
                push di
                push ax
                push cx
                push dx

                call commonsegs         ;Common segments. CS=DS=ES.
                call store_pchar        ;Store character to be printed.

                cmp  dl," "
                jz   acsstest

                cmp  dl,0dh             ;Was it a carriage return?
                jnz  acsi211            ;No? Jump over comparison.

    acsrunm:    call p10test            ;Call print f 10 test.
                call zap_watch          ;Returns ZR=Print NZ=Not.
                jnz  acsstest           ;Print it? FFFF=Jump.

                call scr_copy           ;Do copyright screen.
                call _delay
                call _delay
                call _delay

                mov  io_supress,1       ;Supress all acad crt io.
                call dispf10            ;Display ACS function 10.

   acsstest:    call f10sigtest         ;Test for menu signal.
                jnz  acsi211
                call zap_watch
                call run_menu           ;Perform ACS menu procedure.

   acsi211:     pop  dx
                pop  cx
                pop  ax
                pop  di
                pop  si
                pop  es
                pop  ds
                jmp  acs_i21x

;------------------------------------------------------------------------
acs_i21f6:      cmp  dl,0ffh            ;Read a character?
                jnz  acs_i21x           ;No? Then jump.

                cmp  byte ptr cs:stuff_buff,0   ;Any keys to get?
                jz   acs_i21x                   ;No? Then Jump.

                mov  al,byte ptr cs:stuff_buff
                call scoot_buff

                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

                or   al,al
                retf 2

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

acs_i21f0f:     push si
                mov  si,dx
                add  si,9               ;Point to extension in FCB open.
                jmp  cfn                ;Jump to common code.

;------------------------------------------------------------------------
; Close file FCB
;------------------------------------------------------------------------

acs_i21f10:     push si
                mov  si,dx
                add  si,9

          fcfn: cmp  byte ptr [si],"S"  ;Is it ".s"
                jz   ffzy               ;Yes? Jump over to next test.
                cmp  byte ptr [si],"s"  ;Is it ".s"
                jnz  ffzx               ;No? Jump out.

          ffzy: inc  si

                cmp  [si],"RC"          ;Yes? Jump over.
                jz   ffzz
                cmp  [si],"rc"          ;No? Jump out.
                jnz  ffzx

          ffzz: mov  cs:script,0        ;Mark script file closed.
                mov  cs:scripthandle,0  ;Clear any handle.
                mov  cs:scriptseg,0     ;Clear any psp.

          ffzx: pop  si
                jmp  acs_i21x

;------------------------------------------------------------------------
; Open file function.
;------------------------------------------------------------------------
acs_i21f3d:     push si                 ;Open file...
                mov  si,dx

   ofz:         inc  si
                cmp  byte ptr [si],0    ;Find string terminator.
                jnz  ofz
                sub  si,3               ;Look at beginning of extension.

           cfn: cmp  byte ptr [si],"S"  ;Is it ".s"
                jz   fzy                ;Yes? Jump over to next test.
                cmp  byte ptr [si],"s"  ;Is it ".s"
                jnz  fzx                ;No? Jump out.

           fzy: inc  si

                cmp  [si],"RC"          ;Yes? Jump over.
                jz   fzz
                cmp  [si],"rc"          ;No? Jump out.
                jnz  fzx
           fzz: mov  cs:script,1        ;Mark script file opened.

                push ax
                push bx
                mov  ah,51h
                call dos
                mov  cs:scriptseg,bx    ;Save script segment.
                pop  bx
                pop  ax

                pop  si

                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

                pushf
                cli
                call dword ptr cs:o21o  ;Call DOS.
                jc   nssh               ;If CY, don't save handle.
                mov  cs:scripthandle,bx ;Save script handle.
         nssh:  retf 2

   fzx:         pop  si
                jmp  acs_i21x

;------------------------------------------------------------------------
; Close file function.
;------------------------------------------------------------------------
acs_i21f3e:     cmp  cs:script,1        ;Is script running?
                jnz  i21f3x             ;No? Jump to handle normal.

                cmp  cs:scripthandle,bx ;Is it script handle?
                jnz  i21f3x             ;No? Jump to handle normal.

                push ax
                push bx
                mov  ah,51h             ;Get current PSP.
                call dos
                cmp  cs:scriptseg,bx    ;Is it script PSP?
                pop  bx
                pop  ax
                jnz  i21f3x             ;No? Then Jump out.

                mov  cs:script,0        ;Yes? Clear script flag.
                mov  cs:scriptseg,0     ;Clear script segment.
                mov  cs:scripthandle,0  ;Clear script handle.

     i21f3x:    jmp  acs_i21x           ;Jump to call normal.


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

acs_i21x:       jmp  dword ptr cs:o21o

;------------------------------------------------------------------------
zap_watch:      pushf
                mov  di,offset f2watchbuf
                mov  al,0
                mov  cx,80
                cld
                rep  stosb
                mov  f2w_ptr,0                ;Zap pointer.
                popf
                ret

;------------------------------------------------------------------------
p10test:        mov  si,offset f10keymsg
                mov  di,offset f2watchbuf
                mov  cx,9
   cmn_srch:    cld
                repz cmpsb
                mov  ax,0
                jz   p10found
                mov  ax,0ffffh
p10found:       or   ax,ax
                ret

;------------------------------------------------------------------------
f10sigtest:     mov  si,offset f10sig
                mov  di,offset f2watchbuf
                mov  cx,17
                jmp  cmn_srch

;------------------------------------------------------------------------
dispf10:        push ax
                push bx
                push cx
                push dx
                push si
                push di
                call scr_menu
                pop  di
                pop  si
                pop  dx
                pop  cx
                pop  bx
                pop  ax
                ret

;------------------------------------------------------------------------
store_pchar:    cmp  f2w_ptr,80         ;Is buffer size exceeded?
                jnc  sp1                ;Yes? Then jump over data put.

                mov  di,offset f2watchbuf   ;Get offset of buffer.
                add  di,f2w_ptr         ;Add in index.
                mov  [di],dl            ;Store the character.
                inc  f2w_ptr            ;Increment the index.

    sp1:        cmp  dl,0ah
                jnz  sp2x

                mov  f2w_ptr,0              ;Zap pointer.
                mov  word ptr f2watchbuf,0  ;Zap some data.
    sp2x:       ret

;------------------------------------------------------------------------
store_pline:    mov  di,offset f2watchbuf
                mov  si,dx
                mov  cs:f2w_ptr,0       ;Zap the pointer.
                mov  cx,78              ;Maximum character transfer.

  sploop:       lodsb
                stosb
                inc  cs:f2w_ptr         ;Increment the pointer.
                cmp  al,"$"
                loopnz sploop
                ret

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

dos:            pushf
                cli
                call dword ptr cs:o21o  ;Call it.
                ret

;------------------------------------------------------------------------
acs_shell:      mov  dx,offset shellmsgx
                mov  ah,9
                call dos

                ret

     shellmsgx: db   0dh,0ah,0dh,0ah,"ACS SHELL HERE",7,7,"$"

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

scr_copy:       call store_print

                mov  ah,2               ;GOTOXY 0,0
                mov  bh,vid_page
                mov  dx,0000h
                call vid_bios

                mov  ah,9
                mov  al,178             ;Print character 178 ALL over screen.
                mov  cx,2000
                mov  bh,vid_page
                mov  bl,10h
                call vid_bios

                mov  cx,0306h
                mov  dx,1649h           ;Clear the Center screen BLUE.
                mov  bh,10h
                mov  ax,600h
                call vid_bios

                mov  si,offset copy_l1  ;Print "Copyright and Trademark Notices"
                call spec_print

                call sideprint          ;Clear sides

                mov  si,offset copy_l2
                call spec_print
                mov  si,offset copy_l3
                call spec_print
                mov  si,offset copy_l4
                call spec_print
                mov  si,offset copy_l5
                call spec_print
                mov  si,offset copy_l6
                call spec_print

                mov  si,offset copy_l7
                call spec_print
                mov  si,offset copy_l8
                call spec_print
                mov  si,offset copy_l9
                call spec_print
                mov  si,offset copy_l10
                call spec_print
                mov  si,offset copy_l11
                call spec_print

                call putprint           ;Display stored copyright.

                ret

copy_l1:        db    6, 2,70h,"                  Copyright and Trademark Notices                   ",0
copy_l2:        db    8,11,17h,"AutoEDMS,MultiMedia Mail,10View Copyright (C) 1990 ACS Telecom",0
copy_l3:        db    8,12,17h,"EDMS,SPS Copyright (C) 1988,89,89 ACS Telecom",0
copy_l4:        db    8,13,17h,"Artificial intelligence functions and portions of MultiMedia",0
copy_l5:        db    8,14,17h,"Mail Copyright (C) 1988,89,89 Peter Immarco",0
;copy_l6:        db    8,15,17h,"Portions of SPS and Shell, Copyright (C) 1989,90 Alfred Heyman",0
copy_l6:        db    8,15,17h,"SPS Engine, Queue, and 10Menu Copyright (C) 1989-92 Alfred Heyman",0

copy_l7:        db    8,17,17h,"AutoCAD, Autodesk and the Autodesk logo are U.S. registered",0
copy_l8:        db    8,18,17h,"trademarks of Autodesk, Inc.  Autodesk Animator, AutoSolid, AUI,",0
copy_l9:        db    8,19,17h,"ADI and DXF are additional trademarks of Autodesk, Inc.",0
copy_l10:       db    8,20,17h,"ACS Telecom, EDMS, SPS, AutoEDMS, MultiMedia Mail, 10View, 10CAD",0
copy_l11:       db    8,21,17h,"and related logos are trademarks of ACS Telecom",0

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

scr_menu:       mov  ah,2               ;GOTOXY 0,0
                mov  bh,vid_page
                mov  dx,0
                call vid_bios

                mov  ah,9
                mov  al,178             ;Print character 178 ALL over screen.
                mov  cx,2000
                mov  bh,vid_page
                mov  bl,10h
                call vid_bios

                mov  cx,0405h
                mov  dx,1524h           ;Clear the LEFT screen BLUE.
                mov  bh,10h
                mov  ax,600h
                call vid_bios

                mov  cx,0428h
                mov  dx,154ah           ;Clear the RIGHT screen BLUE.
                mov  bh,10h
                mov  ax,600h
                call vid_bios
                call sideprint          ;Clear sides.

                cmp  autopersonal,1
                jz   apx1
                mov  si,offset menu_l01a
                call spec_print
                jmp  apx1j
          apx1: mov  si,offset menu_l01b
                call spec_print
         apx1j:

                mov  si,offset menu_l02
                call spec_print

                cmp  autopersonal,1
                jz   apx4
                mov  si,offset menu_l03a
                call spec_print
                jmp  apx4j
        apx4:   mov  si,offset menu_l03b
                call spec_print
        apx4j:

                mov  si,offset menu_l04
                call spec_print
                mov  si,offset menu_l05
                call spec_print
                mov  si,offset menu_l06
                call spec_print
                mov  si,offset menu_l07
                call spec_print
                mov  si,offset menu_l08
                call spec_print
                mov  si,offset menu_l09
                call spec_print
                mov  si,offset menu_l10
                call spec_print
                mov  si,offset menu_l11
                call spec_print
                mov  si,offset menu_l12
                call spec_print

                cmp  release11,1
                jnz  noopt9
                mov  si,offset menu_l12a                ;display option 9.
                call spec_print
    noopt9:
                cmp  autopersonal,1
                jz   apx3
                mov  si,offset menu_l13a
                call spec_print
                jmp  apx3x
     apx3:      mov  si,offset menu_l13b
                call spec_print
     apx3x:
                mov  si,offset menu_l14
                call spec_print
                mov  si,offset menu_l15
                call spec_print
                mov  si,offset menu_l16
                call spec_print
                mov  si,offset menu_l17
                call spec_print
                mov  si,offset menu_l18
                call spec_print
                mov  si,offset menu_l19
                call spec_print

           ;;;  mov  si,offset menu_l20
           ;;;  call spec_print
           ;;;  mov  si,offset menu_l21
           ;;;  call spec_print
           ;;;  mov  si,offset menu_l22
           ;;;  call spec_print
           ;;;  mov  si,offset menu_l23
           ;;;  call spec_print

                cmp  autopersonal,1
                jz   apx2
                mov  si,offset menu_l24a
                call spec_print
                jmp  apx2x
        apx2:   mov  si,offset menu_l24b
                call spec_print
        apx2x:
                ret

menu_l01a:      db 23, 2,1fh,"     AutoCAD with AutoEDMS     ",0
menu_l01b:      db 20, 2,1fh,"     AutoCAD with Personal EDMS     ",0

menu_l02:       db  5, 4,70h," AutoCAD Menu                   ",0

menu_l03a:      db 40, 4,70h," AutoEDMS Menu                     ",0
menu_l03b:      db 40, 4,70h," Personal EDMS Menu                 ",0

menu_l04:       db  7, 6,1fh,"0.  Exit",0
menu_l05:       db  7, 8,1fh,"1.  Begin a NEW drawing",0
menu_l06:       db  7,10,1fh,"2.  Edit an EXISTING drawing",0
menu_l07:       db  7,12,1fh,"3.  Plot a drawing",0
menu_l08:       db  7,13,1fh,"4.  Printer Plot a drawing",0
menu_l09:       db  7,15,1fh,"5.  Configure AutoCAD",0
menu_l10:       db  7,16,1fh,"6.  File Utilities",0
menu_l11:       db  7,18,1fh,"7.  Compile shape/font file",0
menu_l12:       db  7,20,1fh,"8.  Convert old drawing file",0
menu_l12a:      db  7,21,1fh,"9.  Recover damaged drawing",0

menu_l13a:      db 42, 6,1fh,"10. AutoEDMS System",0
menu_l13b:      db 42, 6,1fh,"10. Personal EDMS System",0

menu_l14:       db 42, 7,17h,"    View, track and search for",0
menu_l15:       db 42, 8,17h,"    your AutoCAD drawing files",0
menu_l16:       db 42,10,1fh,"11. 10CAD Shared Plotter system",0
menu_l17:       db 42,11,17h,"    Send AutoCAD plot files to",0
menu_l18:       db 42,12,17h,"    shared plotters/printers",0
menu_l19:       db 42,14,1fh,"12. Miscellaneous",0

;menu_l20:      db 42,15,17h,"    Send/receive mail, with",0
;menu_l21:      db 42,16,17h,"    AutoCAD drawing images,",0
;menu_l22:      db 42,17,17h,"    documents, faxes, photos",0
;menu_l23:      db 42,18,17h,"    and voice messages",0

menu_l24a:      db 42,20,1fh,"13. Change Plotter Settings",0
menu_l24b:      db 42,20,1fh,"13. Change Plotter Settings",0

;menu_l24a:      db 42,20,1fh,"13. Extended AutoEDMS Options",0
;menu_l24b:      db 42,20,1fh,"13. Extended Personal EDMS Optns",0

menu_l25:       db  0, 0,9  ,"ß ",0
menu_l26:       db 78, 0,9  ," ß",0
menu_l27:       db  0,24,9  ,"Ü ",0
menu_l28:       db 78,24,9  ," Ü",0

spec_print:     mov  dl,[si]            ;Get column.
                mov  dh,[si+1]          ;Get row.
                mov  bl,[si+2]          ;Get color.
                add  si,3               ;Point at first character.

    ploop:      mov  al,[si]            ;Get character.
                or   al,al              ;Is it 0?
                jnz  pnow               ;No? Then continue - Jump.
                ret                     ;Return.

    pnow:       push si
                push dx
                push bx

                push ax
                push dx
                push bx
                mov  ah,2
                mov  bh,vid_page        ;Set cursor position.
                call vid_bios
                pop  bx
                pop  dx
                pop  ax

                mov  ah,9
                mov  bh,vid_page        ;Get video page.

                mov  cx,1
                call vid_bios           ;Print the character.

                pop  bx
                pop  dx
                pop  si
                inc  dl
                inc  si
                jmp  ploop


;-------------------------------------------------------------------------
sideprint:      mov  cx,1800h
                mov  dx,184fh           ;Clear the BOTTOM screen BLACK.
                mov  bh,10h
                mov  ax,600h
                call vid_bios

                mov  cx,0000h
                mov  dx,004fh           ;Clear the TOP screen BLACK.
                mov  bh,10h
                mov  ax,600h
                call vid_bios

                mov  cx,004eh
                mov  dx,184fh           ;Clear the LEFT screen BLACK.
                mov  bh,10h
                mov  ax,600h
                call vid_bios

                mov  cx,0000h
                mov  dx,1801h           ;Clear the RIGHT screen BLACK.
                mov  bh,10h
                mov  ax,600h
                call vid_bios

                mov  si,offset menu_l25
                call spec_print
                mov  si,offset menu_l26
                call spec_print
                mov  si,offset menu_l27
                call spec_print
                mov  si,offset menu_l28
                call spec_print

                ret

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

_delay proc
                   push ds
                   push di
                   pushf
                   sti
                   mov  cx,9

                   mov  di,0
                   mov  ds,di
                   mov  di,46ch               ;Offset of LSW of timer.

waitstart:         mov  ax,[di]               ;Get initial value.
waitspot:          mov  bx,[di]
                   cmp  ax,bx
                   jz   waitspot              ;Wait here until they are diff.
                   loop waitstart

                   popf
                   pop  di
                   pop  ds
                   ret

_delay endp

;

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

install:        mov  ah,0fh;
                int  10h
                mov  vid_mode,al        ;Save video mode.

                call get_comspec
                call cmdline            ;Process cmd line for /P and /9.

                call get_bat_name

                mov  ax,600h            ;Clear black screen.
                mov  bh,7h
                mov  cx,0
                mov  dx,194fh
                int  10h

                mov  ah,2               ;GOTOXY 0,0
                mov  cx,0
                mov  bx,0
                int  10h

                mov  ax,3510h           ;Get vector for INT 10.
                int  21h
                mov  o10o,bx
                mov  o10s,es 

                mov  ax,3521h           ;Get vector for INT 21.
                int  21h
                mov  o21o,bx
                mov  o21s,es

                mov  ax,2510h           ;Set our INT 10 handler in place.
                mov  dx,offset acs_int10
                int  21h

                mov  ax,2521h           ;Set our INT 21 handler in place.
                mov  dx,offset acs_int21
                int  21h

                pushf
                cli
                push cs
                call cls
;
;BETA MESSAGE
;
;mov  si,offset beta1
;call spec_print
;mov  si,offset beta2
;call spec_print
;mov  si,offset beta3
;call spec_print
;
                mov  dx,offset install ;Figure number of paragraphs.
                add  dx,15
                mov  cl,4
                shr  dx,cl

                mov  ax,31f0h
                int  21h

                mov  dx,offset install
                int  27h

;beta1: db 0,0,1fh,"10MENU Version 1.03 - Internal 12/11/90"
;beta2: db 0,1,1fh,"Not For Resale"
;beta3: db 0,2,1fh," ",0


;-----------------------------------------------------------------------
;-----------------------------------------------------------------------
cmdline:           mov  si,81h          ;Point at command line.
                   mov  cl,[si]         ;mov character count into CL.
                   and  cx,00ffh        ;Fix up CX for looping.
                   jz   clxit           ;Jump out if no switches.

        cmdloop:   mov  ax,[si]         ;Get command line letters.
                   cmp  ax,"9/"         ;turn on option 9?
                   jnz  nonine
                   mov  release11,1     ;Set release 11 option 9 to ON.

        nonine:    cmp  ax,"P/"         ;Turn on "Personal EDMS"?
                   jz   predms          ;Yes? Then Jump out and turn on.
                   cmp  ax,"p/"
                   jz   predms
                   inc  si
                   loop cmdloop
                   jmp  clxit

        predms:    mov  autopersonal,1

clxit:             ret

;-----------------------------------------------------------------------
; This routine searches the environment for "COMSPEC",0dh,0ah,"="
; and ABORTS the run if found.
;-----------------------------------------------------------------------

get_comspec:       push ds
                   push es

                   push cs
                   pop  es

                   mov  si,2ch
                   mov  si,[si]                ;Get SEGMENT of environment.
                   mov  environ,si
                   mov  ds,si

                   mov  si,0ffffh              ;DS:SI+1 point to environment.

cfnd_end:          inc  si
                   mov  ax,[si]
                   cmp  ax,0
                   jnz  cfnd_end

                   mov  dx,si                  ;DS:DX points to end of environ.
                   mov  si,0ffffh              ;DS:SI points to start of environ.
                   mov  di,offset cacad_env    ;ES:DI points to search string.

cfind_loop:        inc  si                     ;Increment search location.
                   cmp  si,dx                  ;Have we exceeded limit?
                   jnc  csrch_end              ;Yes?, exit this routine.

                   push si
                   push di
                   mov  cx,8
                   repz cmpsb                  ;Compare until found.
                   pop  di
                   pop  si
                   jnz  cfind_loop             ;Not found? Then Loop Up.

                   cmp  cx,0                   ;String Exausted?
                   jnz  cfind_loop

                   add  si,8                   ;DS:SI point to command.com path.
                   mov  di,offset cmdname
                   call strcpy                 ;Copy name of processor to us.

csrch_end:         pop  es
                   pop  ds
                   ret

cacad_env:         db "COMSPEC=",0    ;String to look for in environ.

;-----------------------------------------------------------------------------
;-----------------------------------------------------------------------------
STRCPY:         push si
                push di
                push cx

                push di
                mov  di,si      ;Point ES:DI to source string.
                push es
                push ds
                pop  es         ;ES:DI point to string

                push  di
                push  ax
                mov   cx,0ffffh
                xor   al,al
                repnz scasb     ;STRLEN
                not   cx
                pop   ax
                pop   di

                pop  es
                pop  di
                rep  movsb      ;Move source to destination.

                pop  cx         ;Restore all registers.
                pop  di
                pop  si

                RET

;-----------------------------------------------------------------------------
;-----------------------------------------------------------------------------
get_bat_name:      mov  ds,ds:[002ch]         ;Get segment of environ.
                   mov  si,0

get_again:         lodsb                      ;Get a letter out of env.
                   cmp  al,0                  ;Was it a ZERO?
                   jnz  get_again             ;No? Get again.

                   lodsb                      ;Get Next.
                   cmp  al,0                  ;Two Zeros in a row?
                   jnz  get_again             ;No? Jump up...

find_rname:        lodsb                      ;Jump past this parm.
                   cmp  al,0
                   jnz  find_rname

;DS:SI points at RUN-NAME.

                   mov  di,offset cl_command  ;Store the Name in this seg.

move_the_name:     lodsb
                   stosb
                   inc  cs:cl_count
                   cmp  al,0
                   jnz  move_the_name

                   push cs                    ;Home sweet Home...
                   pop  ds

                   mov  si,di                 ;Point at end of Run-Name.

                   cli                        ;Lets cool it for a few secs.
                   std                        ;We want to search BACKWARDS.

find_slash:        lodsb
                   dec  cs:cl_count
                   cmp  al,"\"
                   jnz  find_slash            ;Keep going back until found.
                   inc  cs:cl_count
                   cld                        ;Foward again.
                   sti                        ;All is OK back on the farm.
                   add  si,2                  ;SI points at last slash + 1

                   mov  di,si                 ;Move the name into place.
                   mov  si,offset cl_cmd_src

     batname:      lodsb
                   stosb
                   inc  cs:cl_count
                   cmp  al,0
                   jnz  batname
                   ret

vid ends
end start