Refactor pathing
This commit is contained in:
parent
46fb8226bf
commit
7fc533f69d
114
1802mc/til_wrm.asm
Normal file
114
1802mc/til_wrm.asm
Normal file
@ -0,0 +1,114 @@
|
||||
; til_wrm.asm
|
||||
; Copyright (C) 2023 William R. Moore
|
||||
;
|
||||
; This program is free software: you can redistribute it and/or modify
|
||||
; it under the terms of the GNU General Public License as published by
|
||||
; the Free Software Foundation, either version 3 of the License, or
|
||||
; (at your option) any later version.
|
||||
;
|
||||
; This program is distributed in the hope that it will be useful,
|
||||
; but WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||
; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
||||
; GNU General Public License for more details.
|
||||
;
|
||||
; You should have received a copy of the GNU General Public License
|
||||
; along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||
|
||||
|
||||
;******************************************************************
|
||||
; Threaded Interpretive Language (TIL) for COSMAC 1802 CPU.
|
||||
; Core of Threaded Interpretive Language I/O
|
||||
;
|
||||
; From the book "Threaded Interpretive Languages: Their Design and Implementation"
|
||||
;
|
||||
;******************************************************************
|
||||
|
||||
|
||||
; Register definitions (1802 has R0-RF 16 x 16 bit registers)
|
||||
STACK EQU 2 ; stack pointer
|
||||
PC EQU 3 ; program counter
|
||||
CALLR EQU 4 ; call register
|
||||
RETR EQU 5 ; return register
|
||||
TXTPTR EQU 7 ; text pointer
|
||||
INBUF EQU 8 ; Input line buffer pointer register.
|
||||
; TIL registers
|
||||
I EQU 10 ; Instruction Pointer
|
||||
WA EQU 11 ; Word Address
|
||||
TPC EQU 12 ; TIL Program Counter
|
||||
|
||||
|
||||
; Stack for ram High - top of ram, minus monitor scratch pad area.
|
||||
USTACK EQU 0FFBFH
|
||||
; SCRT routine locations Standard ROM org'd at 0
|
||||
CALLSC EQU 0ADBH
|
||||
RETURN EQU 0AEDH
|
||||
; I/O ROUTINES
|
||||
OUTSTR EQU 0526H
|
||||
; The Monitor "INPUT" routine is at 8005hex in the ORG'ed 8000hex Monitor
|
||||
; The inputted character is returned in RB.0
|
||||
INDATA EQU 11
|
||||
INCHR EQU 0005H
|
||||
; The Monitor "OUTPUT" routine is at 821Dhex in the ORG'ed 8000hex Monitor
|
||||
; The character to be outputted is stored in RB.0
|
||||
OUTCHR EQU 021DH
|
||||
|
||||
; Start at 8000h for ROM @ 0000h
|
||||
ORG 8000H
|
||||
; Setup for SCRT routines.
|
||||
; Set R3 as program counter
|
||||
LOAD PC, MAIN
|
||||
SEP PC
|
||||
; *** Main program entry.
|
||||
MAIN LOAD STACK, USTACK ; Setup stack pointer
|
||||
SEX STACK
|
||||
; Setup 4 to CALLSC routine 8ADB
|
||||
LOAD CALLR, CALLSC
|
||||
; Setup R5 to RETURN (8AED)
|
||||
LOAD RETR, RETURN
|
||||
; R7 points to string.
|
||||
; Use SCRT
|
||||
; R3 is the PC
|
||||
; R4 is the call register - points to the call routine in rom
|
||||
; R5 is the return register - points to return routine in rom
|
||||
; CALL pseudo-op of the A18 assembler
|
||||
; Set program counter to R4 and follow with word address of the routine to be called.
|
||||
LOAD TXTPTR, GREET
|
||||
CALL OUTSTR
|
||||
|
||||
INLINE LOAD TXTPTR, PROMPT
|
||||
CALL OUTSTR
|
||||
|
||||
; Read a char, echo a char
|
||||
; if ctrl-c stop
|
||||
IOLOOP CALL INCHR
|
||||
GLO INDATA ; io leaves in RB.0
|
||||
SDI 3 ; subtract ctrl-c
|
||||
BZ EXIT
|
||||
;; simplistic now, must add typed chars to a buffer.
|
||||
;;
|
||||
;; CHECK FOR <CR>
|
||||
GLO INDATA
|
||||
SDI 13 ; CR?
|
||||
BZ EXECBUF ; YES - GOTO EXECUTE BUFFER
|
||||
CALL OUTCHR ; ECHO CHARACTER
|
||||
BR IOLOOP
|
||||
|
||||
EXECBUF LOAD TXTPTR, OKMSG
|
||||
CALL OUTSTR
|
||||
BR INLINE
|
||||
|
||||
; Exit to Membership Card monitor.
|
||||
EXIT SEP 1
|
||||
|
||||
; Cold start
|
||||
GREET TEXT "Welcome to William's TIL."
|
||||
BYTE 0
|
||||
|
||||
OKMSG TEXT " OK"
|
||||
BYTE 0
|
||||
|
||||
PROMPT BYTE 0DH, 0AH, 24H, 00
|
||||
|
||||
|
||||
END
|
||||
|
154
altair8800/SCC.asm
Normal file
154
altair8800/SCC.asm
Normal file
@ -0,0 +1,154 @@
|
||||
; SCC.asm
|
||||
; Copyright (C) 2023 William R. Moore
|
||||
;
|
||||
; This program is free software: you can redistribute it and/or modify
|
||||
; it under the terms of the GNU General Public License as published by
|
||||
; the Free Software Foundation, either version 3 of the License, or
|
||||
; (at your option) any later version.
|
||||
;
|
||||
; This program is distributed in the hope that it will be useful,
|
||||
; but WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||
; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
||||
; GNU General Public License for more details.
|
||||
;
|
||||
; You should have received a copy of the GNU General Public License
|
||||
; along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||
|
||||
; 8080 Assembly implementation of "Ship, Captain, Crew" for the
|
||||
; Altair 8800 using CP/M
|
||||
|
||||
title 'Ship, Captain, Crew'
|
||||
|
||||
BDOS equ 0005h
|
||||
WRITESTR equ 09h
|
||||
WRITECHR equ 02h
|
||||
CONSTAT equ 0bh
|
||||
EOS equ 24h
|
||||
CR equ 0dh
|
||||
LF equ 0ah
|
||||
|
||||
org 0100h
|
||||
lxi h, 0
|
||||
mvi d, 080h
|
||||
|
||||
; Clears the screen
|
||||
push h
|
||||
push b
|
||||
mvi c, WRITESTR
|
||||
lxi d, cls
|
||||
call BDOS
|
||||
pop b
|
||||
pop h
|
||||
|
||||
run:
|
||||
in 0ffh
|
||||
mov d, a
|
||||
cpi 0
|
||||
jz exit
|
||||
jmp rand_
|
||||
|
||||
continuerun:
|
||||
push h
|
||||
push b
|
||||
mvi c, WRITESTR
|
||||
add d, '0'
|
||||
|
||||
lxi h, d
|
||||
lxi d, '$'
|
||||
call concatenate
|
||||
|
||||
lxi d, m
|
||||
call BDOS
|
||||
pop b
|
||||
pop h
|
||||
|
||||
jmp run
|
||||
|
||||
concatenate:
|
||||
CONCATENATE_LOOP:
|
||||
; Load a character from the source string
|
||||
MOV A, M
|
||||
CPI 0 ; Check for end of source string (null terminator)
|
||||
JZ CONCATENATE_DONE
|
||||
|
||||
; Copy the character to the destination string
|
||||
MOV M, A
|
||||
|
||||
; Move to the next character in both strings
|
||||
INX H ; Increment source string pointer
|
||||
INX D ; Increment destination string pointer
|
||||
|
||||
JMP CONCATENATE_LOOP ; Repeat the loop
|
||||
|
||||
CONCATENATE_DONE:
|
||||
; Null-terminate the concatenated string
|
||||
MVI M, 0 ; Store null terminator at the end of the destination string
|
||||
ret
|
||||
|
||||
print:
|
||||
; push h
|
||||
; push b
|
||||
; lxi d, textstr
|
||||
; mvi c, WRITESTR
|
||||
; call BDOS
|
||||
; pop b
|
||||
; pop h
|
||||
; jmp exit
|
||||
|
||||
;------------------------------------------------------------------------
|
||||
; rand_
|
||||
; This is an implementation of George Marsaglia's three-stage
|
||||
; XOR-shift algorithrm
|
||||
;------------------------------------------------------------------------
|
||||
rand_:
|
||||
; Initialize random seed (optional)
|
||||
mvi c, 42H ; Seed value (you can change this)
|
||||
lxi h, 5678H ; Address to store seed (change this)
|
||||
shld random_seed
|
||||
|
||||
; Roll the die
|
||||
call roll_die
|
||||
jmp continuerun
|
||||
|
||||
; roll a die
|
||||
roll_die:
|
||||
lxi h, random_seed ; Load the seed address
|
||||
mov a, m ; Load the seed value
|
||||
xra a ; Clear the accumulator
|
||||
rrc ; Rotate right through carry
|
||||
rlc ; Rotate left through carry
|
||||
rrc ; Rotate right through carry
|
||||
rlc ; Rotate left through carry
|
||||
rrc ; Rotate right through carry
|
||||
rlc ; Rotate left through carry
|
||||
mvi b, 06H
|
||||
call MODULO
|
||||
ret
|
||||
|
||||
; Perform modulo operation
|
||||
MODULO:
|
||||
xchg ; Exchange A and D registers, D = dividend, A = divisor
|
||||
lxi d, 0 ; Initialize remainder (D) to 0
|
||||
MODULO_LOOP:
|
||||
cmp b ; Compare A (divisor) with B (counter)
|
||||
jc MODULO_DONE ; If A < B, exit loop
|
||||
|
||||
sub b ; Subtract B (counter) from A (divisor)
|
||||
inr d ; Increment D (remainder)
|
||||
|
||||
jmp MODULO_LOOP ; Repeat the loop
|
||||
|
||||
MODULO_DONE:
|
||||
xchg ; Restore original values (A = divisor, D = remainder)
|
||||
ret
|
||||
|
||||
exit: hlt
|
||||
|
||||
random_seed: ; Placeholder for the random seed value
|
||||
dw 0 ; You can initialize it with any value
|
||||
ship: db 'You have a ship', CR, LF, EOS
|
||||
captain: db 'You have a captain!', CR, LF, EOS
|
||||
crew: db 'You have a crew!', CR, LF, EOS
|
||||
cls: db 1bh, '[2J$' ; ANSI clear screen: ESC [ 2 J
|
||||
end
|
||||
|
113
altair8800/SillyDieRoller.asm
Normal file
113
altair8800/SillyDieRoller.asm
Normal file
@ -0,0 +1,113 @@
|
||||
; SillyDieRoller.asm - "rolls" a die and makes the LEDs blink while it happens
|
||||
; Copyright (C) 2023 William R. Moore
|
||||
;
|
||||
; This program is free software: you can redistribute it and/or modify
|
||||
; it under the terms of the GNU General Public License as published by
|
||||
; the Free Software Foundation, either version 3 of the License, or
|
||||
; (at your option) any later version.
|
||||
;
|
||||
; This program is distributed in the hope that it will be useful,
|
||||
; but WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||
; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
||||
; GNU General Public License for more details.
|
||||
;
|
||||
; You should have received a copy of the GNU General Public License
|
||||
; along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||
|
||||
CR EQU 0DH
|
||||
LF EQU 0AH
|
||||
|
||||
; CP/M calls
|
||||
WRITESTR EQU 9H
|
||||
PRTCHR EQU 02H
|
||||
CHRIN EQU 01H
|
||||
BDOS EQU 05H
|
||||
CONSOLEOUT EQU 06H
|
||||
CONSOLEIN EQU 0AH
|
||||
NONBLOCKIN EQU 0FFH
|
||||
|
||||
ORG 100H
|
||||
INIT LXI H,DATA ; HL points to blinken data
|
||||
SHLD SAVE_HL
|
||||
|
||||
GETD LHLD SAVE_HL ; restore HL
|
||||
MOV A,M ; get data @ HL
|
||||
CPI EOF ; End of the data list?
|
||||
JZ INIT ; Yes, reset HL pointer.
|
||||
MOV D,A ; No, put in D register for the display pattern.
|
||||
INR L ; HL++
|
||||
SHLD SAVE_HL ; Save data
|
||||
|
||||
INPDEL
|
||||
MVI C, CONSOLEIN
|
||||
MVI D, NONBLOCKIN
|
||||
CALL BDOS
|
||||
CPI 0H
|
||||
JZ NO_INPUT
|
||||
|
||||
MVI C, WRITESTR
|
||||
LXI D, WELCOME
|
||||
CALL BDOS
|
||||
|
||||
MVI C, CHRIN
|
||||
MVI D, -1
|
||||
MVI E, NONBLOCKIN
|
||||
CALL BDOS
|
||||
CPI 0H
|
||||
JZ NO_INPUT
|
||||
CPI 03H
|
||||
JZ DONE
|
||||
|
||||
; LXI H,0 ; Init HL to zero before starting the delay loop
|
||||
; IN 0FFH
|
||||
; CPI 00H ; All Sense switches off finishes the program.
|
||||
; JZ DONE
|
||||
|
||||
NO_INPUT
|
||||
LXI B,4H ; Hardcoded timer
|
||||
|
||||
BLINK
|
||||
LDAX D
|
||||
LDAX D
|
||||
LDAX D
|
||||
LDAX D
|
||||
DAD B
|
||||
JNC BLINK
|
||||
JMP GETD
|
||||
; Done with this loop go get the next D
|
||||
|
||||
; Return to CP/M if 00 on sense switches. Some way to drop out.
|
||||
DONE JMP 0H
|
||||
; Somewhere to save HL, since it will get clobbered by the delay routine.
|
||||
SAVE_HL DW 0
|
||||
; Put your pattern list here... this is just jiggy wiggy back forth here.
|
||||
|
||||
DATA
|
||||
DB 10111010b
|
||||
DB 11000011b
|
||||
DB 11011111b
|
||||
DB 10001000b
|
||||
DB 01001000b
|
||||
DB 00110000b
|
||||
DB 01000110b
|
||||
DB 10000010b
|
||||
DB 01101010b
|
||||
DB 01000000b
|
||||
DB 00100111b
|
||||
DB 01010111b
|
||||
DB 00100000b
|
||||
DB 11110010b
|
||||
DB 01101111b
|
||||
DB 10000011b
|
||||
DB 00110011b
|
||||
DB 00010101b
|
||||
DB 10001100b
|
||||
DB 10111011b
|
||||
DB 00000000b
|
||||
|
||||
DB EOF
|
||||
|
||||
|
||||
EOF EQU 042 ; end of data
|
||||
WELCOME DB "Welcome to the Silly Dice Roller!", CR, LF, "$"
|
||||
END
|
446
altair8800/cpm/til.z80
Normal file
446
altair8800/cpm/til.z80
Normal file
@ -0,0 +1,446 @@
|
||||
; ***** TIL
|
||||
; Outer Interpreter
|
||||
; Author Kelly Loyd
|
||||
; Target System
|
||||
; Z80 CP/M 64K RAM
|
||||
; ***
|
||||
|
||||
; Non Standard Z80 MC
|
||||
STD_CPM EQU 1
|
||||
|
||||
;---------- Put in CP/M Transient Memory space.
|
||||
ORG 100h
|
||||
|
||||
;---------- START/RESTART
|
||||
START LD DE,RSTMSG
|
||||
LD A,(BASE)
|
||||
AND A
|
||||
JR NZ, ABORT
|
||||
LD A,10
|
||||
LD (BASE),A
|
||||
LD DE,SRTMSG
|
||||
ABORT LD SP,STACK
|
||||
PUSH DE
|
||||
LD HL,0
|
||||
LD (MODE),HL
|
||||
LD IY,NEXT
|
||||
LD IX,RETURN
|
||||
LD HL,8080h
|
||||
LD (LBEND),HL
|
||||
LD BC,OUTER ; Effectively, Set OUTER as the next routine
|
||||
JP NEXT ; Call NEXT in the Inner Interpreter, which will load address of OUTER and Jump to it.
|
||||
|
||||
; Entry point of OUTER interpreter.
|
||||
OUTER DW TYPE
|
||||
DW INLINE
|
||||
DW ASPACE
|
||||
DW TOKEN
|
||||
DW TILHALT
|
||||
DW QSEARCH ; Leaves something on the stack if found or not found?
|
||||
DW @IF
|
||||
|
||||
; --------- Inner Interpreter
|
||||
SEMI DW $ + 2
|
||||
LD C,(IX+0)
|
||||
INC IX
|
||||
LD B,(IX+0)
|
||||
INC IX
|
||||
NEXT LD A,(BC) ; BC = Instruction Register
|
||||
LD L,A ; @I -> WA (HL = word address)
|
||||
INC BC
|
||||
LD A,(BC)
|
||||
LD H,A
|
||||
INC BC ; I = I + 2
|
||||
RUN LD E,(HL) ; @WA -> CA (Code Address)
|
||||
INC HL ; WA = WA + 2
|
||||
LD D,(HL)
|
||||
INC HL
|
||||
EX DE,HL ; CA -> PC
|
||||
JP (HL)
|
||||
|
||||
COLON DEC IX
|
||||
LD (IX+0),B
|
||||
DEC IX
|
||||
LD (IX+0),C
|
||||
LD C,E
|
||||
LD B,D
|
||||
JP (IY)
|
||||
;----------- End of Inner -----
|
||||
|
||||
;---------- IMPORTANT - Start of Vocabulary, Dictionary Entries
|
||||
; Any code that is INTERNAL only, should come after the last Dictionary Entry.
|
||||
DICT_BEG
|
||||
DB 5,'TOK' ; TOKEN ID
|
||||
DW SEARCH - 6 ; should point to the Entry start.
|
||||
TOKEN DW $ + 2
|
||||
EXX ; Save IR (EXX exchanges BC, DE, and HL with shadow registers with BC', DE', and HL'.)
|
||||
LD HL,(LBP) ; pointer to token
|
||||
LD DE,(DP) ; pointer to Dictionary
|
||||
POP BC ; space left by ASPACE
|
||||
LD A,20H ; space code
|
||||
CP C ; space?
|
||||
JR NZ, TOK
|
||||
IGNLB CP (HL)
|
||||
JR NZ,TOK
|
||||
INC L
|
||||
JR IGNLB
|
||||
TOK PUSH HL
|
||||
COUNT INC B
|
||||
INC L
|
||||
LD A,(HL)
|
||||
CP C
|
||||
JR Z,ENDTOK
|
||||
RLA
|
||||
JR NC,COUNT
|
||||
DEC L
|
||||
ENDTOK INC L
|
||||
LD (LBP), HL
|
||||
LD A,B
|
||||
LD (DE), A
|
||||
INC DE
|
||||
POP HL
|
||||
LD C,B
|
||||
LD B,0
|
||||
LDIR ; Move token to dictionary
|
||||
EXX
|
||||
JP (IY)
|
||||
|
||||
|
||||
; SEARCH Primitive
|
||||
DB 6,'SEA'
|
||||
DW AT - 6 ; Point to the Entry proper.
|
||||
SEARCH DW $ + 2
|
||||
EXX ; save registers
|
||||
POP HL ; start of header
|
||||
TESTIT PUSH HL ; save start of header
|
||||
LD DE,(DP) ;dictionary pointer.
|
||||
LD C, 0 ; used with B as false flag
|
||||
LD A,(DE) ;get dictionary token length
|
||||
CP (HL) ; same as keyword length?
|
||||
JP NZ, NXTHDR ; go to next entry in linked list.
|
||||
CP 4 ; Is length over 3?
|
||||
JR C, BEL04 ; skip set 3
|
||||
LD A, 3 ; length = 3
|
||||
BEL04 LD B, A
|
||||
NEXTCH INC HL ; Bump header
|
||||
INC DE ; bump dictionary pointer.
|
||||
LD A, (DE) ; next character
|
||||
CP (HL)
|
||||
JR NZ, NXTHDR ; Go to next header entry.
|
||||
DJNZ NEXTCH ; next character
|
||||
POP HL ; start of found header
|
||||
LD DE,6 ; start plus 6
|
||||
ADD HL,DE ; == Word Address
|
||||
PUSH HL ; push WA; BC = 0 for Flag.
|
||||
JR FLAG
|
||||
NXTHDR POP HL ; start of current header
|
||||
LD DE,4 ; plus 4 == Link Address (pointer to next entry)
|
||||
ADD HL, DE ; To Next keyword
|
||||
LD E, (HL) ; get link address
|
||||
INC HL
|
||||
LD D, (HL)
|
||||
EX DE, HL
|
||||
LD A, H
|
||||
OR L
|
||||
JR NZ, TESTIT ; not 0, test next header.
|
||||
LD C, 1 ; false
|
||||
FLAG PUSH BC ; push flag
|
||||
EXX ;Restore registers
|
||||
JP (IY) ; back to NEXT
|
||||
|
||||
; @ - AT (Assembler won't allow @ for a label.)
|
||||
DB 1,'@',0,0 ; Search will find length of 1 and only look at first char. others are spaces to fill 3 bytes.
|
||||
DW CONTEXT - 6
|
||||
AT DW $ + 2
|
||||
POP HL
|
||||
LD E, (HL) ; low byte at address
|
||||
INC HL
|
||||
LD D, (HL) ; high byte
|
||||
PUSH DE
|
||||
JP (IY)
|
||||
|
||||
; CONTEXT, push address of Vocabulary to stack.
|
||||
DB 7,'CON'
|
||||
DW EXECUTE - 6
|
||||
CONTEXT DW $ + 2
|
||||
|
||||
|
||||
; EXECUTE primitive needs a dictionary entry for defining words.
|
||||
; This is a model for all other Primitive words that will be added to the dictionary
|
||||
;
|
||||
DB 7,'EXE' ; Header for dictionary search
|
||||
DW 0 ; Link address 0000 == End of Linked List.
|
||||
EXECUTE DW $ + 2 ; Address of EXECUTE.
|
||||
POP HL ; primitive code.
|
||||
JP RUN
|
||||
|
||||
;---------- End of Dictonary Entries
|
||||
|
||||
;
|
||||
; ?SEARCH - Secondary to search dictionary.
|
||||
QSEARCH DW $ + 2
|
||||
DW COLON
|
||||
DW CONTEXT
|
||||
DW AT
|
||||
DW AT
|
||||
DW SEARCH
|
||||
DW DUP
|
||||
DW @IF
|
||||
|
||||
|
||||
; TYPE - String with length byte (0a1234567890) printed to console.
|
||||
TYPE DW $ + 2
|
||||
TYPEIT POP DE ; get address of string
|
||||
PUSH HL ; save WA
|
||||
PUSH BC ; Save IR.
|
||||
EX DE,HL
|
||||
LD B,(HL)
|
||||
INC HL
|
||||
ONECHAR LD A,(HL)
|
||||
CALL _ECHO
|
||||
INC HL
|
||||
DJNZ ONECHAR
|
||||
POP BC ; Restore IR
|
||||
POP HL ; Restore WA
|
||||
JP NEXT
|
||||
|
||||
|
||||
|
||||
|
||||
; INLINE
|
||||
INLINE DW $ + 2 ;header address
|
||||
PUSH BC ; Save IR
|
||||
ISTART CALL _CRLF ; Issue CR / LF on terminal for new input
|
||||
LD HL, LBADD ; Buffer
|
||||
LD (LBP), HL
|
||||
LD B, LENGTH
|
||||
CLEAR LD (HL), SPACE
|
||||
INC HL
|
||||
DJNZ CLEAR
|
||||
ZERO LD L,0
|
||||
INKEY CALL _KEY
|
||||
CP LINEDEL ; CTRL-X is Line Delete
|
||||
JR NZ,TSTBS
|
||||
CALL _ECHO
|
||||
JR ISTART
|
||||
TSTBS CP BKSP ; backspace CTRL-H
|
||||
JR NZ, TSTCR
|
||||
DEC HL
|
||||
JP M,ZERO
|
||||
LD (HL), SPACE
|
||||
ISSUE CALL _ECHO
|
||||
JR INKEY
|
||||
TSTCR CP CR
|
||||
JR Z,LAST1
|
||||
BIT 7,L
|
||||
JR NZ,IEND
|
||||
SAVEIT LD (HL),A
|
||||
CP 61H ; Less than LC A ?
|
||||
JR C,NOTLC
|
||||
CP 7BH ; MORE THAN LC Z?
|
||||
JR NC,NOTLC
|
||||
RES 5,(HL)
|
||||
NOTLC INC L
|
||||
JR ISSUE
|
||||
IEND DEC L
|
||||
LD C,A
|
||||
LD A,BKSP
|
||||
CALL _ECHO
|
||||
LD A,C
|
||||
JR SAVEIT
|
||||
LAST1 LD A, SPACE
|
||||
CALL _ECHO
|
||||
POP BC
|
||||
JP (IY) ; Return to NEXT inner interpreter.
|
||||
|
||||
; Push 20h to stack, will pop into BC in TOKEN, and BC will be 0020h
|
||||
ASPACE DW $ + 2
|
||||
LD DE, 20h
|
||||
PUSH DE
|
||||
JP (IY)
|
||||
|
||||
|
||||
|
||||
; ABSENT?
|
||||
; - NO -> ?EXECUTE -> ASPACE
|
||||
; - YES -> NUMBER
|
||||
|
||||
; ?EXECUTE - Execute Secondary.
|
||||
QEXECUTE DW $ + 2
|
||||
NOP
|
||||
JP (IY)
|
||||
|
||||
QNUMBER DW $ + 2
|
||||
NOP
|
||||
JP (IY)
|
||||
|
||||
@IF DW $ + 2
|
||||
POP HL
|
||||
LD A,L
|
||||
OR H
|
||||
JP Z,_ELSE
|
||||
INC BC
|
||||
JP (IY)
|
||||
|
||||
_ELSE LD A,(BC) ; get jump byte
|
||||
ADD A, C ; add to IR
|
||||
LD C, A ; Reset IR
|
||||
JR NC, OUT ; Past Page?
|
||||
INC B ; Yes
|
||||
OUT JP (IY)
|
||||
|
||||
|
||||
|
||||
DUP DW $ + 2
|
||||
POP HL
|
||||
PUSH HL
|
||||
PUSH HL
|
||||
JP (IY)
|
||||
|
||||
; For Z80 MC - DDT was changed to use RST 6 since the hardware uses RST 7.
|
||||
; For Standard CP/M
|
||||
TILHALT DW $ + 2
|
||||
IF STD_CPM = 1
|
||||
RST 7
|
||||
ELSE
|
||||
RST 6
|
||||
ENDIF
|
||||
|
||||
|
||||
; INVALID NUMBER?
|
||||
; NO -> ASPACE
|
||||
; YES -> QUESTION
|
||||
|
||||
; QUESTION
|
||||
QUESTION DW $ + 2
|
||||
LD HL,(DP)
|
||||
INC HL
|
||||
BIT 7,(HL) ; IF BIT SET, A TERMINATOR
|
||||
JR Z,ERROR ;NOT SET ERROR
|
||||
LD DE,OK
|
||||
PUSH DE
|
||||
JP (IY)
|
||||
ERROR CALL _CRLF
|
||||
LD IY,RETURN
|
||||
JP TYPE
|
||||
RETURN LD DE, QMSG
|
||||
JP _PATCH
|
||||
|
||||
; GOTO TYPE
|
||||
|
||||
|
||||
; Internals
|
||||
|
||||
QMSG DB '?', 0
|
||||
OK DB 'OK',0
|
||||
|
||||
; PATCH internal routine.
|
||||
_PATCH DB 0
|
||||
|
||||
|
||||
|
||||
|
||||
;----------------------------------------
|
||||
; CP/M Machine Specific routines
|
||||
;
|
||||
; * Internal Routines interfacing with Operating System.
|
||||
; * _ECHO - Echo a character to terminal
|
||||
; * _KEY - Read a key from terminal
|
||||
; * _CRLF - Output CR/LF to terminal
|
||||
;----------------------------------------
|
||||
;; Handy Constants
|
||||
CR EQU 0DH
|
||||
LF EQU 0AH
|
||||
DOLLAR EQU 24H
|
||||
ESC EQU 1BH
|
||||
CTRLC EQU 03H
|
||||
|
||||
; Screen print calls
|
||||
CHAR_IN EQU 03H
|
||||
C_STAT EQU 0BH
|
||||
C_RAWIO EQU 06H
|
||||
|
||||
; til has own write str using _ECHO
|
||||
;WRITESTR EQU 9H
|
||||
PRTCHR EQU 02H
|
||||
BDOS EQU 05H
|
||||
|
||||
; Output one character.
|
||||
; A = Input Char.
|
||||
; preserve BC register.
|
||||
; preserve HL register.
|
||||
_ECHO
|
||||
PUSH HL
|
||||
PUSH BC
|
||||
PUSH DE
|
||||
LD D,A
|
||||
LD E,A
|
||||
LD C, PRTCHR
|
||||
CALL BDOS
|
||||
POP DE
|
||||
POP BC
|
||||
POP HL
|
||||
RET
|
||||
|
||||
; Get a key
|
||||
_KEY
|
||||
; Preserve BC, DE, and HL.
|
||||
PUSH BC
|
||||
PUSH DE
|
||||
PUSH HL
|
||||
WAITKEY LD C, C_RAWIO
|
||||
LD DE,FFFFh
|
||||
CALL BDOS
|
||||
OR A
|
||||
JR Z,WAITKEY
|
||||
POP HL
|
||||
POP DE
|
||||
POP BC
|
||||
; Character returned in A register.
|
||||
RET
|
||||
|
||||
; Output CR LF to console.
|
||||
_CRLF
|
||||
PUSH AF
|
||||
LD A, CR
|
||||
CALL _ECHO
|
||||
LD A, LF
|
||||
CALL _ECHO
|
||||
POP AF
|
||||
RET
|
||||
|
||||
; Constants
|
||||
;
|
||||
LINEDEL EQU 18H ; ctrl-x line delete
|
||||
SPACE EQU 20h ; space
|
||||
BKSP EQU 08h ; ctrl-H backspace
|
||||
|
||||
; Variables
|
||||
BASE DB 0 ; BASE for restart/warm start
|
||||
MODE DB 0 ; MODE
|
||||
LBP DW 0 ; line buffer pointer
|
||||
LENGTH EQU 128 ; buffer length
|
||||
ORG 400h ; put on page boundary
|
||||
LBADD DS 128 ; text input buffer
|
||||
LBEND DW 0
|
||||
|
||||
; CORE points to Core Vocab (first entry in dictionary)
|
||||
CORE DW DICT_BEG
|
||||
|
||||
;---- CONTEXT... points to Vocabulary?
|
||||
CTXTPTR DW DP
|
||||
; Dictonary pointer
|
||||
DP DW DICT
|
||||
STACK EQU 8000h
|
||||
|
||||
; Strings
|
||||
RSTMSG DB ' TIL RESTART'
|
||||
SRTMSG DB ' WELCOME TO RETRO TIL'
|
||||
|
||||
|
||||
DICT DS 4000
|
||||
|
||||
|
||||
|
||||
|
||||
END 0000
|
37
altair8800/rand.asm
Normal file
37
altair8800/rand.asm
Normal file
@ -0,0 +1,37 @@
|
||||
; Altair 8080 LCG Random Number Generator
|
||||
|
||||
ORG 100h ; Start of program
|
||||
|
||||
MAIN:
|
||||
LXI B, 0Ah ; Initialize loop counter (10 iterations)
|
||||
MVI C, 0 ; Initialize seed value (you can change this)
|
||||
MVI D, 13h ; Multiplier (you can change this)
|
||||
MVI E, 07h ; Increment (you can change this)
|
||||
|
||||
RANDOM_LOOP:
|
||||
; Compute the next random number using LCG formula
|
||||
MOV A, C
|
||||
MVI H, 0
|
||||
MOV L, D
|
||||
DAD H
|
||||
XTHL
|
||||
MOV A, L
|
||||
ADD E
|
||||
MOV L, A
|
||||
JNC SKIP_CARRY
|
||||
INR H
|
||||
|
||||
SKIP_CARRY:
|
||||
XTHL
|
||||
MOV C, A
|
||||
|
||||
; Output the random number
|
||||
; You can replace this with any code to use the random number
|
||||
; For simplicity, we'll just output it to the console
|
||||
OUT 01h
|
||||
|
||||
; Decrement loop counter
|
||||
DCR B
|
||||
JNZ RANDOM_LOOP
|
||||
|
||||
END
|
10
src/BLINKEN.BAS
Normal file
10
src/BLINKEN.BAS
Normal file
@ -0,0 +1,10 @@
|
||||
1 PINM 13,1
|
||||
10 E=DREAD(2)
|
||||
20 IF E=1 THEN GOTO 100
|
||||
30 DWRITE 13,0
|
||||
40 DELAY 500
|
||||
50 DWRITE 13,1
|
||||
60 DELAY 500
|
||||
70 GOTO 10
|
||||
100 DWRITE 13,0
|
||||
110 END
|
@ -33,10 +33,13 @@ LF EQU 0AH
|
||||
DOLLAR EQU 24H
|
||||
ESC EQU 27
|
||||
|
||||
; Screen print calls
|
||||
; CP/M calls
|
||||
WRITESTR EQU 9H
|
||||
PRTCHR EQU 02H
|
||||
BDOS EQU 5H
|
||||
CHRIN EQU 01H
|
||||
BDOS EQU 05H
|
||||
CONSOLEOUT EQU 06H
|
||||
CONSOLEIN EQU 0AH
|
||||
|
||||
ORG 100h
|
||||
|
||||
@ -45,31 +48,67 @@ MAIN:
|
||||
CALL PUTS
|
||||
|
||||
READING:
|
||||
CALL INPUT
|
||||
LD DE, PROMPT
|
||||
CALL PUTS
|
||||
; PUSH HL
|
||||
; CALL INPUT
|
||||
LD C, CONSOLEIN
|
||||
CALL BDOS
|
||||
|
||||
call PUTS
|
||||
; POP HL
|
||||
LD DE, NEWLINE
|
||||
CALL PUTS
|
||||
JP READING
|
||||
|
||||
INPUT:
|
||||
LD C,11 ; C_STAT
|
||||
LD DE,0
|
||||
CALL BDOS
|
||||
OR A
|
||||
JR Z,INPUT
|
||||
; LD HL, BUFFER
|
||||
; LD B, BUFFER_SIZE
|
||||
|
||||
LD C,6
|
||||
LD DE,-1
|
||||
; ; Read first character in, process it, and output
|
||||
; ; it to the console
|
||||
; LD C, CHRIN
|
||||
; LD DE, -1
|
||||
; CALL BDOS
|
||||
|
||||
; CP 03H
|
||||
; JP Z, EXIT
|
||||
|
||||
; CP 0DH
|
||||
; JP Z, INPUTEX
|
||||
|
||||
; LD (HL), A
|
||||
; INC HL
|
||||
; ; ADD HL, HL
|
||||
; DEC B
|
||||
|
||||
INPUTLP:
|
||||
LD C, CHRIN
|
||||
LD DE, -1
|
||||
CALL BDOS
|
||||
OR A
|
||||
JP Z,INPUT
|
||||
|
||||
CP 03H
|
||||
JP Z, EXIT
|
||||
|
||||
CP 0DH
|
||||
JP Z, EXIT
|
||||
JP Z, INPUTEX
|
||||
|
||||
LD D, A
|
||||
LD E, A
|
||||
CALL PUTC
|
||||
; LD (HL), A
|
||||
; INC HL
|
||||
; ; ADD HL, HL
|
||||
; DEC B
|
||||
; DJNZ INPUTLP
|
||||
JP INPUTLP
|
||||
|
||||
INPUTEX:
|
||||
; LD (HL), DOLLAR
|
||||
; INC HL
|
||||
; LD A, 0H
|
||||
; LD (HL), A
|
||||
; ADD HL, HL
|
||||
; LD A, DOLLAR
|
||||
; LD (HL), A
|
||||
; LD HL, BUFFER
|
||||
RET
|
||||
|
||||
; Print a string
|
||||
@ -78,18 +117,20 @@ PUTS:
|
||||
CALL BDOS
|
||||
RET
|
||||
|
||||
; Print a character
|
||||
PUTC:
|
||||
LD C, PRTCHR
|
||||
CALL BDOS
|
||||
RET
|
||||
|
||||
CL: DB ESC,"[H",ESC,"[2J$"
|
||||
BUFFER: DS BUFFER_SIZE
|
||||
GREET: DB "William Moore's FORTH TIL!", CR, LF, 0H
|
||||
PROMPT: DB ESC, ESC, "$ ", 0H
|
||||
BUFFER DS 255
|
||||
EOS DB "$"
|
||||
GREET DB "William Moore's FORTH TIL!", CR, LF, "$"
|
||||
PROMPT DB "> $"
|
||||
NEWLINE DB CR, LF, "$"
|
||||
|
||||
|
||||
EXIT:
|
||||
JP 0h
|
||||
; JP 0h
|
||||
HALT
|
||||
|
||||
END
|
Loading…
Reference in New Issue
Block a user