ZXNet эхоконференция «code.zx»


тема: TCP/IP



от: Alexander Kotof
кому: All
дата: 30 Mar 2001

Hi *All*!

.DEVICE ACE1101

;;; webACE Server
;;; A tiny RS232/SLIP/IP/ICMP/TCP/HTTP stack for the Fairchild ACE1101.

;;; Copyright (C) 1999 Fredric M White
;;;
;;; Redistribution and use in source and binary forms, with or without
;;; modification, are permitted provided that the following conditions
;;; are met:
;;; 1. Redistributions of source code must retain the above copyright
;;; notice, this list of conditions and the following disclaimer.
;;; 2. Redistributions in binary form must reproduce the above copyright
;;; notice, this list of conditions and the following disclaimer in the
;;; documentation and/or other materials provided with the distribution.
;;; 3. All advertising materials mentioning features or use of this software
;;; must acknowledge Copyright Holder.
;;; 4. The name of the Copyright Holder may not be used to endorse or promote
;;; products derived from this software without specific prior written
;;; permission.
;;;
;;; THIS SOFTWARE IS PROVIDED "AS IS" AND WITHOUT ANY EXPRESS OR IMPLIED
;;; WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED WARRANTIES OF
;;; MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.

;; The current code tosses packets larger than 255 bytes. This could
;; be fixed, although fixing it should not be necessary if the client
;; TCP obeys our window size.

;; The fun begins in the function "tcpfun". I doubt that it is the
;; perfect TCP response function, but it works well enough for HTTP.

;; Some more bytes could be squeezed out of this code, but I tried to
;; avoid optimizations which would really obfuscate things.

;; You'll need to customize the "login" function, or at least fill
;; in values for "slipuser" and "slippass". As well as adjust the
;; equates for the port bits. Maybe also IP_ADDR_x.

;; The home page is stored in the data eeprom. See end of this file.

;; The baud rate is tuned by typing rubout (0377) chars to the login
;; function. I know this is a bit hokey, but I haven't needed anything
;; better -- the RC oscillator is quite stable over the 15░F range
;; of normal room temperature. Timer1 in input capture mode could
;; be used to accurately time the bit period. I haven't tried it.

;; There may be more info at http://www.geocities.com/fwhite/ace
;; Chip info at http://www.fairchildsemi.com/products/memory/ace

;; If you found this code to be useful, please drop me a note at
;; fmw@pobox.com. Have fun.
;
;; STATUS register bits
Ready EQU 7
Global EQU 4
Zero EQU 3
Carry EQU 2
Half EQU 1
Neg EQU 0

;; Timer1 control bits
T1EN EQU 2 ; Timer 1 interrupt enable bit
T1PND EQU 3 ; Timer 1 pending bit
T1C0 EQU 4 ; Timer 1 start bit

;; Random constants
CR EQU 0Dh
LF EQU 0Ah

;; Port bits
CTS equ 0 ; G0 (o)
REDLED equ 1 ; G1 (o)
FREE equ 2 ; G2 (o)
RXD equ 3 ; G3 (i)
TXD equ 4 ; G4 (o)
GRNLED equ 5 ; G5 (o)

;; All outputs initially, except RXD.
PortCfg equ (1 shl GRNLED) or (1 shl TXD) or (1 shl FREE) or (1 shl
REDLED) or (1 shl CTS)

;; Outputs are initially 1, except LEDs
PortDat equ (1 shl TXD) or (1 shl FREE) or (1 shl CTS)

;; EEPROM (must keep in sync with data eeprom -- see end of this file)
webdata EQU 40h ; Web page data
weblen EQU 3Fh ; Web page length
ledurl EQU 66h ; Address of LED URL byte
ledstr EQU 6Ah ; Address of LED on/off string
(second char thereof)
hitcnt EQU 7Dh ; Address of hit count (last digit
thereof)
baud EQU 7Fh ; baud rate adjust (last byte of ee)

;; RAM
BufLen EQU 16 ; A PC is to CTS as a Boston driver
is to a red light.
buf EQU 00h ; Serial receive buffer [16]
bufptr EQU 10h
bufcnt EQU 11h

tmp EQU 12h ; Temporary
tmpX EQU 13h ; Temporary
cnt EQU 14h ; Loop counter

