home *** CD-ROM | disk | FTP | other *** search
- title glassmodem.asm Glass TTY routine for IBM VCAPI
- Page 60,132
- ;
- ; This ain't beautiful code. It just evolved this way.
- ; I could have spent more time cleaning things up.
- ; It should be useful as a guide as to how to call the
- ; IBM Voice Communication Application Program Interface.
- ; This has only been tested with Microsoft MASM 4.0
- ;
- ; The program takes the number to be dialed from the command
- ; line. What ever garbage you put on the command line will be
- ; fed to the dial routine.
- ;
- ; Control break exits
- ; F10 prints error summary there are more errors than their ought to be!
- ; It is left as an exercise to the reader to make F9 send a break
- ;
- ; There are two modules in this file the last one is called ERR.
- ; It should be assembled seperately.
- ; Use the following to link these files:
- ;
- ; link glasmode+err/dosseg,glasmode,glasmode/map;
- ;
- ; Note the /dosseg flag this puts the zzrom segment last in
- ; memory. There is probably some way to get the last memory from
- ; the prefix header, but that has always been an unfathomable mystery
- ; to me.
-
- include veqts.asm
- sseg segment para stack
- db 100 dup('STACK')
- sseg ends
- zzrom segment public 'dseg'
- zzrom ends
- ;
- code segment para public 'code'
- assume cs:code,ss:sseg,ds:dyseg,es:dyseg
- extrn uerr:near ;Load code to print string
- extrn nout:near ;print number in decimal
- extrn hout:near ;print byte in hex
- extrn perr:near ;writes dos error code
- extrn getlast:near ;gets last location loaded in memory
- public main
- main proc far
- mov ax,es ;shrink allocated memory
- mov bx,zzrom ;IBM resident code does dynamic memory
- sub bx,ax ;allocation so we must give it back first
- call getlast ;so some is available
- add bx,ax
- mov ah,4ah
- int dos
- jnc dispok
- jmp hbye ;Thats all folks
- dispok: lea bx,dyseglen ;Length in bytes of dynamic memory
- push ds ;save prefix
- call getmemory ;gets dynamic memory
- jnc memok
- jmp hbye
- memok: pop ax
- mov prefix,ax ;prefix segment needed later
- xor ax,ax ;zero modem error counts
- mov framec,ax
- mov parityc,ax
- mov overunc,ax
- ;
- ; open VCAPI
- ;
- mov ax,255 ;wierd return code
- mov ret,ax ;if unchanged there is no card
- mov ah,11h ;VCAPI id
- mov al,open ;function code for open
- mov dx,21fh ;Card I/O address
- lea bx,plist ;Address of parameter list
- ;
- ; note DS register will be used by interrupt routines
- ;
- int 14h ;invoke open
- or ax,ax ;IBM could save a lot by using cc
- je openok ;Continue if no error
- mov ax,ret ;perhaps not installed
- cmp ax,255
- jne operr
- mov ax,2 ;Tell world vcapi not installed
- call uerr
- jmp hbye
- operr: mov bx,open ;Let world know what we were doing
- jmp errcod
- openok: lea bx,parms ;bx always points to parameter list
- chkerr = 1 ;print errors if they happen
-
- ;
- ;grab hardware we need
- ;
- stuf2 claimhdw,rcb,bid,port1+line1+part1+part2+telephone,0,claimok
- ;
- ;connect function to port
- ;
- claimok:
- stuf2 connftop,cid1,bid,port1,telephony,cftpok
- ;
- ;see if we can load modem in part 2
- ;
- cftpok:
- stuf2 connftop,cid2,bid,port1,amodem,cftpok2
- ;
- ;read modem configuration values
- ;
- cftpok2:
- stuf rconfig,cid2,cid2,rcok
- ;
- ;set new modem config values
- ;
- rcok:
- mov [bx].rate,12 ;set baud 1200
- mov [bx].length,8 ;8 bit bytes
- mov [bx].parity,0 ;no parity
-
- ;
- ;set these new values
- ;
- stuf cconfig,cid2,cid2,stok
- ;
- ;connect devices to port
- ;
- stok: stuf2 conndtop,rcb,bid,port1,line1,cdtpok
- ;
- ;disconnect line 1
- ;
- cdtpok:
- stuf1 dcondevs,rcb,bid,line1,disconok
- ;
- ;set up interrupt for bid with special macro
- ;
- disconok:stuf3s estint,rcb,bid,comdcomplet,1,baseint,bestiok
- ;
- ; allow command complete interrupt to work
- ;
- bestiok:mov ax,comdcomplet
- call benaints
- ;
- ; pick up the phone
- ;
- stuf1 offhook,rcb,bid,1,offhok ;Note equate for line1 is 10h not 1
- offhok: mov ax,50 ;Wait 5 seconds
- call wait
- jnc offok
- offok: mov ret,0
- ;
- ;link interrupts to interrupt routine
- ;
- stuf3s estint,cid1,cid1,readcallprogc+dialcomplete,1,cid1int,esti1ok
- esti1ok:mov ax,readcallprogc+dialcomplete
- mov dx,cid1
- call cenaints
- ;
- ; see whether we got a dial tone
- ;
- stuf4 readcall,cid1,cid1,70,70,0,0,rdok
- rdok: mov ax,100 ;wait 10 seconds
- call wait
- jnc rdcok
- mov ax,5 ;Tell world we timed out
- call uerr
- jmp hbye
- rdcok: cmp [bx].subints2,dialtone
- jz gotdt
- mov ax,6
- call uerr
- jmp hbye
- gotdt: lea di,[bx].w2
- mov ds,prefix
- mov al,byte ptr ds:80h ;count of characters on command line
- mov si,81h ;point to characters on command line
- and ax,0fh ;Only allow 15 characters
- mov cx,ax
- rep movsb
- mov al,':'
- stosb
- push es
- pop ds ;restore dynamic segment
- mov ax,1100h+dial ;dial the number
- mov dx,cid1
- mov [bx].w1,dx
- int 14h
- or ax,ax ;test return code
- jz dialok
- mov bx,dial
- jmp errcod
- dialok: mov ax,200
- call wait
- jnc dialdone
- mov ax,5 ;Tell world we timed out
- call uerr
- jmp hbye
- ;
- ; see what we got at other end of phone
- ; this part of the code is weak and doesn't work for all
- ; phones. A bit of fiddeling with parameters and a more intelligent
- ; retry mechanism would be nice. Also if a person answers the phone
- ; it would be polite to give the operator a chance to pick up the
- ; phone so they could talk.
- ;
- dialdone:stuf4 readcall,cid1,cid1,70,70,0,0,rdok2
- rdok2: mov ax,100 ;wait 10 seconds (more than 7 sec!)
- call wait
- jnc rdcdok
- mov ax,5 ;Tell world we timed out
- call uerr
- jmp hbye
- rdcdok: cmp [bx].subints2,carrier
- jz gotcar
- cmp [bx].subints2,ringback
- jnz wrdans
- mov ax,9 ;tell em it is ringing
- call uerr
- mov ah,06 ;check console
- mov dl,0ffh
- int dos
- lea bx,parms ;dos clobbered this
- jz rdok2 ;wait for another ring
- jmp hbye
- wrdans: cmp [bx].subints2,busy
- jz gotbus
- cmp [bx].subints2,fastbusy
- jnz whtnxt
- gotbus: mov ax,10
- call uerr ;announce phone is busy
- jmp hbye
- ;
- ; we could ask user to pick up phone to see if we got a person
- ; or something but we are just interested in a carrier
- ;
- whtnxt: mov ax,7
- call uerr
- jmp hbye
- gotcar: mov ax,8
- call uerr
- lea ax,cbuff ;initialise circular pointers
- mov tailptr,ax
- mov headptr,ax
- ;
- ; hook up to interrupt routine for incomming characters
- ;
- stuf3s estint,cid2,cid2,dataready,1,rcvint,esti2ok
- esti2ok:
- ;
- ;hook up routine to count errors
- ;
- stuf3s estint,cid2,cid2,linerr,1,errint,esti3ok
- esti3ok:
- mov ax,lnkstatus
- mov dx,cid2 ;for this cid
- call cenaints
- ;
- ; start modem going
- ;
- stuf start,cid2,cid2,strtok
- strtok: stuf readstat,cid2,cid2,chkints
- chkints:mov ax,[bx].ints
- test ax,lnkstatus
- jz strtok
- mov ax,[bx].subints1 ;these bits tell if modem started OK
- and ax,0f0h
- jz watup
- mov ax,11
- call uerr
- jmp hbye
- watup: mov ax,0fh ;enable all interrupts
- mov dx,cid2 ;for this cid
- call cenaints
- ;
- ; here is main glasstty loop
- ;
- public sndok
- sndok: MOV AH,1 ; CHARACTER TYPED?
- INT 16H ; BIOS KBD
- JZ NOKEY ; JUMP IF NOT
- MOV AH,0 ; READ CHAR TYPED
- INT 16H ; BIOS KBD
- OR AX,AX ; CONTROL BREAK?
- jnz gotkey
- jmp hbye ;punt
- gotkey: cmp ax,4400h ;F10?
- jne not_f10 ;Jump if not
- jmp prtsum ;print error summary for f10
- not_f10:and ax,7fh
- push ax
- watup3: stuf readstat,cid2,cid2,tstup2
- tstup2: mov ax,[bx].state
- test ax,modemstrt+statxmitrdy
- jz watup3
- pop ax
- mov [bx].w2,ax ;character to be sent
- stuf send,cid2,cid2,sndok
- ;
- ;no fall through here
- ;
- nokey: mov si,headptr ;see if anything is in circular buffer
- cmp si,tailptr
- jnz carin
- jmp sndok
- carin: lodsb
- cmp si,offset bufend
- jnz nowrap
- lea si,cbuff
- nowrap: mov headptr,si
- MOV AH,14 ; WRITE TTY
- INT 10H ; BIOS VIDEO
- jmp sndok
- ;
- ; print error summary
- ;
- prtsum: mov ax,parityc
- or ax,ax
- jz noparer
- call nout
- mov ax,12
- call uerr
- noparer:mov ax,framec
- or ax,ax
- jz noframer
- call nout
- mov ax,13
- call uerr
- noframer:mov ax,overunc
- or ax,ax
- jz noverun
- call nout
- mov ax,14
- call uerr
- noverun:add ax,framec ;Were there any errors?
- add ax,parityc
- jnz diderr
- mov ax,15 ;tell em no errors
- call uerr
- diderr: jmp sndok ; control break exits
-
- main endp
- ;
- ; interrupt routine for incomming character
- ;
- rcvint proc far
- push ds
- pop es ;IBM wasn't good enough to do this for us
- chkerr = 0 ;don't print errors from int code
- lea bx,iparms ;int code gets own copy of parm area
- stuf receive,cid2,cid2,yepchr
- yepchr: mov ax,[bx].w2 ;here be character
- mov di,tailptr
- and al,07fh
- stosb
- cmp di,offset bufend ;stuff incomming char in circular buffer
- jnz notwrap
- lea di,cbuff
- notwrap:mov tailptr,di
- ret
- chkerr = 1 ;print errors if they happen
-
- rcvint endp
- ;
- ; interrupt routine for base function complete
- ;
- baseint proc far
- public baseint
- mov dx,bid
- mov ax,rcb ;do real simple setup for
- rdstx: lea bx,parms ;readstat command
- mov [bx].w1,ax
- mov ax,1100h+readstat
- push ds
- pop es ;IBM doesn't restore es!!
- int 14h
- ;
- ;If this fails we are dead anyway so don't bother checking
- ;
- mov ret,1 ;signal foreground something happened
- ret
- baseint endp
- ;
- ; interrupt routine for cid1 interrupts is just as simple
- ;
- cid1int proc
- public cid1int
- mov ax,cid1
- mov dx,ax
- jmp rdstx
- cid1int endp
- ;
- ; errint adds one to the error count for what ever is ailing us
- ;
- errint proc far
- public errint
- push ds
- pop es ;IBM wasn't good enough to do this for us
- chkerr = 0 ;don't print errors from int code
- lea bx,iparms ;int code gets own copy of parm area
- stuf readstat,cid2,cid2,cnters
- cnters: mov ax,[bx].subints1
- test al,1
- jz tstpar
- inc overunc
- tstpar: test al,2
- jz tstfrm
- inc parityc
- tstfrm: test al,4
- jz nofrm
- inc framec
- nofrm: ret
- errint endp
- ;
- ; print message saying this is vcapi return code presumably uerr
- ; was called so the user is informed as to which call failed
- ; error code passed as 16 bits in AX command code in BL
- ;
- errcod proc near
- push ax ;save error code
- push bx
- mov ax,-3 ;print message saying here is command code
- call uerr
- pop ax
- call hout ;hex the command code
- mov ax,-4 ;print message saying here is errorcode
- call uerr
- pop ax
- call nout ;manual gives errors in decimal
- xor ax,ax
- call uerr ;prints crlf
- jmp hbye ;always a fatal error
- errcod endp
- benaints proc near
- ;
- ;This could be done by macro byt since it gets called so many times...
- ;
- ; Interrupt mask passed in AX
- ; BX as always points to parameter list
- ;
- mov [bx].w2,ax ;Interrupt mask
- mov ax,rcb
- mov [bx].w1,ax
- mov dx,bid
- enaj: mov ax,1100h+maskint
- int 14h
- or ax,ax
- jc badmask
- ret
- badmask:mov bx,maskint
- jmp errcod ;don't mind not popping stack
- benaints endp
- cenaints proc near
- ;
- ;This could be done by macro byt since it gets called so many times...
- ;
- ; Interrupt mask passed in AX
- ; BX as always points to parameter list
- ;
- mov [bx].w2,ax ;Interrupt mask
- mov [bx].w1,dx
- jmp enaj
- cenaints endp
- getmemory proc near
- ;
- ;This gets dynamic memory in C or Pascal environment call the heap allocator
- ;or Windows or Topview (or whatever) memory allocator. This should have
- ;conditional assembly parameters to support all those good things. Currently
- ;just ask DOS.
- ;
- ;On entry BX contains bytes required
- ;On exit DS and ES point to segment
- ;
- add bx,10h ;round to paragraph
- mov cl,4
- shr bx,cl
- mov ah,48h ;Allocate memory function
- int dos
- jnc aok
- push ax ;save return code
- mov ax,-1 ;tell world memory allocate
- call uerr
- pop ax
- call perr ;prints DOS error
- stc
- aok: mov ds,ax ;set segment registers
- mov es,ax ;invalid if carry set
- ret
-
- getmemory endp
- ;
- ; Local timer to check on board uses stack space this is a busy
- ; wait timer. If running in an environment with real tasking support
- ; replace this code with something better!!!!
- ;
- strtc proc near
- xor ah,ah ; read clock
- int btod ; BIOS time-of-day routine
- mov [bp],cx ; high portion of clock
- mov [bp].2,dx ; low portion of clock
- ret
- strtc endp
- dw_mpd dw 1000/10 ; msecs per decisecond
- dw_tick_len dw tick_len ; timer tick in msecs
- chk_timr proc near
- mov ah,0 ;read clock
- int btod ;BIOS time-of-day routine
- sub dx,[bp].2
- sbb cx,[bp]
- mov ax,dx ;Prepare for mul/div
- mov dx,cx ; ax=lo, dx=hi
- mul dw_tick_len ;Convert ticks
- div dw_mpd ;to 100 msec ticks
- cmp ax,[bp].4 ;Wait for specified time
- ret
- chk_timr endp
- ;
- ; Wait waits for an event or for timer to expire.
- ; Carry exit means time expired. This can be replaced by
- ; something that actually causes a context switch when DOS grows up
- ;
- wait proc near ;AX contains time in deciseconds in AX
- push bx
- strt_timr
- cloop0: test ret,1 ;This bit gets set when interrupt routine
- jne donwat ;is run
- call chk_timr
- jl cloop0
- add sp,6 ;pop stack
- pop bx
- stc ;error exit
- ret
- donwat: add sp,6
- pop bx
- mov ret,0
- clc ;good exit
- ret
- wait endp
- ;
- ; hbye closes the vcapi, releases dynamic memory and exits
- ;
- hbye proc near
- mov ax,1100h+onhook
- lea bx,parms ;May have been clobbered by now
- mov dx,rcb ;dx = rcb
- mov [bx].w1,dx ;move rcb into paramater list
- mov dx,1 ;Line 1 (no equate here)
- mov [bx].w2,dx
- mov dx,bid ;Base commands
- int 14h
- ;don't care if this works or not
- chkerr = 0 ;don't check errors
-
- stuf1 conndevs,rcb,bid,telephone+line1
- ;don't care here either
- mov ax,1100h+close
- lea bx,plist ;Address of parameter list
- mov dx,bid ;dx = base id (for base commands)
- int 14h
- ;
- ;Don't bother checking return code
- ;
- push ds
- pop es ;free data segment
- mov ah,49h
- int dos
- mov ax,4c00h
- int dos ;say goodbye with 0 return code
- hbye endp
- code ends
- end main
-
- Comment +
-
- ----- Cut here for ERR Module -----
-
-
- title ERR
- page 55,131
- ;
- ; This module contains lots of error print out routines.
- ; It uses its own data segment and is reentrant. Error
- ; messages are referred to by number so any program can be
- ; written and error messages later changed to whatever language
- ; is desired.
- ;
-
- cr equ 13
- lf equ 10
- zzrom segment public 'dseg'
- ertab dw m0,m1,m2,m3,m4,m5,m6,m7,m8,m9
- dw m10,m11,m12,m13,m14,m15,m16,m17,m18,m19
- dw m20,m21,m22,m23,m24,m25,m26,m27,m28,m29
- dw m30,m31,m32,m33,m34,m35
- uertab dw u0,u1,u2,u3,u4,u5,u6,u7,u8,u9,u10,u11,u12,u13,u14,u15
- dw10 dw 10
- crlf db cr,lf,'$'
- m0 db '$'
- m1 db 'Invalid Function Number$'
- m2 db 'File not Found$'
- m3 db 'Path not found$'
- m4 db 'Too many Open Files$'
- m5 db 'Access Denied$'
- m6 db 'Invalid Handle$'
- m7 db 'Memory Control blocks destroyed$'
- m8 db 'Insufficient Memory$'
- m9 db 'Invalid memory block address$'
- m10 db 'Invalid environment$'
- m11 db 'Invalid format$'
- m12 db 'Invalid access code$'
- m13 db 'Invalid data$'
- m14 db 'Reserved (ask Microsoft)$'
- m15 db 'Invalid drive specification$'
- m16 db 'Attempt to remove current directory$'
- m17 db 'Not same device$'
- m18 db 'No more files$'
- m19 db 'Diskette write protected$'
- m20 db 'Unknown Unit$'
- m21 db 'Drive not ready$'
- m22 db 'Unknown Command$'
- m23 db 'Data Error (CRC)$'
- m24 db 'Bad request structure length$'
- m25 db 'Seek error$'
- m26 db 'Unknown Media Type$'
- m27 db 'Sector not found$'
- m28 db 'Printer out of paper$'
- m29 db 'Write fault$'
- m30 db 'Read fault$'
- m31 db 'General failure$'
- m32 db 'Sharing violation$'
- m33 db 'Lock violation$'
- m34 db 'Invalid disk change$'
- m35 db 'FCB Unavailable$'
- maxmsg equ 35
- unknown db 'Unknown Error code $'
- u0 db '$'
- u1 db 'Memory allocation: $'
- u2 db 'Voice communications application interface not installed$'
- u3 db 'Fatal Error calling VCAPI Command: $'
- u4 db ' Return Code: $'
- u5 db 'Timed out waiting for VCAPI interrupt$'
- u6 db 'Could not detect dial tone$'
- u7 db 'Unable to detect modem carrier$'
- u8 db 'modem carrier detected$'
- u9 db 'ring$'
- u10 db 'busy$'
- u11 db 'modem start command failed$'
- u12 db ' parity errors$'
- u13 db ' frameing errors$'
- u14 db ' overun errors$'
- u15 db 'no errors yet$'
- maxumsg equ 15
- hextab db '0123456789ABCDEF'
- last label byte
- zzrom ends
- CODE SEGMENT PARA PUBLIC 'CODE'
- ASSUME CS:CODE,DS:zzrom
- public perr ;Prints DOS error
- public uerr ;User error
- public nout ;Print decimal AX
- public whout ;Print hex AX
- public hout ;print hex AL
- public getlast ;gets last value in memory
- ;
- ; gets last paragraph boundary there are better ways and this
- ; won't work in a high level language environment but....
- ;
- getlast proc near
- lea ax,last
- add ax,0fh
- shr ax,1
- shr ax,1
- shr ax,1
- shr ax,1
- ret
- getlast endp
- perr proc near
- push ds
- push ax
- mov ax,zzrom ;Got to address our strings
- mov ds,ax
- pop ax
- or ax,ax ;ax contains error code
- jg ok
- jnz unk
- jmp short perr_x ;do nothing for zero
- unk: push ax
- lea dx,unknown ;never seen this error code
- mov ah,9
- int 21h
- pop ax
- call whout ;print numeric code
- jmp short perr_x
- ok: cmp ax,maxmsg
- jg unk ;unknown error
- add ax,ax ;make word inder
- mov si,ax
- mov dx,ertab[si]
- mov ah,9
- int 21h
- perr_x: pop ds
- ret
- perr endp
- ;
- ; print an error string if error number is negative don't append CRLF
- ;
- uerr proc near
- push ds
- push ax
- push ax ;save second one as crlf flag
- mov ax,zzrom ;Got to address our strings
- mov ds,ax
- pop ax
- or ax,ax ;ax contains error code
- jg ok1
- neg ax ;Make negative positive
- jg ok1
- jnz unk1
- jmp short uerr_x ;do nothing for zero
- unk1: push ax
- lea dx,unknown ;never seen this error code
- mov ah,9
- int 21h
- pop ax
- call nout ;print numeric code
- jmp short uerr_x
- ok1: cmp ax,maxumsg
- jg unk1 ;unknown error
- add ax,ax ;make word inder
- mov si,ax
- mov dx,uertab[si]
- mov ah,9
- int 21h
- uerr_x: pop ax ;If code was positive do crlf
- or ax,ax ;If negative don't
- jl nocrlf
- lea dx,crlf ;get new line
- mov ah,9
- int 21h
- nocrlf: pop ds
- ret
- uerr endp
-
- ; Print the number in AX on the screen in decimal
-
- NOUT PROC NEAR
- push ds
- push ax
- mov ax,zzrom ;Got to address our strings
- mov ds,ax
- pop ax
- push dx
- mov dx,0 ;High order word should be zero.
- div dw10 ;AX <-- Quo, DX <-- Rem.
- cmp ax,0 ;Are we done?
- jz nout0 ;Yes.
- call nout ;If not, then recurse.
- nout0: add dl,'0' ;Make it printable.
- push ax
- mov ah,2 ;Single character to display
- int 21H
- pop ax
- pop dx
- pop ds
- ret ;We're done. [21c]
- NOUT ENDP
- whout proc near ;Print words worth of hex code
- push ax
- call hout ;by calling hout twice
- pop ax
- mov al,ah
- jmp hout
- whout endp
- hout proc near ;Print byte in hex
- push ds
- push ax
- mov ax,zzrom ;Got to address our strings
- mov ds,ax
- pop ax
- push dx ;Save registers used
- push bx
- push cx
- push ax ;Save input so we can get low nibble
- mov cx,4 ;Do hi nibble first
- shr al,cl
- and ax,0fH ;Just four bits
- lea bx,hextab
- xlat hextab ;Turn into printable
- mov dl,al ;Print single character
- mov ah,2
- int 21H
- pop ax
- and al,0fH ;Now do low bits
- xlat hextab
- mov dl,al
- mov ah,2
- int 21H
- pop cx ;and restore registers
- pop bx
- pop dx
- pop ds
- ret
- hout endp
- code ends
- end
-
- +