home *** CD-ROM | disk | FTP | other *** search
-
- PAGE 44,132
-
- ; Copyright (C) 1991 by Jan.Engvald@ldc.lu.se, see file COPYING.
-
- ;========================================================================
- include pdclkset.doc
- ;========================================================================
-
- ESCAPE equ 27
- RFCC equ TBLBUILD+PINGCLIENT ; RFC compliance needed
-
- if TBLBUILD
- PROGSTR equ 'pdtbuild'
- else
- PROGSTR equ 'pdclkset'
- endif ; TBLBUILD
-
- IDSTRING equ PROGSTR,PRGVERSION
-
-
- include defs.asm
-
- ;************************************************************************
- ;* Start of segment (PSP data) *
- ;************************************************************************
-
- .386 ; (to avoid masm expression overflow)
-
- code_s segment use16
- assume cs:code_s, ds:code_s, es:code_s
-
- org 0
- CodeOrg label byte
- PspInt20 dw ?
- PspTopMem dw ?
-
- org 5Ch ; PSP reused for data
-
- org 80h ; PSP command parameter area
- phd_dioa db ?
- db ? ; always a space
- phd_string db ?
-
-
- ;************************************************************************
- ;* Start of segment (code) *
- ;************************************************************************
-
- org 100h
- StackEnd equ $ ; 80h-100h is interupt stack
- SaveSP equ $
- SaveSS equ SaveSP+2
-
- start: jmp start1 ; jump over data area
- nop
-
- id_label db IDSTRING
-
-
- ;************************************************************************
- ;* *
- ;* Data area *
- ;* *
- ;************************************************************************
-
- NotEnoughMsg db LF, "Need to know at least IP nr, Offset and Timeserver$"
- OccupiedMsg db LF, "My IP nr is already in use by another host with hardware addr "
- OccupiedHw db "00:00:00:00:00:00$"
- MsgNoConect db LF, "No response from target host$"
- NoBotReplyMsg db LF, "No BOOTP reply$"
- NoGwyMsg db LF, "Need to know a gateway (or wrong mask)$"
- NoTimeServMsg db LF, "No reply from time server$"
-
- usage_msg db LF
- db "Copyright (C) 1991 by Jan.Engvald@ldc.lu.se, see file COPYING.", CR, LF
- db IDSTRING, ' ', ??date, " usage to set the PC clock from an UDP/IP TIME server:", CR, LF, LF
- ; db "pdclkset b[ootp] or", CR, LF, LF, LF
- db PROGSTR," [o[ffset]=time] (time is [-|+][<hours>h][<minutes>m][<seconds>[s]])", CR, LF, LF
- db " [d[aylightsave]=PAC | USA | CUB | CHIL | BRZ | GBR |", CR, LF
- db " W_EU | M_EU | E_EU | LIBY | EGY | TURK | ISR |", CR, LF
- db " IRAN | PRC | ROK | AUS | TASM | NSW | LHI | NZE |", CR, LF
- db " FrTime,FrWeekDay,FrDayOfYear,ToTime,ToWday,ToDayOfYr,AddTime]", CR, LF, LF
- db " [i[pnr]=n.n.n.n] [t[imserver]=n.n.n.n[,n.n.n.n[,...]]]", CR, LF, LF
- db " [m[ask]=n.n.n.n g[ateway]=n.n.n.n[,n.n.n.n[,...]]] [f[lags]=flagnr]", CR, LF, LF
- db " [z[onename]= # | variable=normalname,dlsname] [a[lter]=days,time]", CR, LF, LF
- db " [p[ktintno]=hexnr]"
- if PINGCLIENT
- db " [e[cho]=name|n.n.n.n [,size,interval[,data,inc]]]", CR, LF, LF
- db " [n[ameserver]=n.n.n.n[,n.n.n.n[,...]]]"
- endif ; PINGCLIENT
- db CR, LF, LF
- db "Example: ",PROGSTR," o= -1h d=M_EU z=# (my IP nr and timeserver(s) from BOOTP)", CR, LF
- db " ",PROGSTR," offs= 6h dst= USA zonename= tz=CST,CDT (sets TZ=CST or CDT)", CR, LF
- db " ",PROGSTR," o=8h d=PAC ip=123.45.6.7 ts=123.45.6.8 (BOOTP not used)"
-
- if PINGCLIENT
- db CR, LF, " ",PROGSTR," pktdrv= 0x7c echo= ping.lu.se (ping client)"
- endif
- if TBLBUILD
- db CR, LF, " ",PROGSTR," flags= 2+4 (address table builder for LANwatch)"
- endif
- db '$'
- crlf_msg db CR, LF, '$'
-
- MsgNotSet db CR, LF
- db "***************************************", CR, LF, 7
- db "* *", CR, LF, 7
- db "* Could not set correct date and time *", CR, LF
- db "* *", CR, LF
- db "***************************************", CR, LF, "$"
-
- MsgTerm db CR, LF, "End of ", IDSTRING, ", error="
- MsgTermNr db 255, ", HWaddr "
- MsgTermHw db "00:00:00:00: , IP nr "
- MsgMyIp db "1.2.3.4 ", CR, LF
- MsgTermStop db "$", 7, Cr, LF, 7
- db "Dst entries too old, update and reassemble PDCLKSET", CR, LF, '$'
-
- even
- Flagword dw 0
- DONT_SETTIME equ 1
- HAVE_MYIPNR equ 2
- HAVE_TIMEOFFSET equ 4
- HAVE_TIMESERVER equ 8
-
- HAVE_ENOUGH equ HAVE_MYIPNR + HAVE_TIMEOFFSET + HAVE_TIMESERVER
- EnoughWord dw HAVE_ENOUGH
-
- ArgFlags dw 0
- TERM_WAIT equ 1
- MAKE_TABLE equ 2
- LANW_TABLE equ 4
- TBL_PROBE equ 8
- TIM_NOHIRES equ 16
-
- MAXTSERVS equ 4
- RespondingIpNr dw 0, 0
-
- TservNum dw 0
- TimeServIpNr dw MAXTSERVS*2 dup(0)
-
- Sday equ 3600*24
-
- days macro incval
- dd x*Sday
- x = x+incval
- endm
-
- Ytab:
- x = 15*366 + 49*365 ; start at 1964
- rept 16
- days 366
- days 365
- days 365
- days 365
- endm ; ends on year 2027
-
- Motab: ; normal year
- x = 0
- days 31 jan
- days 28 feb
- days 31 mar
- days 30 apr
- days 31 may
- days 30 jun
- days 31 jul
- days 31 aug
- days 30 sep
- days 31 oct
- days 30 nov
- days 31 dec
- days 1
-
- Mltab: ; leap yer
- x = 0
- days 31 jan
- days 29 feb
- days 31 mar
- days 30 apr
- days 31 may
- days 30 jun
- days 31 jul
- days 31 aug
- days 30 sep
- days 31 oct
- days 30 nov
- days 31 dec
- days 1
-
- Weekdays db " Sun"
- db " Mon"
- db " Tues"
- db "Wednes"
- db " Thurs"
- db " Fri"
- db " Satur"
-
-
- AlgTab AlgData <>
- AlgTabEnd equ $
-
- AlgPtr dw 0
-
- m6hour dw 6*3600
- m12hour dw 12*3600
- mhour dw 3600
- m60b db 60,0
- m7 dw 7
- m6 db 6
- m1 dw 1
-
- cWday dw 0
- cYear dw 0
- cMonth dw 0
- cDay dw 0
- cHour dw 0
- cMinute dw 0
- cSecond dw 0
-
- cNonLeapYear db 0, 0
- cDayOfYear dw 0
- cTime dw 0, 0
- AlterTime dw 0, 0, 0
- tzoffset dw 0, 0
- DstAdvance dw 0, 0
-
- msgweek = $+13
- msgyear = $+23
- msghour = $+37
- msgset db 'Clock set to Wednesday 1989-10-21 at 18:21:15'
- msgts = $+11
- db ' from host 1.2.3.4 ', '$'
-
-
- ;**********************************************************************
- ;*
- ;* End of data area
- ;*
- ;**********************************************************************
-
- .8086 ; ensure no 386-only instructions
-
- MULTIPROCESS equ 1 ; (the interrupt process counts here)
-
- PushfDI macro
- if MULTIPROCESS
- pushf ; save enable interrupt flag
- cli ; and disable interrupt
- endif ; MULTIPROCESS
- endm
-
- PopfEI macro
- if MULTIPROCESS
- popf ; restore enable interrupt flag
- endif ; MULTIPROCESS
- endm ; (probably enabling interrupt)
-
-
-
- ;************************************************************************
- ;* Something2Do
- ;*
- ;* Simulates a task scheduler.
- ;*
- ;* Destroys: flags
- ;************************************************************************
-
- Something2Do proc near
- push ax
- push bx
- push cx
- push dx
- push si
- push di
- push bp
- push es
- push ds
- if RFCC
- mov di,offset IcmpToDo
- call GetFromList
- jz SomethingNxt4
- mov cx,[bx].dPktLen ; (actually IP data length)
- call SendIcmpPkt
- call BufRelease
- SomethingNxt4:
- endif ; RFCC
- mov di,offset SendToDo
- call GetFromList
- jz SomethingNxt2
- call SendAndWait
- call BufRelease
- SomethingNxt2:
- if TBLBUILD
- cmp sp,offset StackLow+6*16 ; avoid overload
- jb SomethingNxt5
- call TblProbe
- mov di,offset TblToDo
- call GetFromList
- jz SomethingNxt5
- call DoTable
- SomethingNxt5:
- endif ; TBLBUILD
-
- if TBLBUILD or PINGCLIENT
- mov di,offset NameToDo
- call GetFromList
- jz SomethingNxt6
- call DoNsInterp
- call BufRelease
- SomethingNxt6:
- endif ; TBLBUILD or PINGCLIENT
-
- if RFCC
- mov ax,SendToDo.lBufsAvail
- add ax,IcmpToDo.lBufsAvail
- endif ; RFCC
- if TBLBUILD
- add ax,TblToDo.lBufsAvail
- endif ; TBLBUILD
- if TBLBUILD or PINGCLIENT
- add ax,NameToDo.lBufsAvail
- endif ; TBLBUILD or PINGCLIENT
- pop ds
- pop es
- pop bp
- pop di
- pop si
- pop dx
- pop cx
- pop bx
- pop ax
- ret
- Something2Do endp
-
-
-
- include pktdr.asm
-
- include pkterr.asm
-
- include movemem.asm
-
- ARPSLOTS equ 8 + 4*TBLBUILD
- ROUTESLOTS equ 5
- MAXDEFGWYS equ 4 + 6*TBLBUILD
- MAXDEFNS equ 3
-
- SNAP equ 0
-
- NBUFSMALM equ 24 ; at least so many small bufs
-
- ;========================================================================
- include bufs.asm
-
- ;========================================================================
- include ip.asm
-
-
- ;========================================================================
- include arp.asm
-
- ;************************************************************************
- ;* MakeSendDescr
- ;************************************************************************
-
- MakeSendDescr proc near
- push si
- mov [bx].dSqDelay,0
- mov [bx].dWaitEvent,0
- mov [bx].dTimOutMsg,offset MsgNoConect
- mov [bx].dTickTimeout,4*18
- mov [bx].dTickResend,1*18
- lea di,[bx+DESCRLEN]
- mov [bx].dPtrPhys,di
- lea si,[di]+GIANT
- mov [bx].dPktEnd,si
- add di,H2Len
- add di,2
- xor cx,cx
- test GenFlags,USE_SNAP
- jz MakeNotSnap
- add di,8 ; snap
- inc cx
- MakeNotSnap:
- mov [bx].dSnap,cl
- mov [bx].dPtrIp,di
- mov cx,IPHDRLEN
- mov si,offset IpHdr
- push cs
- pop es
- call movemem ; copy IP hdr prototype
- mov [bx].dPtrUdp,di
- pop si
- ret
- MakeSendDescr endp
-
-
-
-
- ;************************************************************************
- ;************************************************************************
- ;*
- ;* Input and Output routines
- ;*
- ;************************************************************************
- ;************************************************************************
-
-
- PutNumFiller db '0'
- even
- GetNumBase dw 10
- PutNumBase dw 10
- PutMinDigits dw 2
- k10000 dw 10000
-
- IntTmpHwAd dw 0, 0, 0, 0, 0, 0
- IntTmpIpNr equ IntTmpHwAd
-
-
-
- ;************************************************************************
- ;* SkipPastEq
- ;************************************************************************
-
- SkipPastEq proc near
- mov cx,30 ; max name length
- SkipLook4Eq:
- cmp al,'=' ; look for equal sign
- je SkipFoundEq
- cmp al,':' ; colon is alias for equal
- je SkipFoundEq ; (batch parameters need it)
-
- lodsb
- loop SkipLook4Eq
- SkipFoundEq:
- call skip_blanks ; blanks may follow
-
- ret
- SkipPastEq endp
-
-
-
- ;************************************************************************
- ;* GetNums
- ;************************************************************************
-
- GetNums proc near
- mov ch,',' ; comma separated numbers
- jmp short GetSkipBlanks
- GetNumsDot:
- mov ch,'.' ; dot separated numbers
- GetSkipBlanks:
- push bx
- mov bx,cx
- call skip_blanks
- GetNextNum:
- call GetNum ; get a number
- stosw ; store it in table
- dec bl ; do we want more nums?
- jz GetNumsRet ; - no, return
-
- lodsb ; - yes
- cmp al,bh ; is this a separator char?
- je GetNextNum ; - yes
- GetNumsRet: ; - no, return
- pop bx
- ret
- GetNums endp
-
-
-
- ;************************************************************************
- ;* GetNum
- ;************************************************************************
-
- GetNum proc near
- xor dx,dx
- lodsb
- cmp al,'-' ; minus prefix?
- pushf
- je GetNumSign
- cmp al,'+' ; plus prefix?
- jne GetNoPrefix
- GetNumSign:
- lodsb ; get a char
- GetNoPrefix:
- mov GetNumBase,10
- cmp al,'0' ; hex leading '0x' ?
- jne GetNextDig
- cmp byte ptr [si],'X'
- je GetNextHex
- cmp byte ptr [si],'x'
- jne GetNextDig
- GetNextHex:
- inc si
- mov GetNumBase,16
- lodsb
- GetNextDig:
- cmp al,'0' ; a digit?
- jb GetNumEnd
- cmp al,'9'
- ja GetTstHex
-
- sub al,'0' ; convert to integer
- jmp short GetNumConv
- GetTstHex:
- cmp al,'A'
- jb GetNumEnd
- cmp al,'F'
- ja GetTstHex2
- sub al,'A'-10
- jmp short GetNumConv
- GetTstHex2:
- cmp al,'a'
- jb GetNumEnd
- cmp al,'f'
- ja GetNumEnd
- sub al,'a'-10
- GetNumConv:
- cbw
- add ax,dx
- mov cx,ax
- mul GetNumBase
- mov dx,ax
- lodsb
- jmp short GetNextDig
- GetNumEnd:
- mov dx,60*60
- cmp al,'h' ; hours suffix?
- je GetNumScale
-
- mov dx,60
- cmp al,'m' ; minutes suffix?
- je GetNumScale
-
- mov dx,1
- cmp al,'s' ; seconds suffix?
- je GetNumScale
-
- dec si ; move back char ptr
- GetNumScale:
- mov ax,cx ; do suffix scaling
- mul dx
-
- cmp byte ptr [si],'+' ; composite number?
- je GetComposite
- cmp byte ptr [si],'-'
- je GetComposite
- cmp byte ptr [si],'0'
- jb GetSingle
- cmp byte ptr [si],'9'
- ja GetSingle
- GetComposite:
- push di ; save partial value
- mov cx,ax
- push cx
- mov di,dx
- call GetNum ; get next part
- pop cx
- add ax,cx ; add to previous part
- adc dx,di
- pop di
- GetSingle:
- popf ; minus prefix?
- jne GetNumRet
-
- not dx ; make number negative
- not ax
- add ax,1
- adc dx,0
- GetNumRet:
- cmp ax,ax ; ensure zero flag
- ret
- GetNum endp
-
-
-
- ;************************************************************************
- ;* GetIpNr
- ;************************************************************************
-
- GetIpNr proc near
- mov cx,1
- GetIpNums:
- push cs
- pop es
- push cx ; remember how many we wanted
- GetIpCont:
- push cx ; IP #'s left to read
-
- push di
- mov cl,4
- mov di,offset IntTmpIpNr
- call GetNumsDot ; read an IP #
- mov cx,4
- pop di
- jnz GetIpNrErr
-
- push si
- mov si,offset IntTmpIpNr
- GetIpNrLoop:
- lodsw ; convert to bytes
- stosb
- loop GetIpNrLoop
-
- pop si
- pop cx ; want more IP #'s?
- loop GetIpMore
- GetIpNrRet:
- pop ax
- sub ax,cx ; ax = IP #'s read
- cmp cx,cx ; zero flag
- ret
-
- GetIpMore:
- lodsb
- cmp al,',' ; comma separator?
- je GetIpCont
-
- dec si
- jmp short GetIpNrRet
-
- GetIpNrErr:
- pop cx
- pop cx
- ret ; non-zero return
- GetIpNr endp
-
-
-
- ;************************************************************************
- ;* PutIpNum (4 bytes from DS:SI to decimal at ES:DI)
- ;************************************************************************
-
- PutIpNum proc near
- push di
- push es
- push cs
- pop es
- mov cx,4
- mov di,offset IntTmpIpNr
- xor ah,ah
- PutIpLoop:
- lodsb ; convert IP #
- stosw ; into integers
- loop PutIpLoop
- pop es
- pop di
-
- push ds
- push cs
- pop ds
- mov si,offset IntTmpIpNr
- mov ch,'.'
- mov cl,4
- mov PutMinDigits,1
- call PutNums ; put IP #
- pop ds
- ret
- PutIpNum endp
-
-
-
- ;************************************************************************
- ;* PutHwNum
- ;************************************************************************
-
- PutHwNum proc near
- push di
- push cs
- pop es
- mov cx,6
- mov di,offset IntTmpHwAd
- xor ah,ah
- PutHwLoop:
- lodsb ; convert HW #
- stosw ; into integers
- loop PutHwLoop
- pop di
-
- push cs
- pop ds
- mov si,offset IntTmpHwAd
- mov ch,'-' ; separator char
- test ArgFlags,LANW_TABLE
- jz PutHwDash
- mov ch,7fh ; except for LANwatch table
- PutHwDash:
- mov cl,6
- mov PutNumBase,16
- mov PutMinDigits,2
- mov PutNumFiller,'0'
- call PutNums ; put HW #
- mov PutNumBase,10
- ret
- PutHwNum endp
-
-
-
- ;************************************************************************
- ;* PutNums
- ;************************************************************************
-
- PutNumsD4 proc near
- mov PutMinDigits,4
- PutNums:
- NextNum:
- lodsw ; get integer from table
- call PutNum ; convert to decimal
- dec cl ; any more #'s?
- jz PutNumsRet
-
- cmp ch,7fh ; no separator char?
- je NextNum
-
- mov al,ch
- stosb ; put separator char
- jmp short NextNum
- PutNumsRet:
- ret
- PutNumsD4 endp
-
-
-
- ;************************************************************************
- ;* PutNum
- ;************************************************************************
-
- PutNumD2 proc near
- mov PutMinDigits,2
- PutNum:
- xor dx,dx
- PutBigNum:
- push bx
- push cx
- xor cx,cx ; extract significant digits
- mov bx,dx
- cmp PutNumBase,10
- jne NextDig
- div k10000
- mov bx,ax
- mov ax,dx
- NextDig:
- xor dx,dx
- div PutNumBase
- add dx,'0'
- cmp dx,'9'
- jle PutNotHex
-
- add dx,'a'-'9'-1
- PutNotHex:
- push dx
- inc cx
- or ax,ax
- jnz NextDig
-
- or bx,bx
- jz PutFiller
-
- mov al,'0'
- PutZeroNext:
- cmp cx,4
- jae PutZeroNumbr
-
- push ax
- inc cx
- jmp short PutZeroNext
- PutZeroNumbr:
-
- mov ax,bx
- NextDig2:
- xor dx,dx
- div PutNumBase
- add dx,'0'
- push dx
- inc cx
- or ax,ax
- jnz NextDig2
- PutFiller:
- mov al,PutNumFiller
- PutFillNext:
- cmp cx,PutMinDigits ; want more digits?
- jae PutDigNumbr
-
- push ax
- inc cx
- jmp short PutFillNext
- PutDigNumbr:
- mov dx,cx ; save DX = # of digits
- PutDigs:
- pop ax
- stosb ; put the digits
- loop PutDigs
-
- pop cx
- pop bx
- ret
- PutNumD2 endp
-
-
-
- ;************************************************************************
- ;* PutBigNums
- ;************************************************************************
-
- PutBigNums proc near
- PutBigNext:
- lodsw
- mov dx,ax
- lodsw
-
- call PutBigNum
- loop PutBigNext
-
- ret
- PutBigNums endp
-
-
-
- ;************************************************************************
- ;* SkipBlk
- ;************************************************************************
-
- include skipblk.asm
-
- ;************************************************************************
- ;* ChrOut
- ;************************************************************************
-
- include chrout.asm
-
-
-
-
- ;************************************************************************
- ;************************************************************************
- ;* *
- ;* Program begins *
- ;* *
- ;************************************************************************
- ;************************************************************************
-
-
- start1:
- call BufInit ; initialize buffers
- call DoArgs ; decode arguments
- call FindPktint ; find the packet driver
- call InitArp ; initialize ARP protocol
- call InitIp ; initilize IP protocol
-
- test ArgFlags,TERM_WAIT+MAKE_TABLE ; if we build tables
- jnz NeedIpOnly
- if PINGCLIENT
- cmp EchoTarget,0 ; or do pinging
- endif ; PINGCLIENT
- jz MustHave
- NeedIpOnly:
- mov EnoughWord,HAVE_MYIPNR ; time things not needed
- MustHave:
- mov dx,Flagword
- and dx,EnoughWord
- cmp dx,EnoughWord ; do we have needed info?
- jne UseBootp
-
- call ValidateIpNr ; - yes. IP # occupied?
- jmp short SkipBootp
- UseBootp:
- call DoBootpPkt ; - no, ask a bootp server
- call InterpBootp
- SkipBootp:
- mov dx,Flagword
- and dx,EnoughWord
- cmp dx,EnoughWord ; do we NOW have needed info?
- je DoTime
-
- mov dx,offset NotEnoughMsg
- mov ah,9
- int 21h
- mov al,07 ; error code 7
- jmp short SkipTime
- DoTime:
- call MakeMynet ; process mask and IP #
-
- cmp EnoughWord,HAVE_MYIPNR
- je DidntGetIt
-
- call GetTime ; ask the time server
- jnz DidntGetIt
- call SetTime ; set the PC clock
- call SetZone ; set zone environment name
- DidntGetIt:
- if TBLBUILD
- call TableInit
- endif ; TBLBUILD
-
- if PINGCLIENT
- call EchoAwhile ; do some ping?
- endif ; PINGCLIENT
- call DelayTermin ; keep it running some more?
- mov al,00 ; error code 0
- SkipTime:
- call terminate
-
- ;************************************************************************
- ;************************************************************************
- ;* End of program *
- ;************************************************************************
- ;************************************************************************
-
-
-
- ;************************************************************************
- ;* DoArgs
- ;************************************************************************
-
-
- ArgTabEnt struc
- ArgTabNam db 'a' ; first char of arg name
- ArgTabAdr dw 0 ; arg name handler
- ARGTABLEN equ $-ArgTabNam
- ArgTabEnt ends
-
- ArgTab ArgTabEnt <'a', offset ArgAlter>
- ArgTabEnt <'d', offset ArgDls>
- if PINGCLIENT
- ArgTabEnt <'e', offset ArgEcho>
- endif ; PINGCLIENT
- ArgTabEnt <'f', offset ArgFlag>
- ArgTabEnt <'g', offset ArgGwy>
- ArgTabEnt <'i', offset ArgIpnr>
- ArgTabEnt <'m', offset ArgMask>
- if TBLBUILD or PINGCLIENT
- ArgTabEnt <'n', offset ArgNameserv>
- endif ; TBLBUILD or PINGCLIENT
- ArgTabEnt <'o', offset ArgOffset>
- ArgTabEnt <'p', offset ArgPktIntNo>
- ArgTabEnt <'t', offset ArgTimeserv>
- ArgTabEnt <'z', offset ArgZoneNam>
- ArgTabEnd equ $
-
- DoArgs proc near
- mov si,offset phd_dioa
- lodsb
- xor ah,ah
- mov bp,ax
- add bp,si ; end of args
- call skip_blanks
- cmp al,CR ; no args?
- je ArgError ; - yes, display usage msg
-
- NextArg:
- call skip_blanks
- cmp si,bp
- ja ArgError
-
- or al,020h ; conv to lower case
-
- cmp al,'b' ; bootp only, no args
- je DoArgRet
-
- cmp al,CR+020h ; end
- je DoArgRet
-
- mov bx,offset ArgTab-ARGTABLEN
- ArgFindLoop:
- add bx,ARGTABLEN
- cmp bx,offset ArgTabEnd
- jae ArgError
- cmp al,[bx] ; first char of arg name
- jne ArgFindLoop
-
- call SkipPastEq ; skip rest of name
- inc bx
- call [bx] ; process arg
- jz NextArg ; look for next arg
-
- ArgError:
- mov dx,offset usage_msg
- error:
- mov ah,9
- int 21h ; display usage message
- mov ax,4c01h ; error code 1
- int 21h ; terminate program
- DoArgRet:
- if DEBUG
- xor ax,ax
- mov word ptr phd_dioa,ax
- mov word ptr StackLow,ax
- endif ; DEBUG
- ret
- DoArgs endp
-
-
-
- ArgAlter:
- or word ptr Flagword,DONT_SETTIME ; alter time
- mov di,offset AlterTime
- mov cl,2
- call GetNums
- mov AlterTime+4,dx
- ret
-
- ArgDls:
- cmp al,'9' ; daylight saving algorithm
- jbe ArgGetAlgPar
- lodsw
- mov dx,ax
- lodsw
- mov di,offset AlgTab-AlgEntryLen
- cmp ah,CR
- jne ArgNextDls
- mov ah,' '
- dec si
- ArgNextDls:
- add di,AlgEntryLen
- cmp di,offset AlgTabEnd-1
- ja ArgDlsRet
- cmp dx,[di]
- jne ArgNextDls
- cmp ax,[di+2]
- jne ArgNextDls
- mov AlgPtr,di
- ret
- ArgGetAlgPar:
- mov di,offset AlgTab
- mov AlgPtr,di
- add di,4
- mov cl,5
- call GetNums
- ArgDlsRet:
- ret
-
- if PINGCLIENT
- ArgEcho:
- cmp al,'A'
- jae ArgEchoName
-
- mov di,offset EchoTarget ; echo to a target (ping)
- call GetIpNr
- jnz ArgEchoRet
- ArgEchoMore:
- cmp byte ptr [si],','
- jne ArgGoodRet
- inc si
- mov cl,1
- call GetNums
- jmp short ArgEchoMore
- ArgEchoRet:
- ret
-
- ArgEchoName:
- mov byte ptr EchoTarget,127 ; marker to do dns lookup
- mov bx,offset EchoNameBuf
- lea di,[bx+1]
- xor cx,cx
- ArgEchoLoop:
- lodsb
- cmp al,' '
- je ArgEchoNamEnd
- cmp al,CR
- je ArgEchoNamEnd
- cmp si,bp
- ja ArgEchoRet
- cmp al,','
- je ArgEchoNamEnd
- cmp al,'.'
- jne ArgEchoNamChar
- mov [bx],cl ; prepend length to string
- mov cx,-1
- mov bx,di
- ArgEchoNamChar:
- stosb
- inc cx
- jmp short ArgEchoLoop
-
- ArgEchoNamEnd:
- mov [bx],cl ; prepend length to string
- xor ax,ax
- stosb
- inc ah
- stosw ; store type and class
- stosw
- dec si
- mov di,offset EchoTarget+4
- jmp short ArgEchoMore
- endif ; PINGCLIENT
-
- ArgFlag:
- call GetNum
- or ArgFlags,ax ; set arg flags
- ArgGoodRet:
- xor ax,ax
- ret
-
- ArgGwy:
- mov di,offset DefGwys ; defult gateways
- mov cx,MAXDEFGWYS
- call GetIpNums
- mov DefGwyNum,ax
- ret
-
- ArgIpnr:
- or Flagword,HAVE_MYIPNR ; my ip nr
- mov di,offset MyIpNr
- call GetIpNr
- ret
-
- ArgMask:
- mov di,offset MyMask ; net mask
- call GetIpNr
- ret
-
- if TBLBUILD or PINGCLIENT
- ArgNameserv:
- mov di,offset DefNS ; defult nameservers
- mov cx,MAXDEFNS
- call GetIpNums
- mov DefNSnum,ax
- ret
- endif ; TBLBUILD or PINGCLIENT
-
- ArgOffset:
- or Flagword,HAVE_TIMEOFFSET
- call GetNum ; time offset
- xchg ah,al
- xchg dh,dl
- mov tzoffset,dx
- mov tzoffset+2,ax
- ret
-
- ArgPktIntno:
- call GetNum ; packet int number
- mov word ptr packet_int_no,ax
- ret
-
- ArgTimeserv:
- or Flagword,HAVE_TIMESERVER ; time server
- mov di,offset TimeServIpNr
- mov cx,MAXTSERVS
- call GetIpNums
- mov TservNum,ax
- ret
-
- ArgZoneNam:
- or GenFlags,ARGZONE ; set zone env variable
- cmp al,'#'
- jne ArgZonePar
- inc si
- jmp short ArgGoodRet
- ArgZonePar:
- or GenFlags,ARGZONESPEC
- mov dl,05fh ; convert to upper case for name
- mov di,offset ZoneString
- mov cx,di
- add cx,ZONESPACE-2
- ArgZoneCopyNext:
- lodsb ; get next arg char
- cmp al,' ' ; end of field?
- je ArgZoneCopyRet
- cmp al,CR
- je ArgZoneCopyRet
- cmp si,bp ; beyond argument string?
- ja ArgZoneCopyErr
- cmp di,cx ; too long name?
- jae ArgZoneCopyErr
- cmp al,'=' ; start of value part?
- jne ArgZoneCopy2
- mov dl,0ffh ; any case allowed for 1st value
- mov bx,di
- sub bx,offset ZoneString-1
- mov ZoneVarLen,bx ; save env name length
- ArgZoneCopy2:
- cmp al,',' ; second value part?
- jne ArgZoneCopy3
- and dl,07fh ; any case allowed for 2nd value
- xor ax,ax
- stosw ; end of string marker
- mov al,'$' ; char for print stop
- stosb
- mov bx,di
- sub bx,offset ZoneString
- mov ZoneDstInd,bx ; remember where 2nd value starts
- jmp short ArgZoneCopyNext
- ArgZoneCopy3:
- and al,dl ; possibly convert to upper case
- stosb
- jmp short ArgZoneCopyNext
- ArgZoneCopyRet:
- dec si
- cmp dl,07fh ; seen two value parts?
- jne ArgZoneCopyErr
- xor ax,ax
- stosb ; end of string marker
- ret
-
- ArgZoneCopyErr:
- inc si ; nonzero ret
- ret
-
-
-
- ;************************************************************************
- ;* GetTime
- ;*
- ;* This code first does one turn to query the timeservers to see if any
- ;* one responds within half a second. If none has responded it will do a
- ;* second turn giving each server 2 seconds to respond. As soon as a time
- ;* reply from any server arrives, it stops.
- ;************************************************************************
-
- GetTime proc near
- call BufAlloc
- call MakeSendDescr
- mov [bx].fBotStruc.uUdpDst,2500h ; 37 = time port
- mov [bx].fBotStruc.uUdpSrc,4321 ; my port
- mov [bx].dTickTimeout,10 ; 10/18 second
- mov [bx].dWaitEvent,GOT_TIMEREPLY
- mov [bx].dTimOut2Msg,offset NoTimeServMsg ; timeout msg
- mov [bx].dTick2Timeout,2*18
- mov dx,offset TservNum
- mov [bx].dPktlen,UDPHDRLEN
- call SendUdpFind ; send time requset
- call BufRelease
- ret
- GetTime endp
-
-
- ;========================================================================
- include settime.asm
-
-
-
- ;************************************************************************
- ;* SearchAndSub
- ;*
- ;* Find lowest index table entry with value (in seconds) <= DX,AX
- ;* and subtract off table value from DX,AX.
- ;************************************************************************
-
- SearchAndSub proc near
- call BinSearch
- call AfterSearch
- ret
- SearchAndSub endp
-
-
-
- BinSearch proc near
- push bx
- mov bx,cx ; compute power of 2
- mov cx,4 ; table size
- BinLenLoop:
- shl cx,1
- cmp cx,bx
- jb BinLenLoop
-
- mov bx,cx ; start binary search
- BinLess:
- sub bx,cx
- BinGreater:
- shr cx,1
- cmp cx,4
- jb BinDone ; no match return
-
- add bx,cx
- cmp dx,2[si+bx]
- BinEval:
- ja BinGreater
- jb BinLess
-
- cmp ax,[si+bx]
- ja BinGreater
- jb BinLess
- BinDone:
- mov cx,bx ; save table index
- lea si,[si+bx] ; and table entry address
- pop bx
- ret
- BinSearch endp
-
-
-
- AfterSearch proc near
- sub ax,[si] ; subtract seconds
- sbb dx,2[si] ; by table value
- shr cx,1 ; calculate table index
- shr cx,1
- ret
- AfterSearch endp
-
-
-
- ;**********************************************************************
- ;
- ; Timezone environment handling
- ;
- ;**********************************************************************
-
- comment |
- ==========
- tech.notes/pc.code #29, from pmaupin, 3407 chars, Sat Jun 4 22:40:45 1988
- ----------
- TITLE: Finding DOS's master environment pointer
- This is a fragment of code that my SD.COM program uses to find
- the environment. This fragment is different than most ways of
- finding the environment, in that it finds the MASTER environment block,
- not the current process's parent's environment.
-
- This is useful in some cases, and has the added advantage that
- it does NOT behave differently when executing under CodeView,
- so you do NOT have to hard-code your system's DOS environment address
- into your program in order to debug it.
- |
-
- EnvPtr EQU 2CH ; Offset in PSP
-
- CommandInterrupt EQU 2EH ; entry point into first Command.Com
- ; through interpreter
-
- DosSegPtr EQU CommandInterrupt * 4 + 2
-
-
- ; FindEnvironment is passed:
-
- ; DS should point to program PSP
-
- ; FindEnvironment returns:
-
- ; ES points to master environment block, or program's copy if couldn't
- ; find the master.
-
- ; CX is length of block, or 0 if couldn't find the master.
-
- ; FindEnvironment destroys:
-
- ; AX, SI
-
-
- FindEnvironment PROC NEAR
- xor si,si ; Point to segment 0
- mov es,si
- mov si, word ptr es:[DosSegPtr]
- mov ax,si
- call VerifyBlock ; make sure we've found COMMAND
- jnz GotBlock ; jump if not a good block --
- ; use process's environment
-
- mov ax,es:[EnvPtr+10h] ; get COMMAND's environment ptr
- or ax,ax ; jump if COMMAND has a
- jnz MaybeGoodBlock ; subsidiary environment
-
- mov ax,si ; If no subsidiary, just use
- add ax,cx ; the allocation block
- inc ax ; immediately after COMMAND
-
- MaybeGoodBlock: call VerifyBlock ; verify that we have a good
- ; one, one way or another
- GotBlock:
- shl cx,1 ; multiply by 16 to get
- shl cx,1 ; length in bytes
- shl cx,1
- shl cx,1
- mov es,ax
- ret
-
-
- ; VerifyBlock tries to insure that we're pointing to a valid DOS
- ; allocation block. If not, returns the current process's environment
- ; block.
-
-
- VerifyBlock PROC NEAR
- dec ax ; get block header into ES
- mov es,ax
- inc ax
-
- cmp byte ptr es:[0],04Dh ; make sure signature is valid
- jnz UseCurrent
- cmp word ptr es:[1],si ; make sure owner is valid
- jnz UseCurrent
- mov cx, word ptr es:[3] ; retrieve the length
- ret
-
- UseCurrent: mov ax,word ptr ds:[EnvPtr] ; get current process's env
- xor cx,cx ; zero length
- ret
- VerifyBlock ENDP
-
- FindEnvironment ENDP
-
- comment |
- So far, this seems to work. I would welcome any feedback on its
- efficacy, but if the feedback is negative, please give the DOS version
- and a detailed problem description. Thanks,
- Pat
- |
-
- ZoneMsg db CR, LF, "Environment variable "
- ZoneString db "TZ=+0100",0,0,"$ "
- ZONESPACE equ $-ZoneString
- ZoneVarLen dw 3
- ZoneStrLen dw 10
- ZoneDstInd dw 10
-
- ;************************************************************************
- ;* SetZone
- ;*
- ;************************************************************************
-
- SetZone proc near
- test GenFlags,ARGZONE ; anything to SET?
- jnz SetZoneInfo
- ret
-
- SetZoneInfo:
- cld
- test GenFlags,ARGZONESPEC ; extended syntax?
- jnz SetZoneSpecial
-
- mov ax,DstAdvance ; -no, use numeric zones
- xor dx,dx ; compute current time offset
- mov cx,tzoffset
- xchg ch,cl
- mov bx,tzoffset+2
- xchg bh,bl
- sub ax,bx
- sbb dx,cx
- mov cl,'+'
- jns ZonePositive ; current time offset sign?
- mov cl,'-'
- not ax ; take absolute value
- not dx
- add ax,1
- adc dx,0
- ZonePositive:
- mov di, offset ZoneString
- add di,ZoneVarLen
- mov [di],cl
- div mhour ; compute hours
- push ax
- mov ax,dx
- div m60b ; and minutes
- xor ah,ah
- mov di,offset ZoneString+3
- add di,ZoneVarLen
- call PutNumD2 ; put minutes
- pop ax
- sub di,4
- call PutNumD2 ; put hours
- jmp short EnvMaster
-
- SetZoneSpecial:
- test GenFlags,DSTNOW ; is it normal or dls time?
- jz EnvMaster
- mov di,offset ZoneString ; -dls, copy dls name
- mov si,di ; on top of normal name
- add di,ZoneVarLen
- add si,ZoneDstInd
- SetZoneLoop:
- lodsb
- stosb
- cmp al,0
- jne SetZoneLoop
- stosb
- mov al,'$'
- stosb
- sub di,offset ZoneString+1
- mov ZoneStrLen,di
- EnvMaster:
- call FindEnvironment ; Find master environment
-
- xor di,di
- xor al,al
- EnvNext:
- jcxz EnvNotFound
-
- test FlagWord,DONT_SETTIME
- jnz EnvZonePr
- push cx ; look for TZ=
- push di
- mov cx,ZoneVarLen
- mov si,offset ZoneString
- repe cmpsb
- jnz EnvNoMatch
-
- pop di ; if found, remove whole string
- pop cx
- push cx
- push di
- repne scasb
- mov si,di
- pop di
- push di
- push es
- pop ds
- rep movsb
- push cs
- pop ds
- EnvNoMatch:
- pop di
- pop cx
-
- cmp byte ptr es:[di],0 ; end of strings?
- je EnvEnd
- repne scasb ; -no, skip past this string
- jmp short EnvNext
- EnvEnd:
- cmp cx,ZoneStrLen ; add TZ string to the end
- jb EnvNotFound
- mov cx,ZoneStrLen
- mov si,offset ZoneString
- rep movsb
-
- EnvZonePr:
- mov dx,offset ZoneMsg
- push cs
- pop ds
- mov ah,9
- int 21h ; display env var contents
-
- EnvNotFound:
- push cs ; restore ds and es
- push cs
- pop ds
- pop es
- ret
- SetZone endp
-
-
-
- ;************************************************************************
- ;* DelayTermin
- ;************************************************************************
-
- DelayTermin proc near
- if RFCC
- test ArgFlags,TERM_WAIT+MAKE_TABLE ; want delayed termination?
- jnz DelayLoop
- ret
- DelayLoop:
- call SomeThing2Do ; ARP or ICMP reply
- if PINGCLIENT
- call EchoDisplay ; show current values
- endif ; PINGCLIENT
- call AnyKey
- jz DelayLoop ; second key stops receive
- DelayCrLf:
- if PINGCLIENT
- cmp al,ESCAPE
- je DelayNotPing
- cmp MsgEchoSweep,'<' ; show drop size distribution
- jne DelayNotPing
-
- mov cx,(1500-20)/20
- mov si,offset EchoSizeVec+2
- mov word ptr FileBuf,LF*256+CR
- mov PutNumFiller,' '
- mov ax,21
- PingNextRow:
- push cx
- push ax
- mov di,offset FileBuf+2
- mov PutMinDigits,4
- call PutNum
- mov PutMinDigits,2
- mov al,':'
- stosb
- xor bx,bx
- mov cx,20
- PingNextCol:
- push cx
- mov al,' '
- stosb
- lodsw
- add bx,ax
- call PutNum
- pop cx
- loop PingNextCol
-
- or bx,bx
- jz PingNoRow
- mov byte ptr [di],'$'
- mov dx,offset FileBuf
- mov ah,9
- int 21h
- dec PingRowCnt
- jnz PingNoRow
- mov PingRowCnt,22
- PingDispPause:
- call AnyKey
- jz PingDispPause
- cmp al,ESCAPE
- jne PingNoRow
- pop ax
- pop cx
- jmp short DelayNotPing
- PingNoRow:
- pop ax
- add ax,20
- pop cx
- loop PingnextRow
- DelayNotPing:
- endif ; PINGCLIENT
- mov dx,offset CrLf_Msg
- mov ah,9
- int 21h
- if TBLBUILD
- call TableWr ; write HW and IP tbl files
- endif ; TBLBUILD
-
- DelayEnd:
- endif ; RFCC
- ret
- DelayTermin endp
-
-
-
- ;************************************************************************
- ;* AnyKey
- ;************************************************************************
-
- AnyKey proc near
- mov ah,06h
- mov dl,0ffh
- int 21h ; any key pressed?
- ret
- AnyKey endp
-
-
-
- if PINGCLIENT
- ;========================================================================
- include ping.asm
- endif ; PINGCLIENT
-
-
-
- if TBLBUILD or PINGCLIENT
-
- NsStruc struc
- uNsUdpHdr UdpStruc <>
- uNsId dw 0
- uNsOpwd dw 0001h ; do recursion
- uNsQdcount dw 0100h ; one question
- uNsAncount dw 0
- uNsNscount dw 0
- uNsArcount dw 0
- uNsQuest equ $-uNsUdpHdr
- NsStruc ends
-
- ;************************************************************************
- ;* NameDecode
- ;*
- ;* Find end of name and change length bytes to dots
- ;************************************************************************
-
- NameDecode proc near
- lodsb
- mov byte ptr [si-1],' ' ; blank 1st length byte
- jmp short NameDcTst
- NameDcLoop:
- lodsb
- mov byte ptr [si-1],'.' ; change length byte to dot
- NameDcTst:
- cmp al,0c0h ; compressed?
- jb NameDcNorm
- mov byte ptr [si],' '
- inc si
- ret
- NameDcNorm:
- mov ah,al
- or al,al ; end of name?
- jz NameDcRet ; -yes, return
- NameDcSkip:
- lodsb ; -no, skip over string
- or al,al ; bad syntax?
- jz NameDcRet ; -yes, better return now
- dec ah ; -no, continue skiping
- jnz NameDcSkip
- jmp short NameDcLoop
- NameDcRet:
- ret
- NameDecode endp
-
-
-
- ;************************************************************************
- ;* NsResolve
- ;*
- ;* Input: DX = my udp port
- ;* AX = Ns Id
- ;* SI = address of querry string
- ;************************************************************************
-
- MsgResolve db "no response.$"
-
- NsResolve proc near
- push bx
- call BufAlloc ; get a big buf
- mov cx,SERRNOBUF
- jz NsResErr
-
- call MakeSendDescr
- mov [di].uUdpDst,3500h
- mov [di].uUdpSrc,dx
- mov [di].uNsId,ax
- xor ax,ax
- mov [di].uNsOpwd,1 ; recursion desired
- mov [di].uNsQdcount,0100h ; 1 question
- mov [di].uNsAncount,ax
- mov [di].uNsNscount,ax
- mov [di].uNsArcount,ax
- mov [bx].dTick2Timeout,14*18 ; give him 14 seconds 2nd turn
- mov [bx].dTimOut2Msg,ax
- mov [bx].dWaitEvent,GOT_NSREPLY
- cmp dx,1234h
- je NsTableBuild
-
- ;*test mov [bx].dWaitEvent,GOT_NSREPLY
- mov [bx].dTickResend,4*18 ; resend after 4 seconds
- mov [bx].dTickTimeout,2*18 ; give him 2 seconds 1st turn
- mov [bx].dTimOut2Msg,offset MsgResolve
- NsTableBuild:
- lea di,[di].uNsQuest ; copy question
- NsQloop:
- lodsb
- stosb
- or al,al
- jnz NsQloop
-
- movsw ; copy type and class
- movsw
-
- mov ax,di ; compute udp data length
- mov si,[bx].dPtrUdp
- sub ax,si
- mov [bx].dPktLen,ax
-
- mov dx,offset DefNsNum
- call SendUdpFind ; send pkt
- NsResOK:
- call BufRelease
- NsResErr:
- or cx,cx
- pop bx
- ret
- NsResolve endp
-
-
-
- ;************************************************************************
- ;* DoNsInterp
- ;************************************************************************
-
- DoNsInterp proc near
- cld
- push cs
- pop es
- mov di,[bx].dPtrUdp
- test [di].uNsOpwd,0080h ; reply?
- jnz NameResReply
- ret
-
- NameResReply:
- if TBLBUILD
- cmp [di].uUdpDst,1234h ; to the tblbuilder?
- jne DoNsIntPing
- jmp DoName
- endif ; TBLBUILD
- DoNsIntPing:
- mov cx,[di].uNsAncount
- xchg ch,cl
- cmp cx,1 ; any answers?
- jb NameResNoAnswer
-
- lea si,[di].uNsQuest
- call NameDecode ; decode question string
- add si,4 ; skip over type and class
- NsAnsLoop:
- call NameDecode ; decode answer string
- mov ax,[si] ; get type
- add si,9 ; skip over junk
- cmp ax,0100h ; address?
- je NsAnsAddr
-
- lodsb
- xor ah,ah
- add si,ax ; skip over data bytes
- loop NsAnsLoop
-
- jmp short NameResNoAnswer
- NsAnsAddr:
- cmp byte ptr [si],4 ; 4 IP bytes here?
- jne NameResNoAnswer
-
- inc si ; copy IP number
- mov di,offset EchoTarget
- movsw
- movsw
- NameResNoAnswer:
- or Events,GOT_NSREPLY ; note we've got ns reply
- ret
- DoNsInterp endp
-
- endif ; TBLBUILD or PINGCLIENT
-
-
-
- if TBLBUILD
- ;========================================================================
- include tblbuild.asm
- endif ; TBLBUILD
-
- ;************************************************************************
- ;* Receive buffers *
- ;************************************************************************
-
- even
- AdrBootpReply dw 0 ; save address of bootp reply
-
- FreeBufs LinkHead <offset FreeBufs,offset Freebufs> ; head of free buffer chain
- FreeSmal LinkHead <offset FreeSmal,offset FreeSmal> ; head of free buffer chain
- SendToDo LinkHead <offset SendToDo,offset SendToDo> ; arp reply list
-
- if RFCC
- IcmpToDo LinkHead <offset IcmpToDo,offset IcmpToDo> ; icmp reply list
- FragList LinkHead <offset FragList,offset FragList> ; fragm reassembly
- endif ; RFCC
-
- if TBLBUILD
- TblToDo LinkHead <offset TblToDo, offset TblToDo> ; build hw addr tbl
- endif ; TBLBUILD
-
- if TBLBUILD or PINGCLIENT
- NameToDo LinkHead <offset NameToDo,offset NameToDo> ; name server replies
- endif ; TBLBUILD or PINGCLIENT
-
- EchoNameBuf equ $
- EchoSizeVec equ EchoNameBuf
- EchoSizeEnd equ EchoSizeVec+2*1500
- BlockAdj = (EchoSizeEnd-CodeOrg) and 0ffh
-
- FileBuf equ EchoSizeEnd+256-BlockAdj
- BufStart equ FileBuf+128 ; buffer pool space
-
- BufStartSml equ BufStart + NBUFS*BUFSIZE
- BufEnd equ BufStartSml + NBUFSMALL*BUFSIZESML
-
- org 0ff30h ; from here to ffff is
- StackLow equ $ ; non interrupt stack space
-
- code_s ends
- end start
-
- ;************************************************************************
- ;* *
- ;* This is the end *
- ;* *
- ;************************************************************************
-