;; IP vars
ckcnt EQU 15h ; Byte number (after de-SLIPing) 1
origin
ckeoc EQU 16h ; End-around-carrys (256 words
worth)
ckhi EQU 17h ; High byte of checksum
cklo EQU 18h ; Low byte of checksum
iplen EQU 19h ; IP total length (one byte)
ipproto EQU 1Ah ; ICMP=1, TCP=6, UDP=17
ipsrc EQU 1Bh ; Source IP address [4]
pkts EQU 1Fh ; Used for ident field

;; TCP vars
srcport EQU 20h ; Source port [2]
dstport EQU 22h ; Dest port (opt: high byte) [2]
seqnum EQU 24h ; Sequence number [4]
acknum EQU 28h ; Acknowledgement number [4]
dataoff EQU 2Ch ; Data offset (in high 4 bits)
tcpflgs EQU 2Dh ; TCP flags

tcplen EQU 2Eh ; TCP data length
url EQU 2Fh ; One-character URL

;; Equivalences
ack EQU acknum+3 ; Low byte of ACK (all that we use)
tcpBufLen EQU 14
tcppkt EQU srcport ; Contiguous 14-byte buffer

;;-----------------------------------------------------------------
;; start -- Start of execution
;;-----------------------------------------------------------------

start ld PORTGD,#PortDat
ld PORTGC,#PortCfg

clr X ; 1,1 Wait for I/O's to stabilize (5ms)
lp inc X ; 1,1
iflt X,#3FEh ; 3,3
jp lp ; 1,1

clr pkts ; todo: optional
clr bufcnt ; NOT optional!

jsr login ; SLIP login
jsr ledoff ; Green LED off, and sync eeprom

server ld SP,#0Fh ; todo: optional
sbit REDLED,PORTGD ; REDLED off
jsr ip ; Top-level protocol
jsr slipend ; Mark end of reply
inc pkts ; Count
jp server

;; ------------------------------------------------------------
;; IP
;; ------------------------------------------------------------

;; Our IP address
IP_ADDR_0 EQU 192
IP_ADDR_1 EQU 168
IP_ADDR_2 EQU 1
IP_ADDR_3 EQU 10

IP_VERS EQU 045h ; IP version and IHL
IP_DF EQU 040h ; Don't Fragment (bit mask in byte)
IP_MF EQU 020h ; More Fragments (bit mask in byte)
IP_TTL EQU 200 ; TTL for outgoing packets.
Whatever.

;; Well-known IP protocols
IP_ICMP EQU 1
IP_TCP EQU 6
IP_UDP EQU 17

;; ip -- Read IP datagram
ip jsr ckinit ; Initialize for a new packet
intr ; Version,IHL
rbit REDLED,PORTGD ; REDLED on
ifne A,#IP_VERS
jp bum ; Chuck this packet.

jsr get2 ; TOS, high byte of length
ifne A,#0 ; Length must be <256
jp bum
intr ; Low byte of length
st A,iplen

jsr get4 ; Identification, IP flags, frag offset
ifne A,#0
bum jmp flush ; Discard if fragment (todo:
ignoring high byte)

intr ; TTL
ifeq A,#0 ; Discard expired datagram (todo:
optional)
bum1 jp bum

intr ; Protocol
st A,ipproto

jsr get2 ; Header checksum

ld X,#ipsrc ; Source address
ld A,#4
jsr getbuf

jsr get4 ; Destination address, ignore.

jsr ckdone ; Finalize checksum
ifc
jp bum1 ; Checksum failed, discard packet.

;; fall thru

;; ipdspch -- dispatch on IP protocol
ipdspch ld A,ipproto
ifeq A,#IP_TCP
jmp tcp
ifeq A,#IP_ICMP
jmp icmp ; todo: short jump

;; fall thru (unknown IP protocol)

;; flush -- read and checksum bytes until end-of-packet.
;; Oddly, this also saves byte 12, if any, into URL.
flush ld cnt,#12
clr url
flsh1 jsr slipget ; Get de-escaped SLIP byte
ifc ; If end of SLIP packet,
ret
dec cnt ; Scarf out URL byte when cnt==0
ifbit Zero,STATUS
st A,url
jsr ckadd ; Add to checksum
jp flsh1

;; ipput -- put IP header
ipput jsr ckinit ; Start a new checksum (and
packet)
jsr slipend ; Send SLIP sync char

ld A,#IP_VERS ; IP version, IHL
jsr putbyte

jsr putzero ; TOS, high byte of iplen

