title SETSIO utility name ('SETSIO') ; The AMSTRAD SETSIO utility for PCW machines ; Disassembled by W.Cirsovius ; Call: SETSIO {option {option..}} OS equ 0000h BDOS equ 0005h CCPcmd equ 0080h _Conout equ 2 _String equ 9 _vers equ 12 CPM31 equ 31h CPM22 equ 22h SA.INIT equ 00b6h SA.BAUD equ 00b9h SA.PARA equ 00bch CD.VERS equ 00e3h _DevTbl equ 20 _Userf equ 30 DevLen equ 8 XON.XOF equ 00010000b LowBits equ 00000011b lf equ 0ah cr equ 0dh eot equ '$' eof equ 'Z'-'@' eos equ -1 ; End of table marker _IG equ 0 _AN equ 1 _EO equ 5 MSB equ 7 jr SETSIO db 'SETSIO #117',cr,lf db 'Developed by Locomotive Software Ltd.',cr,lf db 'Copyright (C) 1985 ' db 'Amstrad Consumer Electronics PLC' db cr,lf ; ; %%%%%%%%%%%%%%%%%%%% ; %%% START SETSIO %%% ; %%%%%%%%%%%%%%%%%%%% ; SETSIO: ld (UsrStk),sp ; Save callers stack ld sp,LocStk ; Get local stack call GetVersion ; Get machine version call PrepCCPline ; Prepare command line call c,ProcSIO ; Process SIO set up ld sp,(UsrStk) ; Get back stack ret ; ; Process SIO set up ; ENTRY Reg C holds macine type ; ProcSIO: ld a,c cp 3 ; Test type ok jp z,InvalEnv ; .. nope call SIOfitted ; Find SIO ld de,$NO.SIO jp nz,ProcErr ; .. not there call ExecOptions ; Do commands call z,ProcErr ; .. error ld de,$NO.CHNG jp z,String ; Tell no set up call ProgramSIO ; Program the SIO jp TellState ; .. and tell state ; $NO.CHNG: db 'SIO left unchanged',cr,lf,eot $NO.SIO: db 'SIO not found',cr,lf,eot ; ; Find SIO fitted ; EXIT Zero set if found ; SIOfitted: call FndSIO ; Find SIO in BIOS table ret nz ; .. not here ld a,(hl) ; Get control and XON.XOF ; Isolate XON/XOFF bit add a,-XON.XOF sbc a,a ; Map bit to FF or 00 ld (SIOx),a call GetSIO ; Get SIO data cpl ; Isolate handshake inc a rra push af sbc a,a ld (HandShk),a ; Set it pop af ; Isolate interrupt rra sbc a,a ld (Intrpt),a ; Set it ld (BdRate),bc ; Save baud rate ld (Parity),de ; Save parity and stop bits ld (TData),hl ; Save data bits xor a ret ; ; Transfer data to SIO ; ProgramSIO: call FndSIO ; Find SIO address ld a,(SIOx) ; Get old XON/XOFF and XON.XOF xor (hl) and XON.XOF xor (hl) ld (hl),a ; .. set into table ld hl,(HandShk) ; Get handshake ld a,l rra ld a,h ; .. and interrupt rla and LowBits cpl inc a ; .. here is the mode ld bc,(BdRate) ; Get baud rate ld de,(Parity) ; Get parity and stop bits ld hl,(TData) ; Get data bits push bc call InitSIO ; Set all pop hl jp SetBAUD ; .. baud rate, too ; ; Find SIO fitted ; EXIT Zero set if found ; Reg HL points to control code of table ; FndSIO: push de push bc call DevTbl ; Get device table ld de,$SIO ; Set search item SIO.loop: ld a,(hl) ; Test end of table (0 is end) cp 1 jr c,No.SIO ; .. no SIO found call CmpStr ; Find in table ld bc,DevLen add hl,bc ; .. point to next jr nz,SIO.loop ; .. not found, try next dec hl ; .. fix address dec hl No.SIO: pop bc pop de ret ; $SIO: db 'SIO ' ; ; Compare two strings ; ENTRY Regs DE and HL point to strings ; EXIT Zero set if same strings ; CmpStr: push hl push de ld b,DevLen-2 ; Set length less control CS.loop: ld a,(de) cp (hl) ; .. compare jr nz,CS.no ; .. no match inc de inc hl djnz CS.loop ; .. loop on CS.no: pop de pop hl ret ; ; Execute command options ; EXIT Zero set on error ; ExecOptions: xor a ld (DefStop),a ; Set default stop bits ExecLoop: ld hl,$CMD.TAB call Decode ; Decode from table call JPr ; .. execute jr nz,ExecLoop ; .. loop if no error jp FixNL ; Set line to end ; ; Main command table ; $CMD.TAB: db 'R' dw SetRecBaud db 'T' dw SetTrmBaud db 'B' dw SetBits db 'S' dw SetStop db 'P' dw SetParity db 'X' dw SetXON db 'H' dw SetHandShake db 'I' dw SetInterrupt db eos dw SetBaudRates ; ; No option, get baud rate for both channels ; SetBaudRates: ld bc,RBx ; Point to reciever baud rate call DecBaudRate ; Get it jr nz,SetBoth ; .. then set transmitter ld de,$BAD.OPTION ; .. remember invalid option ret ; $BAD.OPTION: db 'Bad option',cr,lf,eot ; ; Option TX : Set transmitter baud rate ; SetTrmBaud: ld bc,TBx ; Point to transmit baud rate call DecBaudRate ; Get it ret z ; .. error jr SetDefStop ; Set default stop bits ; ; Option RX : Set receiver baud rate ; SetRecBaud: ld bc,RBx ; Point to receiver baud rate call DecBaudRate ; Get it ret z ; .. error jr SetDefStop ; Set default stop bits ; ; Copy baud rate ; SetBoth: ld a,(bc) ; .. get current receiver dec bc ld (bc),a ; .. copy to transmitter ; ; Set default stop bits ; SetDefStop: ld a,(DefStop) ; Test any selection or a ret nz ; .. yeap, so leave ld a,(bc) ; Get current rate cp 4 ; .. look for 134.5 ccf sbc a,a ; .. build bits inc a ; 50, 75 and 110 get 2 bits add a,a ; .. other get 1 bit ld (StopBit),a ; Save stop bits or 1 ; .. force non zero ret ; ; Decode baud rate ; ENTRY Reg BC points to rate to be set ; DecBaudRate: ld hl,$BAUD.TAB ld de,$BAD.BAUD jp SetOption ; Get and set baud rate ; $BAUD.TAB: db '50',eos,1,0 db '75',eos,2,0 db '110',eos,3,0 db '134.5',eos,4,0 db '134',eos,4,0 db '150',eos,5,0 db '300',eos,6,0 db '600',eos,7,0 db '1200',eos,8,0 db '1800',eos,9,0 db '2400',eos,10,0 db '3600',eos,11,0 db '4800',eos,12,0 db '7200',eos,13,0 db '9600',eos,14,0 db '19200',eos,15,0 db eos,0,eos ; $BAD.BAUD: db 'Bad baud rate',cr,lf,eot ; ; Option BITS : Set bit length ; SetBits: ld hl,$BIT.SEL call Decode ; Decode from table jp (hl) ; $BIT.SEL: db 'R' dw SetRecBits db 'T' dw SetTrmBits db eos dw SetDataBits ; ; Set both same length ; SetDataBits: call SetRecBits ; Get receiver bits ret z ; .. error dec bc ld (bc),a ; .. set transmitter the same ret ; ; Option BITS RECEIVE : Set receive bits ; SetRecBits: ld bc,RData ; Point to receive length jr SetTheBits ; ; Option BITS TRANSMIT : Set receive bits ; SetTrmBits: ld bc,TData ; Point to transmit length SetTheBits: ld hl,$DATA.TAB ld de,$BAD.BITS jp SetOption ; Get and set data length ; $DATA.TAB: db '5',eos,5,0 db '6',eos,6,0 db '7',eos,7,0 db '8',eos,8,0 db eos,0,eos ; $BAD.BITS: db 'Bad bits',cr,lf,eot ; ; Option STOP : Set stop bits ; SetStop: ld hl,$STOP.TAB ld de,$BAD.STOP ld bc,StopBit ; Point to stop bits call SetOption ; Get and set stop bits ret z ; .. invalid ld a,-1 ld (DefStop),a ; Set no default stop bits ret ; $STOP.TAB: db '1.5',eos,1,0 db '1',eos,0,0 db '2',eos,2,0 db eos,0,eos ; $BAD.STOP: db 'Bad stop bits',cr,lf,eot ; ; Option PARITY : Set parity ; SetParity: ld hl,$PARI.TAB ld de,$BAD.PARITY ld bc,Parity ; Point to parity jr SetOption ; Get and set parity ; $PARI.TAB: db 'NONE',eos,0,0 db 'ODD',eos,1,0 db 'EVEN',eos,2,0 db eos,0,eos ; $BAD.PARITY: db 'Bad parity',cr,lf,eot ; ; Option XON : Set XON/XOFF protocol ; SetXON: ld bc,SIOx ; Point to XON/XOFF jr Set.ON.OFF ; .. set it ; ; Option HANDSHAKE : Set handshake ; SetHandShake: ld bc,HandShk ; Point to handshake jr Set.ON.OFF ; .. set it ; ; Option INTERRUPT : Set interrupt mode ; SetInterrupt: ld bc,Intrpt ; Point to interrupt Set.ON.OFF: ld hl,$ON.TAB ld de,$BAD.ON jr SetOption ; Get and set mode ; $ON.TAB: db 'ON',eos,eos,0 db 'OFF',eos,0,0 db eos,0,eos ; $BAD.ON: db 'Bad on/off',cr,lf,eot ; ; Find item from table and store it ; ENTRY Reg BC points to item to be set ; Reg HL points to table ; Reg DE holds error message ; EXIT Zero flag set on error ; SetOption: call FindStr ; Find item inc h ; Test success ret z ; .. nope ld a,l ld (bc),a ; Store value ret ; ; Execute via register ; ENTRY Reg HL points to address ; JPr: jp (hl) ; .. jump ; ; Tell how SIO initilaized ; TellState: call TellRate ; Tell baud rate call TellData ; .. data length call TellStop ; .. stop bits call TellParity ; .. parity call Tell.XON ; .. XON/XOFF call TellHandShake ; .. handshake call TellInterrupt ; .. inerrupt ld de,$CR.LF jp String ; Close statistic $CR.LF: db cr,lf,eot ; ; Tell baud rate ; TellRate: ld hl,(BdRate) ; Get baud rate ld a,h cp l ; Test both same jr z,SameRates ; .. yeap ld de,$RX call String call SameRates ; Give receiver ld a,l ld de,$TX call String ; .. then transmitter SameRates: call Blank ; Print blank ld de,$BAUD.SETS jp TableStr ; $RX: db ' Rx',eot $TX: db ' Tx',eot ; $BAUD.SETS: db 15,'?',eot db 1,'50',eot db 2,'75',eot db 3,'110',eot db 4,'134.5',eot db 5,'150',eot db 6,'300',eot db 7,'600',eot db 8,'1200',eot db 9,'1800',eot db 10,'2400',eot db 11,'3600',eot db 12,'4800',eot db 13,'7200',eot db 14,'9600',eot db 15,'19200',eot ; ; Tell data length ; TellData: ld de,$BITS call String ld hl,(TData) ; Get bit length ld a,h cp l ; Test same length jr z,SameData ld de,$RD call String ; Tell receiver call SameData ld a,l ld de,$TD call String ; .. and transmitter SameData: ld de,$DATA.SETS jp TableStr ; .. tell length ; $BITS: db ' Bits ',eot $RD: db 'rx ',eot $TD: db ' Bits tx ',eot ; $DATA.SETS: db 4,'?',eot db 5,'5',eot db 6,'6',eot db 7,'7',eot db 8,'8',eot ; ; Tell stop bits ; TellStop: ld de,$STOP call String ld a,(StopBit) ; Get stop bits ld de,$STOP.SETS jp TableStr ; .. tell it ; $STOP: db ' Stop ',eot ; $STOP.SETS: db 3,'?',eot db 0,'1',eot db 1,'1.5',eot db 2,'2',eot ; ; Tell parity ; TellParity: ld de,$PARITY call String ld a,(Parity) ; Get parity ld de,$PARITY.SETS jp TableStr ; .. tell it ; $PARITY: db ' Parity ',eot ; $PARITY.SETS: db 3,'?',eot db 0,'none',eot db 1,'odd',eot db 2,'even',eot ; ; Tell XON/XOFF ; Tell.XON: ld de,$XON ld a,(SIOx) ; Get XON/XOFF jr TellOnOff ; .. tell it ; $XON: db ' Xon',eot ; ; Tell handshake ; TellHandShake: ld de,$HAND.SHAKE ld a,(HandShk) ; Get handshake jr TellOnOff ; .. tell it ; $HAND.SHAKE: db ' Handshake',eot ; ; Tell interrupt ; TellInterrupt: ld de,$INTERRUPT ld a,(Intrpt) ; Get interrupt jr TellOnOff ; .. tell it ; $INTERRUPT: db ' Interrupt',eot ; ; Tell ON or OFF ; TellOnOff: call String ld de,$ON.OFF jp TableStr ; Tell state ; $ON.OFF: db 2,' ?',eot db 0,' off',eot db -1,' on',eot ; ; Process error ; ENTRY Reg DE points to error message ; ProcErr: push bc push af call String ; Print error call GetAttr ; Test EOL or EOF jr nz,PE.ex ; .. yeap ld de,$IGNORE call String ; Tell ignoring jr PE.go PE.loop: ld a,c call Conout ; Print character PE.go: call GetChr ; Get character and attribute call GetAttr ; Test EOL or EOF call Get ; Get character jr z,PE.loop ; .. there is more to print ld de,$CRLF call String ; .. close line PE.ex: pop af pop bc ret $IGNORE: db 'Ignoring rest of line: ',eot $CRLF: db cr,lf,eot ; ; Tell invalid environment ; InvalEnv: push de ld de,$INVENV call String ; Print error pop de ret $INVENV: db 'This program will not run in this environment' db cr,lf,eot ; ; Print string from table ; ENTRY Accu holds value ; Reg DE points to table ; Table starts with number of entries ; Each strings ends with value ; TableStr: push hl push de push bc push af ld c,a ; Get value ex de,hl ld b,(hl) ; Get entry inc hl ld e,l ; Copy string ld d,h inc b ; Test special end of table jr z,TS.swap TS.skip: ld a,(de) ; Find end of sub-string inc de cp eot jr nz,TS.skip ld a,(de) ; Get next value inc de cp c ; .. compare jr z,TS.string TS.swap: dec b ; Count down jr nz,TS.skip ex de,hl TS.string: call String ; .. print string pop af pop bc pop de pop hl ret ; ; Print string on console ; ENTRY Reg DE points to string closed by '$' ; String: push hl push de push bc push af ld c,_String call BDOS ; .. print pop af pop bc pop de pop hl ret ; ; Print blabk on console ; Blank: push af ld a,' ' call Conout ; Print blank pop af ret ; ; Print character on console ; ENTRY Accu holds character ; Conout: push hl push de push bc push af ld e,a ld c,_Conout call BDOS ; .. print pop af pop bc pop de pop hl ret ; ; Fix line to end ; FixNL: call GetAttr ; Get attributes call nz,Get ; .. read till EOL or EOF ret ; ; Decode from table ; ENTRY Reg HL points to table ; Entry: Command key, execution address ; Closed by -1, execution address ; EXIT Reg HL holds execution address ; Decode: push de push bc push af call ChrGet ; Get character jr Dec.go ; .. start Dec.loop: inc hl ; Skip address inc hl Dec.go: ld a,(hl) ; Get character inc hl cp eos ; Test end of table jr z,Dec.ex call CmpChr ; Find character jr nz,Dec.loop Dec.skip: call Get ; Skip alphanumeric characters call GetChr bit _AN,b jr nz,Dec.skip Dec.ex: ld e,(hl) ; Fetch address inc hl ld d,(hl) ex de,hl pop af pop bc pop de ret ; ; Find string from table ; ENTRY Reg HL points to table ; EXIT Reg L holds 1st operand ; Reg H holds 2nd operand or -1 if not found ; FindStr: push de push bc push af call ChrGet ; Get valid character ld d,b ; Save attribute dec hl ; .. fix list jr FS.go FS..unget: inc e FS.unget: dec e call nz,UnGet ; Unget character jr nz,FS.unget FS.skip: ld a,(hl) ; Get character inc hl inc a jr nz,FS.skip ; .. skip item inc hl FS.go: ld e,0 ; Init counter jr FS.cmp FS.loop: call CmpChr ; Compare character jr nz,FS..unget ; .. not found call Get ; Get character from line inc e FS.cmp: call GetChr ; Get character and attribute inc hl ld a,(hl) cp eos ; Test end of string jr nz,FS.loop ; .. nope inc e dec e ; Test total end jr z,FS.end ; .. yeap ld a,b xor d ; Test same attribute and 00101011b ; Test result jr z,FS..unget ; .. still searching FS.end: inc hl ld e,(hl) ; Get operands inc hl ld d,(hl) ex de,hl ; .. into right reg pop af pop bc pop de ret ; ; Compare characters ; ENTRY Accu and reg C hold characters ; EXIT Zero set if same ; CmpChr: sub c ; Compare ret z ; .. found cp -' ' ; Test blank ???? ret nz ; .. nope ld a,b or 11111101b ; Fix attribute inc a ; .. fix result ret ; ; Get valid definition character from command line ; ChrGet: jr .ChrGet ; .. skip reading CG.loop: call Get ; Get character .ChrGet: call GetChr ; Get character and attribute bit _EO,b ; Test end of input ret nz ; .. exit bit _IG,b ; Test valid character jr nz,CG.loop ; .. nope ret ; ; Prepare CCP command line ; EXIT Carry set if line OK ; PrepCCPline: push hl push de push bc ld hl,CCPcmd ld a,(hl) ; Fetch length of input inc a ld (RecPtr),a ; .. save it inc hl ld (BufPtr),hl ; Init buffer dec a add a,l ; Point to end of line ld l,a adc a,h sub l ld h,a ld (hl),eof ; Close line scf pop bc pop de pop hl ret nc ; ; Get character from command line ; Store character and attribute ; Get: push hl push de push bc push af ld hl,(BufPtr) ; Get current pointer ld c,(hl) ; .. get character ex de,hl call PutChr ; .. save it ld a,c cp eof ; Test end of line jr z,Get.eof ld a,(RecPtr) dec a ; Fix pointers ld (RecPtr),a ex de,hl inc hl ld (BufPtr),hl Get.eof: pop af pop bc pop de pop hl ret ; ; Unget current character ; UnGet: push hl push de push bc push af ld a,(Char) ; Get character cp eof ; Test end of line ld hl,(BufPtr) jr z,UG.dummy ; .. yeap, skip ld hl,RecPtr inc (hl) ; Fix pointers if not ld hl,(BufPtr) dec hl ld (BufPtr),hl UG.dummy: dec hl ld c,(hl) call PutChr ; Save character and attribute pop af pop bc pop de pop hl ret ; ; Put character and attribute into memory ; ENTRY Reg C holds character ; PutChr: bit MSB,c ; Test 80..FF ld b,01h jr nz,.PutChr ; .. yeap, set standard ld b,0 ld hl,AttrTable add hl,bc ld b,(hl) ; Fetch attribute .PutChr: ld (Char),bc ; Save character and attribute ret ; ; Get current character and attribute ; EXIT Reg C holds character ; Reg B holds attribute ; GetChr: ld bc,(Char) ; Get character and attribute ret ; ; Get EOL or EOF state of current character ; EXIT Zero set if not EOL or EOF ; GetAttr: ld a,(Attr) ; Get attribute and 1 SHL _EO ; .. test bit ret ; ; Get version of machine ; EXIT Reg C holds type of machine ; 0 : CPC6128 ; 1 : PCW8256 ; 3 : CP/M 2.2 version ; 4 : Other machine ; GetVersion: ld c,_vers call BDOS ; Get OS version cp CPM31 ; Test CP/M+ jr z,Vers31 cp CPM22 ; Test CP/M 2.2 ld c,4 ret nz ld c,3 ret Vers31: ld hl,(OS+1) ld de,3*(_Userf-1) add hl,de ld (Userf+1),hl ; Set USERF vector ld de,3*(_DevTbl-_Userf) add hl,de ld (DevTbl+1),hl call GetType ; Get machine type ld c,a ; .. set result ret ; ; Execute BIOS function 30 : USERF ; Userf: jp $-$ ; ; Execute BIOS function 20 : DEVTBL ; EXIT Reg HL points to device table ; DevTbl: jp $-$ ; ; Get type of machine ; EXIT Accu holds type of machine ; GetType: call Userf ; .. get type dw CD.VERS ret ; ; Set SIO ; ENTRY Accu holds mode ; Reg D holds stop bits ; Reg E holds parity ; Reg H holds receiver data bits ; Reg L holds transmitter data bits ; InitSIO: call Userf dw SA.INIT ; .. init SIO ret ; ; Get current SIO settings ; EXIT Accu holds mode ; Reg B holds receiver baud rate ; Reg C holds transmitter baud rate ; Reg D holds stop bits ; Reg E holds parity ; Reg H holds receiver data bits ; Reg L holds transmitter data bits ; GetSIO: call Userf dw SA.PARA ; .. get SIO ret ; ; Set baud rate for SIO ; ENTRY Reg H holds receiver baud rate ; Reg L holds transmitter baud rate ; SetBAUD: call Userf dw SA.BAUD ; .. set baud rates ret ; ; Attribute table of all ASCII characters ; Bit definitions: ; ; 7 6 5 4 3 2 1 0 ; +----+----+----+----+----+----+----+----+ ; | xx | xx | EO | EX | NM | HX | AN | IG | ; +----+----+----+----+----+----+----+----+ ; ; xx N.C. ; EO EOL or EOF ; EX Extension string ; NM Numeric 0..9 ; HX Hex range A..F ; AN Alphanumeric prefix ; IG Ignore for definition ; AttrTable: ; ; Control characters ; db 01h,01h,01h,01h,01h,01h,01h ; 00..06 db 01h,01h,01h,01h,01h,01h,21h ; 07..0D db 01h,01h,01h,01h,01h,01h,01h ; 0E..14 db 01h,01h,01h,01h,01h,21h,01h ; 15..1B db 01h,01h,01h,01h ; 1C..1F ; ; ASCII characters ; db 01h,01h,00h,10h,01h,01h,10h ; !"#$%& db 01h,01h,01h,01h,01h,01h,01h ; '()*+,\ db 00h,01h,0ch,0ch,0ch,0ch,0ch ; ./01234 db 0ch,0ch,0ch,0ch,0ch,01h,01h ; 56789:; db 01h,01h,01h,01h,01h,06h,06h ; <=>?@AB db 06h,06h,06h,06h,02h,02h,02h ; CDEFGHI db 02h,02h,02h,02h,02h,02h,02h ; JKLMNOP db 02h,02h,02h,02h,02h,02h,02h ; QRSTUVW db 02h,02h,02h,01h,01h,01h,01h ; XYZ[\]^ db 01h,01h,06h,06h,06h,06h,06h ; _`abcde db 06h,02h,02h,02h,02h,02h,02h ; fghijkl db 02h,02h,02h,02h,02h,02h,02h ; mnopqrs db 02h,02h,02h,02h,02h,02h,02h ; tuvwxyz db 01h,01h,01h,01h,01h ; {|}~DEL db eof ds 205,0 DATA equ 1000h HandShk equ DATA+256 Intrpt equ HandShk+1 BdRate equ Intrpt+1 TBx equ Intrpt+1 RBx equ TBx+1 Parity equ RBx+1 StopBit equ Parity+1 TData equ StopBit+1 RData equ TData+1 SIOx equ RData+1 UsrStk equ SIOx+1 LocStk equ UsrStk+258 DefStop equ UsrStk+258 BufPtr equ DefStop+1 RecPtr equ BufPtr+2 Char equ RecPtr+1 Attr equ Char+1 end