home *** CD-ROM | disk | FTP | other *** search
-
- PAGE 44,132
-
- ; Copyright (C) 1991-94 by Jan.Engvald@ldc.lu.se, see file COPYING.
-
- ;========================================================================
- include pdtstnet.doc
- ;========================================================================
-
- ESCAPE equ 27
- RFCC equ TBLBUILD+PINGCLIENT ; RFC compliance needed
- MAXHOP equ 64 ; must be 64
- REPVECLEN equ 512 ; any power of two
-
- if TBLBUILD
- PROGSTR equ 'pdtstnet'
- elseif PINGCLIENT
- PROGSTR equ 'pdclkset'
- else
- PROGSTR equ 'pdclksml'
- 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:nothing, ss:code_s, es:nothing
-
- org 0
- CodeOrg label byte
- PspInt20 dw ?
- PspTopMem dw ?
-
- org 5Ch ; PSP can be reused for data from here
-
- org 80h ; PSP command parameter area
- phd_dioa db ?
- db ? ; always a space
- phd_string db ?
-
-
- ;************************************************************************
- ;* Start of segment (code) *
- ;************************************************************************
-
- .8086
- 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-94 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 PROGSTR," [o[ffset]=time] (time is [-|+][<hours>h][<minutes>m][<seconds>[s]])", CR, 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
- db " [m[ask]=n.n.n.n g[ateway]=n.n.n.n[,n.n.n.n[,...]]] [f[lags]=flagnr]", CR, LF
- db " [z[onename]= # | variable=normalname,dlsname] [a[lter]=days,time]", CR, LF
- db " [p[ktintno]=hexnr]"
-
- if PINGCLIENT or TBLBUILD
- db " [e[cho]=name|n.n.n.n [,size,interval[,data,inc,min]]]", CR, LF
- db " [u[dpecho]=name|n.n.n.n [,size,interval[,data,inc,minsize]]]", CR, LF
- if HOPCHK
- db " [h[opcheck]=name|n.n.n.n [,size,interval[,data,inc,minsize,maxhop]]]", CR, LF
- endif ; HOPCHK
- db " [n[ameserver]=n.n.n.n[,n.n.n.n[,...]]]"
- endif ; PINGCLIENT or TBLBUILD
-
- db " [l[ongertimeout]=time]", 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
- if HOPCHK
- db CR, LF, " ",PROGSTR," hopcheck= ftp.lu.se (trace route)"
- endif ; HOPCHK
- db CR, LF, " ",PROGSTR," flags= 2+4 (address table builder for LANwatch)"
- endif
-
- crlf_msg db CR, LF, '$'
-
- if DEBUG
- MsgErrDet db CR, LF, 7
- db " ax dx cx si ds bx di es bp "
- db " addr stack...", CR, LF
- MsgErrAdr db "0000/0000/0000/0000/0000/0000/0000/0000/0000"
- db " 0000 0000 0000 0000 0000 0000 0000"
- endif ; DEBUG
-
- 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
- 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 ; 0x0001
- NOT_SAFE equ 1 ; 0x0001
- MAKE_TABLE equ 2 ; 0x0002
- LANW_TABLE equ 4 ; 0x0004
- TBL_PROBE equ 8 ; 0x0008
- AVOID_HDWR equ 16 ; 0x0010
- MICRO_100 equ 32 ; 0x0020
- UDP_DISCARD equ 64 ; 0x0040
- QUIET_TERM equ 128 ; 0x0080
- IP_15DIG equ 256 ; 0x0100
- UPCALL_SEND equ 512 ; 0x0200
- STOP_ON_ERR equ 1024 ; 0x0400
- ; 0x0800
- TR_GIANT equ 4096 ; 0x1000
- ; 0x2000
- NOT_ALL_MEM equ 04000h
- TEMP_TEST equ 08000h ; 0x8000
-
-
- MAXTSERVS equ 4
- ARPSLOTS equ 8 + 4*TBLBUILD
- ROUTESLOTS equ 5
- MAXDEFGWYS equ 4 + 6*TBLBUILD
- MAXDEFNS equ 3
-
- ifdef SMALLBUFS
- NBUFSMALM equ 24 ; at least so many small bufs
- else
- NBUFSMALM equ 0 ; at least so many small bufs
- endif
-
- ;========================================================================
- include bufs.inc
-
-
- ;========================================================================
- include arp.inc
-
-
- ;========================================================================
- include ip.inc
-
-
- ;========================================================================
- include settime.inc
-
-
- if PINGCLIENT
- ;========================================================================
- include ping.inc
-
- endif ; PINGCLIENT
-
-
- if TBLBUILD
- ;========================================================================
- include tblbuild.inc
- endif ; TBLBUILD
-
-
-
- ;**********************************************************************
- ;*
- ;* 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)
-
-
- if DEBUG ge 3
-
- CHK_ES_EQ_DS macro
- call ChkEsEqDs
- endm
-
- ChkEsEqDs proc near
- push ax
- push dx
- mov ax,es
- mov dx,ds
- cmp ax,dx
- jne ChkESeqErr
-
- pop dx
- pop ax
- ret
- ChkEsEqDs endp
-
- ChkEsEqErr:
- mov al,'z'-'0'
- call Terminate
-
- else
-
-
- CHK_ES_EQ_DS macro
- endm
-
- endif ; DEBUG ge 3
-
-
- If DEBUG ge 2
- ; This debug routine destroys no registers and needs only 3 bytes at each
- ; place called. It will put on the screen a one-line summary of which events
- ; that have ever occured and then some lines with the last sequence of events.
- ; The macro is called like
- ; SHOW_EVENT 'A'
- ; and you can use one argument in the range from MINEVENT to MAXEVENT below.
-
- MINEVENT equ 'A'
- MAXEVENT equ 'o'
- EVENTCOLOR equ 3eh
- EVENTLINE equ 8
- TRACECOLOR equ 24h
-
- ShowEvent proc near
- x = 0
- rept (MAXEVENT-MINEVENT+1)
- push ax
- mov al,x
- jmp ShowEventNum
- x = x+1
- endm
-
- ShowEventNum:
- pushf
- push di
- push es
- mov ah,EVENTCOLOR
- mov di,ax
- shl di,1
- add al,MINEVENT
- mov es,cs:EventPar
- cld
- stosw
-
- mov ah,TRACECOLOR
- mov es,cs:TracePar
- cli
- mov di,cs:TraceInd
- stosw
- and di,03ffh ; (3ff+1)/2 = 512 log entries
- mov cs:TraceInd,di
- mov al,01bh
- not ah
- stosw
-
- pop es
- pop di
- popf
- pop ax
- ret
- ShowEvent endp
-
- even
- EventPar dw 0b800h+(EVENTLINE-1)*10-2*EVENTCOLOR*16
- TracePar dw 0b800h+EVENTLINE*10
- TraceInd dw 0
-
- endif ; DEBUG ge 2
-
- if DEBUG ge 3
- SHOW_EVENT macro id
- if id gt MAXEVENT or id lt MINEVENT
- .err
- endif
- call ShowEvent+((id-MINEVENT)*(ShowEventNum-ShowEvent)/(MAXEVENT-MINEVENT+1))
- endm
-
- else
-
- SHOW_EVENT macro num
- endm
-
- endif ; DEBUG ge 3
-
- if DEBUG ge 2
- SHOW_TRACE macro id
- if id gt MAXEVENT or id lt MINEVENT
- .err
- endif
- call ShowEvent+((id-MINEVENT)*(ShowEventNum-ShowEvent)/(MAXEVENT-MINEVENT+1))
- endm
-
- else
-
- SHOW_TRACE macro num
- endm
-
- endif ; DEBUG ge 2
-
-
-
- assume ds:nothing
-
- ;========================================================================
- include pktdr.asm
-
- ;========================================================================
- include pkterr.asm
- if RFCC
- ;========================================================================
- include Movesb.asm
- endif ; RFCC
-
- ;========================================================================
- include bufs.asm
-
- ;========================================================================
- include arp.asm
-
-
- ;========================================================================
- include ip.asm
-
-
- ;************************************************************************
- ;* 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
-
- mov ds,cs:Mysegm
- assume ds:code_s
- cld
-
- call Ageing ; clear unused table slots
- if PINGCLIENT or TBLBUILD
- call EchoDisplay ; show current values
- endif ; PIGCLIENT or TBLBUILD
-
- if TBLBUILD
- cmp InSendAndW,0 ; avoid overload
- jne SomethingNxt5
- cmp sp,offset StackLow+13*16
- jb SomethingNxt5
-
- call TblProbe ; do tablebuilding things
- mov di,offset TblToDo
- call GetFromList
- jz SomethingNxt5
- call DoTable
- SomethingNxt5:
- endif ; TBLBUILD
-
- if RFCC
- mov di,offset IcmpToDo ; ICMP or UDP replies to send?
- call GetFromList
- jz SomethingNxt4
-
- mov di,[bx].dPtrIp
- cmp [di].iIpProt,UDP_PROT ; UDP protocol?
- je Udp2Do
-
- call SendIcmpPkt
- jmp short SomeIcmpDone
- Udp2Do:
- mov [bx].dWaitEvent,0 ; don't wait for answer
- call SendUdpPkt
- SomeIcmpDone:
- call BufRelease
- SomethingNxt4:
- endif ; RFCC
- mov di,offset SendToDo ; ARP replies to send?
- call GetFromList
- jz SomethingNxt2
- call SendAndWait
- call BufRelease
- SomethingNxt2:
- if TBLBUILD or PINGCLIENT
- mov di,offset NameToDo ; got nameserver replies?
- call GetFromList
- jz SomethingNxt6
- call DoNsInterp
- call BufRelease
- SomethingNxt6:
- 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
-
-
-
- ;************************************************************************
- ;* PrTerminate
- ;************************************************************************
-
- PrTerminate:
- push cs
- pop ds
- assume ds:code_s
- call DosPr$ ; print error msg
- Terminate:
- if DEBUG
- or cs:GenFlags,DBGSTOP ; ignore upcalls
- push bp
- push es
- push di
- push bx
- push ds
- push si
- push cx
- push dx
- push ax
- endif ; DEBUG
- push cs
- pop ds
- assume ds:code_s
-
- push ax
-
- cld
- push cs
- pop es
- sti
-
- mov bx,IpHandle ; release ARP and IP handles
- call EndProtocol
- mov bx,ArpHandle
- call EndProtocol
- if PINGCLIENT
- cmp EchoTarget,0
- jz TermNoPing
- call RestoreTimer
- TermNoPing:
- endif ; PINGCLIENT
- pop ax
- push ax
- or al,al ; any errors?
- jz termnorm
-
- if DEBUG
- mov PutNumBase,16
- mov PutMinDigits,4
- mov di,offset MsgErrAdr
- mov si,sp
- sub word ptr [si+20],3
- lodsw ; add si,2
- mov cx,16+256*(' ')
- call PutNumsF0 ; show regs
- endif ; DEBUG
-
- cmp EnoughWord,HAVE_MYIPNR ; clock errors?
- je termnorm
-
- mov dx,offset MsgNotSet ; display "clock not set"
- call DosPr$
- termnorm:
-
- pop ax
- push ax
- add al,'0'
- mov MsgTermNr,al ; show error # in end line
-
- cmp al,'0'
- jne showtermsg
- test ArgFlags,QUIET_TERM
- jnz termexit
- showtermsg:
- mov si,offset MyHwAd
- mov di,offset MsgTermHw
- call PutHwNum ; put my HW addr
-
- mov si,offset MyIpNr
- mov di,offset MsgMyIp
- call PutIpNum ; put my IP #
-
- mov dx,offset MsgTerm ; End of PDCLKSET msg
- if DEBUG
- cmp MsgTermNr,'0'
- je TermStdMsg
- mov dx,offset MsgErrDet
- TermStdMsg:
- endif ; DEBUG
- call DosPr$
- termexit:
- pop ax ; error code
- mov ah,4ch
- int 21h ; terminate program
-
-
-
-
- ;************************************************************************
- ;************************************************************************
- ;*
- ;* Input and Output routines
- ;*
- ;************************************************************************
- ;************************************************************************
-
-
- PutNumFiller db '0'
- even
- PutNumBase dw 10
- PutMinDigits dw 2
- k10000 dw 10000
- GetNumBase dw 10
-
- IntTmpHwAd dw 0, 0, 0, 0, 0, 0
- IntTmpIpNr equ IntTmpHwAd
-
-
-
- ;************************************************************************
- ;* DosPr$
- ;************************************************************************
-
- DosPr$ proc near
- assume ds:nothing
- push ax
- mov ah,9 ; print msg in ds:dx
- int 21h
- pop ax
- and cs:GenFlags,not GOT_DSP_ROW
- ret
- DosPr$ endp
-
-
- assume ds:code_s
-
- ;************************************************************************
- ;* SkipPastEq
- ;************************************************************************
-
- SkipPastEq proc near
- mov cx,30 ; max name length
- SkipLook4Eq:
- cmp al,'=' ; look for equal sign
- je SkipFoundEq
-
- lodsb
- loop SkipLook4Eq
- SkipFoundEq:
- call skip_blanks ; blanks may follow
-
- ret
- SkipPastEq endp
-
-
-
- ;************************************************************************
- ;* NegDxAx
- ;************************************************************************
-
- NegDxAx proc near
- not dx ; take negative of number
- not ax
- add ax,1
- adc dx,0
- ret
- NegDxAx endp
-
-
-
- ;************************************************************************
- ;* GetNums
- ;************************************************************************
-
- GetNums proc near
- assume ds:nothing
- 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
- or cx,cx
- jz GetNumsErr
- 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
- GetNumsErr:
- or sp,sp
- GetNumsRet: ; - no, return
- pop bx
- ret
- GetNums endp
-
-
-
- ;************************************************************************
- ;* GetNum
- ;************************************************************************
-
- GetNum proc near
- assume ds:nothing
- push si
- xor dx,dx
- lodsb
- cmp al,'-' ; minus prefix?
- pushf
- je GetNumSign
- cmp al,'+' ; plus prefix?
- jne GetNoPrefix
- GetNumSign:
- lodsb ; get a char
- GetNoPrefix:
- mov cs: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 cs: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 cs: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
-
- call NegDxAx
- GetNumRet:
- pop cx ; si at call
- sub cx,si
- neg cx ; cx = # chars read
- jnz GetNumOkRet
- or sp,sp
- ret
- GetNumOkRet:
- cmp ax,ax ; ensure zero flag
- ret
- GetNum endp
-
-
-
- ;************************************************************************
- ;* GetIpNr
- ;************************************************************************
-
- GetIpNr proc near
- assume ds:nothing
- mov cx,1
- GetIpNums:
- push si ; remember start in case of err
- push cx ; remember how many we wanted
- GetIpCont:
- push cx ; IP #'s left to read
-
- push es
- push cs
- pop es
- push di
- mov cl,4
- mov di,offset IntTmpIpNr
- call GetNumsDot ; read an IP #
- pop di
- pop es
- jnz GetIpNrErr
-
- mov cx,4
- push ds
- push cs
- pop ds
- push si
- mov si,offset IntTmpIpNr
- GetIpNrLoop:
- lodsw ; convert to bytes
- stosb
- loop GetIpNrLoop
-
- pop si
- pop ds
- pop cx ; want more IP #'s?
- loop GetIpMore
- GetIpNrRet:
- pop ax
- sub ax,cx ; ax = IP #'s read
- cmp cx,cx ; zero flag
- pop dx ; dx = original si
- ret
-
- GetIpMore:
- lodsb
- cmp al,',' ; comma separator?
- je GetIpCont
-
- dec si
- jmp short GetIpNrRet
-
- GetIpNrErr:
- pop cx
- pop cx
- pop dx ; original si
- ret ; non-zero return
- GetIpNr endp
-
-
-
- ;************************************************************************
- ;* PutIpNum (4 bytes from DS:SI to decimal at ES:DI)
- ;************************************************************************
-
- PutIpNum proc near
- assume ds:nothing
- 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
- assume ds:code_s
- mov si,offset IntTmpIpNr
- mov ch,'.'
- mov cl,4
- mov PutMinDigits,1
- test ArgFlags,IP_15DIG
- jz PutIpNoZero
- mov PutMinDigits,3
- PutIpNoZero:
- call PutNumsF0 ; put IP #
- pop ds
- ret
- PutIpNum endp
-
-
-
- ;************************************************************************
- ;* PutHwNum
- ;************************************************************************
-
- PutHwNum proc near
- assume ds:nothing
- 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 si
- push ds
- push cs
- pop ds
- assume ds:code_s
- 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
- call PutNumsD2F0 ; put HW #
- mov PutNumBase,10
- pop ds
- pop si
- ret
- PutHwNum endp
-
-
-
- ;************************************************************************
- ;* PutNums
- ;************************************************************************
-
- assume ds:code_s
-
- PutNumsD2F0 proc near
- mov PutMinDigits,2
-
- PutNumsF0: mov PutNumFiller,'0'
-
- 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
- PutNumsD2F0 endp
-
-
-
- ;************************************************************************
- ;* PutNum and PutBigNum
- ;************************************************************************
-
- assume ds:nothing
-
- PutNumD4Fb proc near
- mov cs:PutMinDigits,4
- PutNumFb:
- mov cs:PutNumFiller,' '
- PutNum:
- xor dx,dx
- PutBigNum:
- push ds
- push cs
- pop ds
- assume ds:code_s
- 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
- pop ds
- ret
- PutNumD4Fb endp
-
-
-
- ;************************************************************************
- ;* PutBigNums
- ;************************************************************************
-
- assume ds:code_s
-
- 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 *
- ;* *
- ;************************************************************************
- ;************************************************************************
-
- assume ds:code_s
-
-
- start1:
- call DoArgs ; decode arguments
- call BufInit ; initialize buffers
- call FindPktint ; find the packet driver
- call InitProtocols ; initialize ARP/IP protocols
-
- mov ax,ArgFlags
- and ax,TERM_WAIT+MAKE_TABLE ; if we build tables
- if PINGCLIENT
- or ax,EchoTarget ; or do pinging
- endif ; PINGCLIENT
- jz MustHave
-
- 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 al,07 ; error code 7
- call PrTerminate
- 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?
- xor al,al ; 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
- ArgTabEnt ends
- ARGTABLEN equ SIZE ArgTabEnt
-
- 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>
- if HOPCHK
- ArgTabEnt <'h', offset ArgHop>
- endif ; HOPCHK
- ArgTabEnt <'i', offset ArgIpnr>
- ArgTabEnt <'l', offset ArgLongTimeout>
- ArgTabEnt <'m', offset ArgMask>
- if TBLBUILD or PINGCLIENT
- ArgTabEnt <'n', offset ArgNameserv>
- endif ; TBLBUILD or PINGCLIENT
- ArgTabEnt <'o', offset ArgOffset>
- ArgTabEnt <'p', offset ArgPktIntNo>
- ; suggested: r = ReverseLookup, s = ServiceType (TOS)
- ArgTabEnt <'t', offset ArgTimeserv>
- if PINGCLIENT
- ArgTabEnt <'u', offset ArgUdpecho>
- endif ; PINGCLIENT
- ArgTabEnt <'z', offset ArgZoneNam>
- ArgTabEnd equ $
-
- DoArgs proc near
- cld
- mov si,offset phd_dioa
- lodsb
- xor ah,ah
- mov bp,ax
- add bp,si ; end of args
-
- push si ; substitute : and ; to = and ,
- DoArgSubst:
- lodsb
- cmp al,':'
- jne DoArgChkComma
- mov byte ptr [si-1],'='
- DoArgChkComma:
- cmp al,'/'
- jne DoArgChkCom2
- mov byte ptr [si-1],','
- DoArgChkCom2:
- cmp al,';'
- jne DoArgChkE
- mov byte ptr [si-1],','
- DoArgChkE:
- cmp si,bp
- jb DoArgSubst
- pop si
-
- 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:
- call DosPr$ ; display usage message
- mov ax,4c01h ; error code 1
- int 21h ; terminate program
- DoArgRet:
- xor ax,ax
- mov word ptr StackLow,ax
- if DEBUG
- mov word ptr phd_dioa,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
- k10 dw 10
- if HOPCHK
- ArgHop:
- mov EchoInterval,110
- mov EchoSize,34
- or MoreFlags,HOP_CHK ; hop check (trace route)
- or ArgFlags,MAKE_TABLE ; (it will be removed later)
- endif ; HOPCHK
- ArgUdpEcho:
- or GenFlags,UDP_ECHO ; UDP echo
- ArgEcho:
- mov di,offset EchoTarget ; ICMP echo to a target (ping)
- call GetIpNr
- jnz ArgEchoName
- cmp byte ptr [si],'.'
- je ArgEchoName
- ArgEchoMore:
- cmp byte ptr [si],','
- jne ArgGoodRet
-
- inc si
- mov cl,1
- call GetNums
-
- cmp byte ptr [si],'.'
- jne ArgEchoMore
- inc si
- mul k10
- push ax
- call GetNum
- pop dx
- add ax,dx
- mov [di-2],ax
- or ArgFlags,MICRO_100
- jmp short ArgEchoMore
-
- ArgEchoName:
- mov si,dx ; rescan
- mov byte ptr [di],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
- ArgEchoRet:
- ret
-
- ArgGwy:
- mov di,offset DefGwys ; default 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
-
- ArgLongTimeout:
- call GetNum ; longer timeout
- mul m18
- mov LongerTimOut,ax
- jmp short ArgGoodRet
-
- ArgMask:
- mov di,offset MyMask ; net mask
- call GetIpNr
- ret
-
- if TBLBUILD or PINGCLIENT
- ArgNameserv:
- mov di,offset DefNS ; default 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
- assume ds:code_s
- push es
- push ds
- call BufAlloc
- assume ds:nothing
- call MakeSendDescr
- mov [di].uUdpDst,2500h ; 37 = time port
- mov [di].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
- pop ds
- assume ds:code_s
- pop es
- ret
- GetTime endp
-
-
- ;========================================================================
- include settime.asm
-
-
-
- ;************************************************************************
- ;* DelayTermin
- ;************************************************************************
-
- assume ds:code_s
-
- DelayTermin proc near
- if RFCC
- test ArgFlags,TERM_WAIT+MAKE_TABLE ; want delayed termination?
- jnz DelayLoop
- ret
-
- DelayLoop:
- call SomeThing2Do ; ARP or ICMP reply to do
- if PINGCLIENT
- test GenFlags,PING_DELAY
- jnz DelayLoop
- endif ; PINGCLIENT
- call AnyKey
- jz DelayLoop ; second key stops receive
- DelayCrLf:
- if PINGCLIENT
- if HOPCHK
- test MoreFlags,HOP_CHK
- jnz DelayHopEnd
- endif ; HOPCHK
- cmp al,ESCAPE ; want error size distribution?
- je DelayNotPing
-
- mov word ptr FileBuf,LF*256+CR
- mov cx,(GIANTTR-HWHDRLEN-20)/20
- mov si,offset EchoSizeVec+2
- mov ax,21
- PingNextRow:
- push cx
- push ax
- mov di,offset FileBuf+2
- call PutNumD4Fb
- mov al,':'
- stosb
- xor bx,bx
- mov cx,20
- PingNextCol:
- push cx
- mov PutMinDigits,2
- mov al,' '
- stosb
- lodsw
- or bx,ax
- or ax,ax
- jnz PingNextNZ
- mov ax,'. '
- stosw
- jmp short PingNextCol2
- PingNextNZ:
- jns PingNextVal
- mov byte ptr [di],'-'
- inc di
- neg ax
- dec PutMinDigits
- PingNextVal:
- call PutNum
- PingNextCol2:
- pop cx
- loop PingNextCol
-
- or bx,bx
- jz PingNoRow
- mov byte ptr [di],'$'
- mov dx,offset FileBuf
- call DosPr$
- 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
- call DosPr$
- DelayHopEnd:
- if TBLBUILD
- call TableWr ; write HW and IP tbl files
- endif ; TBLBUILD
-
- endif ; RFCC
- ret
- DelayTermin endp
-
-
-
- ;************************************************************************
- ;* AnyKey
- ;************************************************************************
-
- AnyKey proc near
- if PINGCLIENT
- test ArgFlags,AVOID_HDWR
- jnz AnyKeyDos
-
- push es ; simulates int 21h, ah=06, dl=ff, but faster
- push bx
- mov ax,040h
- mov es,ax
- mov bx,es:[01ch]
- mov es:[01ah],bx ; set head to tail
- cmp bx,es:[080h] ; just wraped around?
- ja AnyKeyPtrOK
- mov bx,es:[082h] ; -yes, unwrap
- AnyKeyPtrOK:
- mov ax,es:[bx-2] ; last char typed
-
- cmp OldkeyPtr,0
- jne AnyKeyInited
- mov OldKeyPtr,bx
- AnyKeyInited:
- cmp bx,OldKeyPtr ; any key pressed?
- mov OldkeyPtr,bx
- if HOPCHK
- jz AnyKeyRet
-
- or al,al
- jz AnyKeySpec
- cmp al,0e0h
- jne AnyKeyGot
- AnyKeySpec:
- inc ScrollVal
- cmp ah,48h ; scroll up?
- je AnyKeyRet
- sub ScrollVal,2
- cmp ah,50h ; scroll down?
- je AnyKeyRet
- inc ScrollVal
- AnyKeyGot:
- or sp,sp
- endif ; HOPCHK
- AnyKeyRet:
- pop bx
- pop es
- ret
-
- OldKeyPtr dw 0
- ScrollVal db 0
- endif ; PINGCLIENT
-
- AnyKeyDos:
- mov ah,06h
- mov dl,0ffh
- int 21h ; any key pressed?
- ret
- AnyKey endp
-
-
-
- if PINGCLIENT
- ;========================================================================
- include ping.asm
-
- endif ; PINGCLIENT
-
-
-
- if TBLBUILD
- ;========================================================================
- include tblbuild.asm
- endif ; TBLBUILD
-
- ;************************************************************************
- ;* Receive buffers *
- ;************************************************************************
-
- even
- if PINGCLIENT
- MsgEchoHead db CR, LF, "Ping with packet size "
- MsgEchoSweep db "<"
- MsgEchoSize db "0 and interval"
- MsgEchoMs db " 0 ms to "
- MsgEchoTarget db "1.2.3.4 : ", CR, LF, LF
- MsgEchoStats db "───────── Packets ──────── ║ ────── Delay ms ────── ║ Packet ║ Load ║ Time ", CR, LF
- db "transmit receive diff ║ this min avg max ║ loss ║ kb/s ║ s ", CR, LF, "$$"
- MsgEcho db " 0 0 0 0 0 0 0 0.0000 % 0 0 ", CR, '$'
- MsgEchoSeqEr equ MsgEcho+26
- MsgEchoTime equ $-11
- MsgEchoLen equ $-MsgEcho-2
- endif ; PINGCLIENT
-
- if HOPCHK
- HopTabDsp equ MsgEchoHead+2+80*2
-
- EchoNameBuf equ HopTabDsp+MAXHOP*80
- else
- EchoNameBuf equ $
- endif ; HOPCHK
-
- EchoRepVec equ EchoNameBuf+80
- EchoSizeVec equ EchoRepVec+REPVECLEN
-
- if HOPCHK
-
- HOPTABLEN equ 48+MAXHOP*(3*4*3)
- HopTabIp equ EchoSizeVec+48
- HopTabOth equ HopTabIp+3*MAXHOP*4
- HopTabStat equ HopTabOth+3*MAXHOP*4
-
- if HOPTABLEN ge 2*(GIANTTR-HWHDRLEN)
- EchoSizeEnd equ EchoSizeVec+HOPTABLEN
- else
- EchoSizeEnd equ EchoSizeVec+2*(GIANTTR-HWHDRLEN)
- endif
-
- BlockAdj = (EchoSizeEnd-CodeOrg) and 0ffh
-
- else
-
- EchoSizeEnd equ EchoSizeVec+2*(GIANTTR-HWHDRLEN)
- BlockAdj = (EchoSizeEnd-CodeOrg) and 0ffh
-
- endif ; HOPCHK
-
- FileBuf equ EchoSizeEnd+256-BlockAdj
-
- BufStart equ FileBuf+128 ; buffer pool space
-
- BufStartSml equ BufStart + NBUFS*BUFSIZE
- ; BufEnd equ BufStartSml + NBUFSMALL*BUFSIZESML
-
- org 0fed0h ; from here to ffff is
- StackLow equ $ ; non interrupt stack space
-
- code_s ends
- end start
-
- ;************************************************************************
- ;* *
- ;* This is the end *
- ;* *
- ;************************************************************************
-