ld A,iplen ; Low byte of iplen
jsr putbyte

ld X,#pkts-1 ; Ident: One byte of junk, then pkts
counter.
jsr putword

ld X,#ipflgs ; IP Flags(DF), fragment offset, and TTL.
ld A,#3
jsr putbuf

ld A,ipproto ; Protocol
jsr putbyte

;; The checksum is the current value + srcIP + dstIP
jsr ckaddip ; add source & dest to checksum
jsr ckput ; Finalize and send checksum

ld X,#ourIP ; Put source IP addr
jsr putlong

ld X,#ipsrc ; Put dest IP addr
jmp putlong ; tail call (todo: could fall thru)

;; ------------------------------------------------------------
;; ICMP
;; ------------------------------------------------------------

;; We handle only one ICMP type: echo request (ping)
ICMP_ECHO_REQ EQU 8
ICMP_ECHO_REPLY EQU 0

;; icmp -- read ICMP ECHO packet and reply.
icmp intr ; Type (8=echo_request)
ifne A,#ICMP_ECHO_REQ
bumI jmp flush

intr ; Code. Always 0.
ifne A,#0 ; todo: could probably skip this check
jp bumI

;; Start reply now, up to the ICMP checksum.
jsr ipput ; Clobbers checksum
jsr putzero ; ICMP_ECHO_REPLY=0 and code=0

;; Now compute updated ICMP checksum. (+ means 1's-comp addition)
;; Checksum update equation from RFC1624:
;; HC' = ~(C + (-m) + m') -- [Eqn. 3]
;; = ~(~HC + ~m + m')
;; Here m=0800 and m'=0 so ~m+m' = ~0800h + 0 = F7FFh
;; Thus, HC' = ~(~HC + F7FFh)
jsr ckclr ; Clear ckhi,cklo
jsr get2 ; Read HC into ckhi,cklo
jsr ckcomp ; HC <- ~HC
ld A,#0F7h ; Add high byte of delta
jsr ckadd
ld A,#0FFh ; Add low byte
jsr ckadd
jsr ckput ; Finalize and put

;; fall thru

;; bcopy -- Copy bytes from input to output, up to slip END.
bcopy jsr slipget ; todo: can bum to use intr, but
get double C0's
ifc
ret
jsr putbyte
jp bcopy

;; ------------------------------------------------------------
;; TCP
;; ------------------------------------------------------------

;; Bits in tcpflgs
TCP_FIN EQU 0
TCP_SYN EQU 1
TCP_RST EQU 2
TCP_PSH EQU 3
TCP_ACK EQU 4
TCP_URG EQU 5

;; We might bum a few bytes by making these equal to TTL.
TCP_MSS EQU 200 ; Our max segment size
TCP_WIN EQU 200 ; Our receive window.

;; Well-known TCP ports.
TCP_TELNET EQU 23
TCP_FINGER EQU 79
TCP_HTTP EQU 80

;; tcp -- read TCP packet and reply
tcp jsr ckinit ; Start a new checksum (and packet)
jsr cksudo ; Add pseudo-header
ld A,#tcpBufLen ; Straight copy of first 14 bytes
ld X,#tcppkt
jsr getbuf
jsr flush ; URL magically scarfed here
jsr ckdone ; Check checksum
ifc
ret ; TCP checksum failed (already flushed)

;; We now have a valid TCP packet.

;; fall thru

;; tcpfun -- TCP response function
tcpfun ifbit TCP_RST,tcpflgs ; Do not respond to RSTs
ret

ld A,dstport ; Set RST for unknown dest ports
ifne A,#0 ; But leave SYN on for seq'
computation.
sbit TCP_RST,tcpflgs
ld A,dstport+1
ifne A,#TCP_HTTP
sbit TCP_RST,tcpflgs

ld A,iplen ; Compute tcplen = iplen-40 except 0
if SYN
add A,#(-40 AND 0FFh)
ifbit TCP_SYN,tcpflgs
clr A
st A,tcplen

ifbit TCP_SYN,tcpflgs ; Compute seq' = seq + tcplen + SYN
+ FIN
inc A
ifbit TCP_FIN,tcpflgs
inc A
jsr tcpinc

ifbit TCP_RST,tcpflgs ; Now clear SYN if RST.
rbit TCP_SYN,tcpflgs

ld dataoff,#50h ; Dataoff = 5

jsr pagelen ; Compute tcplen'=pagelen if
ack==1&&tcplen>0, else 0
ifeq tcplen,#0 ; Zero if tcplen==0,
clr A
ifeq ack,#1 ; or if ack<>1
jp tcpA
clr A
tcpA st A,tcplen

add A,#40 ; Compute iplen' = 40. + tcplen'
st A,iplen

ifgt A,#40 ; If tcplen'>0, then the URL byte is
valid,
jsr cgi ; so do CGI stuff (side-effects)

sbit TCP_ACK,tcpflgs ; Compute flags' -- ACKbit=1 always
sbit TCP_PSH,tcpflgs ; PSH iff tcplen'>0
ifeq tcplen,#0
rbit TCP_PSH,tcpflgs

ld A,ack
ifgt A,#1 ; FIN unchanged if ack<=1
jp fin1
jp fin2
fin1 sbit TCP_FIN,tcpflgs ; else FIN=1 iff ack is EVEN
ifbit 0,A
rbit TCP_FIN,tcpflgs
fin2

;; fall thru

;; tcpput -- Transmit TCP reply
tcpput jsr ipput
jsr ckinit ; Start a new checksum
jsr cksudo ; Add pseudo-header

ld X,#dstport ; Flipped dst&src
jsr putword

ld X,#srcport
jsr putword

ld X,#acknum ; Flipped ack&seq
jsr putlong
ld X,#seqnum
jsr putlong

ld X,#dataoff ; Data offset and flags
jsr putword

ld X,#win ; Our (small) window
jsr putword

;; Lookahead to compute checksum
jsr pageptr ; Get pointer to data, X=f(URL)
ld A,tcplen ; Data length
jsr ckbuf
jsr ckput ; Finalize and send checksum

;; Resume sending data
jsr putzero ; Send urgent pointer

jsr pageptr ; Get pointer to data again.
ld A,tcplen ; Data length
jmp putbuf ; tail call

;; tcpinc -- Add A to TCP sequence number. Clobbers X.
tcpinc ld X,#seqnum+4 ; Must be longword-aligned.
rc
incLp dec X
adc A,[X]
st A,[X]
ld A,#00 ; clr A clobbers carry
ifbit 0,XLO ; Done when XLO=xxxxxx00
jp incLp
ifbit 1,XLO
jp incLp
ret

;; ------------------------------------------------------------
;; Utilities
;; ------------------------------------------------------------

;; get4,3,2 -- get 4, 3, or 2 bytes, returning last one.
get4 intr
get3 intr
get2 intr

;; fall thru

;; getbyte -- get network byte and accumulate checksum.
;; Throws to main server loop if reads a slip END.
getbyte jsr slipget ; Get de-escaped SLIP byte
ifc ; If END of packet
jmp server ; Unconditionally resync ("throw")
jmp ckadd ; Add to checksum (preserves A, uses
tmp)
; tail call (todo: jp)

;; putlong -- put 32bit word at [X]
putlong ld A,#4
jp putbuf

;; putzero -- put two zero bytes
putzero ld X,#zero

;; fall thru

;; putword -- put 16bit word at [X] (code or data memory)
putword ld A,#2

;; putbuf -- put A bytes at X to net
putbuf st A,cnt
pb1 dec cnt
ifbit Neg,STATUS
ret
ld A,[#0,X]
jsr putbyte
inc X
jp pb1

;; getbuf -- get A bytes and store at [X]
getbuf st A,cnt
gbuf1 dec cnt
ifbit Neg,STATUS
ret
intr
st A,[X] ; XHI is ignored here, I believe.
inc X
jp gbuf1

;; ------------------------------------------------------------
;; SLIP
;; ------------------------------------------------------------

SLIP_END EQU 0C0h ; End-of-packet marker
SLIP_ESC EQU 0DBh ; Escape
SLIP_ESC_END EQU 0DCh ; Escaped END
SLIP_ESC_ESC EQU 0DDh ; Escaped ESC

;; slipget -- get byte undoing SLIP escapes
slipget jsr getc
rc ; Initialize carry
ifeq A,#SLIP_END
sc ; Return with carry set indicates
end-of-packet
ifne A,#SLIP_ESC ; Normal character?
ret
jsr getc ; Get escaped char
ifeq A,#SLIP_ESC_END
ld A,#SLIP_END
ifeq A,#SLIP_ESC_ESC
ld A,#SLIP_ESC
rc ; Not END
ret

;; putbyte -- put byte and accumulate checksum. Clobbers A,tmp.
putbyte jsr ckadd

;; slipput -- put byte in A, escaping as needed. Clobbers A,tmp.
slipput st A,tmp
ifeq A,#SLIP_END
ld A,#SLIP_ESC_END
ifeq A,#SLIP_ESC
ld A,#SLIP_ESC_ESC
ifeq A,tmp
jp slip%
st A,tmp

ld A,#SLIP_ESC ; Send escape
jsr putc
ld A,tmp
slip% jmp putc ; Send char (tail call)

;; ------------------------------------------------------------
;; Ones-complement checksum routines
;; ------------------------------------------------------------

;; ckinit -- clear checksum and initialize for a new packet
ckinit ld ckcnt,#1

;; ckclr -- clear checksum state
ckclr clr ckeoc ; End-around carry
clr ckhi ; High byte of checksum
clr cklo ; Low byte of checksum
ret

;; cksudo -- Add pseudo-header to TCP checksum
cksudo jsr ckaddip ; Pseudo header is IP addresses
inc ckcnt ; Add 0 high byte (bummed)
ld A,ipproto
jsr ckadd

;; Add TCPlength = IPlength-20 (we discard IP pkts w/hdrs longer than
20.)
inc ckcnt ; Add 0 high byte (bummed)
ld A,iplen
add A,#0ECh ; -20 decimal. Worthless assembler

;; fall thru

;; ckadd -- update checksum with byte in A. Preserves A, clobbers tmp.
ckadd st A,tmp
rc ; Initialize carry
ifbit 0,ckcnt ; Odd-numbered (high) byte?
jp cka1
adc A,cklo ; Process low byte (in A)
st A,cklo
ld A,#00 ; "clr A" clears carry.

cka1 adc A,ckhi ; Process high byte (in A)
st A,ckhi

ifc ; Add to end-around carrys
inc ckeoc ; opt: 16bit incr for larger pkts

inc ckcnt ; Counting bytes for IP and cksum
parity.
ld A,tmp
ret

;; ckcomp -- one's complement the checksum. Clobbers A.
ckcomp ld A,cklo ; HC <- ~HC
xor A,#0FFh
st A,cklo
ld A,ckhi
xor A,#0FFh
st A,ckhi
ret

;; ckdone -- finalize checksum by adding EOC. Also does ckcheck.
ckdone rc
ld A,cklo ; Low byte
adc A,ckeoc
st A,cklo
ld A,ckhi ; High byte
adc A,#0
st A,ckhi
clr ckeoc ; reset end-around carrys

;; ckcheck -- Set carry if checksum invalid (not = 0FFFFh)
ckcheck sc ; Fail
ifeq cklo,#0FFh
jp ckc1
ret
ckc1 ifeq ckhi,#0FFh
rc ; Pass
ret

;; ckaddip -- add IP address to checksum
ckaddip ld A,#4
ld X,#ourIP
jsr ckbuf
ld A,#4
ld X,#ipsrc

;; fall thru

;; ckbuf -- Add A bytes at X to checksum.
ckbuf st A,cnt
ckb1 dec cnt
ifbit Neg,STATUS
ret
ld A,[#0,X] ; Data or code memory
jsr ckadd
inc X
jp ckb1

;; ckput -- Finalize and send checksum.
ckput jsr ckdone ; Finalize checksum
jsr ckcomp ; Put ~checksum
ld A,ckhi
jsr slipput ; without *disturbing* checksum!
ld A,cklo
jmp slipput

;; ------------------------------------------------------------
;; SLIP login
;; ------------------------------------------------------------

;; adjbaud -- adjust baud rate and restart login
adjbaud inc baud
jsr eewait

;; login -- Login to SLIP account. Maybe fine tune baud rate.
login jsr getc
ifeq A,#0FFh ; Octal 377 adjusts baud rate
jp adjbaud
ifeq A,#SLIP_END ; Whoa, SLIP already active?
ret ; Then we're done.
ifne A,#":" ; Just look for ":"
jp login
ld X,#slipuser
jsr putstr

lp2 jsr getc
ifne A,#":"
jp lp2
ld X,#slippass

;; fall thru

;; putstr -- put bytes at [X] until null.
putstr ld A,[#0,X] ; Magic to read CODE memory
ifeq A,#00
ret
jsr putc
inc X
jp putstr

;; ------------------------------------------------------------
;; I/O routines
;; ------------------------------------------------------------

;; slipend -- send SLIP end-of-packet marker
slipend ld A,#SLIP_END

;; fall thru

;; putc -- put char in A to serial port.
putc rbit TXD,PORTGD ; 2,2 START bit
jsr dly14 ; 3,5 delay = this + 4
sc ; 1,1
pc1 rrc A ; 1,1 Next bit into carry
stc TXD,PORTGD ; 2,2 Copy to output bit

;; Identical code in getc (This would be a macro if we had macros).
;; Currently, loop delay=7+explicit = 7+11 = 18
bavd1 ifbit 0,baud ; Delay 3 or 4 cycles
jp bavd2
nop
bavd2 ifbit 1,baud ; Delay 3 or 5 cycles
jp bavd3
nop
nop
bavd3 jmp bavd4 ; Plus 4 more = 10...13 cycles
bavd4
rc ; 1,1
ifne A,#01 ; 2,2
jp pc1 ; 1,1
sbit TXD,PORTGD ; 2,2 STOP bit

;; fall thru

;; dlyNN -- delay NN cycles (approx usec)
;; New chip: 923KHz (at 5v) => 1.065us/inst
;; Current chip: 981.5KHz (at 5v) => 1.019us/inst
dly14 nop
dly13 nop
dly12 nop
dly11 nop
dly10 ret

;; ------------------------------------------------------------
;; getc
;; ------------------------------------------------------------

;; The timeout must be such that if we receive no new character within
;; the timeout, then no more characters are forthcoming (until we release CTS).
Tmout EQU 3000 ; Timeout for 16 chars

;; getc -- Buffered read char from serial port. Clobbers: A,XHI,tmpX.
getc ld tmpX,XLO ; 3,3 Save XLO: TODO: ought to save XHI
too!
ifeq bufcnt,#0 ; 3,3 Buffer empty?
jp fillbuf ; 1,1 Yes

popbuf clr X ; 1,1 Pop char from buffer
ld XLO,bufptr ; 3,3
ld A,[X] ; 1,1
dec bufcnt ; 2,2
inc bufptr ; 2,2
ld XLO,tmpX ; 3,3 Restore XLO
ret ; 1,5

fillbuf clr X ; 1,1 Fill buffer.
clr bufptr ; 1,1
ld TMR1HI,#HIGH(Tmout) ; 3,3
ld TMR1LO,#LOW(Tmout) ; 3,3
ld T1CNTRL,#080h ; 3,3 Mode 1, no toggle. Not pending,
not started.

rbit CTS,PORTGD ; 2,2 Open the floodgates

;; Poll for start bit or timeout.
;; todo: get timer interrupts & stack manip working
gbPoll ifbit T1PND,T1CNTRL ; 2,2 Timer expired?
jp timeout ; 1,1 Yes
ifbit RXD,PORTGP ; 2,2 Start bit?
jp gbPoll ; 1,1
nop ; 1,1
nop ; 1,1
ifbit RXD,PORTGP ; 2,2 Start bit valid?
jp gbPoll ; 1,1 No.
jp gbChar ; 1,1 Yes.

timeout clr T1CNTRL ; 2,2 Stop timer and clear
pending bit
ld bufcnt,XLO ; 3,3 Finalize bufcnt
jmp popbuf

;; Collect char bits
;; TODO: move idempotent ops to replace delay insts.
gbChar ld A,#80h ; 2,2
gbLoop

;; Identical code in putc (This would be a macro if we had macros).
;; Currently, loop delay=18, explicit delay here=13 => baud=01
baud1 ifbit 0,baud ; Delay 3 or 4 cycles
jp baud2
nop
baud2 ifbit 1,baud ; Delay 3 or 5 cycles
jp baud3
nop
nop
baud3 jmp gb1 ; 3,4 Plus 5 more = 11...14 cycles
gb1 nop ; 1,1

ldc RXD,PORTGP ; 2,2 carry<-bit
rrc A ; 1,1 LSB first
ifnc ; 1,1
jp gbLoop ; 1,1

;; From here to the jump back to gbPoll must be between 0.5 and
;; 1.5 bit times (8 and 25 cycles)

st A,[X] ; 1,1 Store char into buffer
inc X ; 1,1

sbit CTS,PORTGD ; 2,2 Close the floodgates
sbit T1C0,T1CNTRL ; 2,2 Start timer, without interrupts.
jmp gbPoll ; 3,4 Start polling for next
character.

;; ------------------------------------------------------------
;; Application Layer
;; ------------------------------------------------------------

;; cgi -- run CGI script(s) for url.
cgi ifeq url,#" " ; Is it our home page?
jsr hit ; Yes. Bump hit count.

ifeq url,#"x" ; LED on request?
rbit GRNLED,PORTGD ; Yes.

ifeq url,#"y" ; LED off request?
ledoff sbit GRNLED,PORTGD ; Yes.

;; ledsync -- Sync eeprom message with state of LED.
ledsync ldc GRNLED,PORTGD
ld X,#ledurl
ld A,#"x" ; LED on URL if currently off
ifnc
inc A ; x->y
jsr eestore

ld X,#ledstr
ld A,#"f" ; How's this for hard-coding!
ifnc
ld A,#"n"
jsr eestore

inc X
ld A,#"f"
ifnc
ld A,#" "

;; fall thru

;; eestore -- Write A to [X] in eeprom, only if differs.
eestore ifeq A,[X]
ret
st A,[X]

;; fall thru

;; eewait -- wait for EEprom ready to read or write.
eewait ifbit Ready,STATUS
ret
jp eewait

;; hit -- Called for hits on the home page.
hit ld X,#hitcnt

;; ascinc -- increment ASCII decimal number with LAST digit at [X]
ascinc ld A,[X]
inc A ; Bump digit.
ifgt A,#'9' ; Carry?
ld A,#'0'
st A,[X] ; Store
jsr eewait
dec X
ifeq A,#'0' ; Carried?
jp ascinc
ret

;; pagelen -- Return length of webpage in A.
pagelen ld A,#webend-page404 ; Default page
ifeq url,#"s" ; Second page?
ld A,#page404-second
ifeq url,#" "
jp pg1
ifeq url,#"x"
jp pg1
ifeq url,#"y"
pg1 ld A,#weblen
ret

;; pageptr -- Return pointer to webpage in X.
pageptr ld X,#page404 ; Default page
ld A,url
ifeq A,#"s" ; Second page?
ld X,#second
ifeq A,#" " ; Home page?
jp pg2
ifeq A,#"x"
jp pg2
ifeq A,#"y"
pg2 ld X,#webdata ; Home page
ret

;; webpages -- Some hardwired pages. Each must be of ODD length.
webpages
second DB "

Another Page

Return home",LF
page404 DB "

404 - Not Found

",LF
webend

;; ------------------------------------------------------------
;; ROM data
;; ------------------------------------------------------------

;; slipuser -- SLIP user name and password.
slipuser
DB "xxx",CR
slippass
DB "yyy",CR

; todo: could use a random ifeq X,#0 for these two zeroes.
zero DB 0 ; End of string, above, and zero WORD.
win DB 0 ; TCP window size
DB TCP_WIN ; Also equal to IP_TTL

ipflgs DB IP_DF,0,IP_TTL ; IP Flags, fragment offset, and
TTL.

;; ourIP -- Our IP address.
ourIP DB IP_ADDR_0, IP_ADDR_1, IP_ADDR_2, IP_ADDR_3

;; vectors -- Interrupt vectors.
ORG 0FF6h
timer0 dw start
timer1 dw start
miwu dw start
swint dw getbyte

END


;;; Home page in data eeprom. This must moved to separate file, assembled,
;;; and programmed into the data eeprom. The page must have odd length.

ORG 040H
DB "

webACE Server

"
DB "LED is ledurl
DB "x?>"
DB "o"
ledstr
DB "ff
"
DB "
"
DB "Hits 0000"
hitcnt
DB "0"
DB 0Ah ; HTTP requires this
baud DB 2 ; Low 2 bits adjust bit delay

END

Always yours Alexander




Темы: Игры, Программное обеспечение, Пресса, Аппаратное обеспечение, Сеть, Демосцена, Люди, Программирование

Похожие статьи:
Список BBS - список BBS в Гродно.
Towdie - Описание-проходилка игры Towdie.
Сеть - Список BBS: BBS сети ZX-Net 095, 3D-Net, Независимые BBS, SuperNet.
Реклама - Инфорком-Пресс представляет...
Найдено в интернете - Hacker online: Взлом ASDSEE.

В этот день...   26 апреля