📄 lsrules.asm
字号:
TITLE LSRULES - functions which map opcodes to 'list-node' structs
;======================================================================
; Module: LsRules.asm
;
; Purpose:
; Contains functions which map opcodes to their equivalent
; 'list-node' structures. See lsmain.asm for general comments.
;
;
;=======================================================================*/
include version.inc
LSRULES_ASM = ON
includeOnce architec
includeOnce context
includeOnce heap
includeOnce lister
includeOnce lsint
includeOnce opmin
includeOnce pcode
includeOnce prsorw
includeOnce qblist
includeOnce rtps
includeOnce scanner
assumes CS,LIST
assumes DS,DGROUP
assumes SS,DGROUP
assumes ES,NOTHING
sBegin DATA
PUBLIC psdLsIncl
psdLsIncl dw 0 ;pointer to buffer filled by Lr_Include
sEnd DATA
sBegin LIST
assumes CS,LIST
subttl Literal opcode listers
;------------------------------------------------------------------
; Literal opcode listers
;------------------------------------------------------------------
; List rule for opcode which encodes I2 literal in high bits of opcode
ListRule LrLitI2
mov ax,[opList] ;ax = opcode + high bit operand
.erre OPCODE_MASK EQ 03ffh ; Assure SHR/SHR is correct
mov al,ah ;al = high-bit operand * 4
shr al,1
shr al,1 ;al = high-bit operand
cbw ;ax = high-bit operand
push si ;preserve si
xchg si,ax ;si = literal number
mov ax,LIT_LINENUM*256+2 ;ah = LIT_LINENUM, al = 2 (bytes)
call NewNum ;ax points to new number node(ax)
pop si ;restore si
jmp SHORT PushRootStg1
ListRule LrLitNum
mov ax,[mpOpLsArg + bx] ;opcode's argument
xchg ah,al
;al = constant value size (2, 4, or 8)
;ah = constant type
; (LIT_D2, LIT_O2, LIT_H2,
; LIT_D4, LIT_O4, LIT_H4,
; LIT_R4, LIT_R8)
call NewNum ;ax points to new number node(ax)
PushRootStg1:
call PushRoot
J0_Stg1Loop:
jmp Stg1Loop ;return to outer loop
; [...] ==> [[" string "] ...]
; Note: can't be [" string "] because each expression term must
; be 1 root node.
;
ListRule LrLitSD
lods WORD PTR es:[si] ;ax = cbText
call PushRootQStr ;push '"' str_node '"' to root stack
jmp Stg1Loop ;push temp list to root as 1 node
; and return to outer loop
subttl Remark related list rules
;------------------------------------------------------------------
; Remark related list rules
;------------------------------------------------------------------
;***************************************************************************
; LrStRem
; Purpose:
; List the opcode opStRem(cbText, text)
; [] ==> [text REM]
;
;***************************************************************************
ListRule LrStRem
call PushRootOpRw ;push "REM" node to root's stack
LrStRem1:
lods WORD PTR es:[si] ;ax = cbText
or ax,ax
je AtLeast1Spc ;brif cbText = 0
call NewEnStr ;ax = offset to new node
jmp PushRootStg1 ;push node ax to root stack
; and return to outer loop
;so opStRem(0)op_Static will list as REM $STATIC and not REM$STATIC
;
AtLeast1Spc:
PushRootSpcStg1:
call PushRootSpc
jmp SHORT J0_Stg1Loop ;return to outer loop
str255Include DB 11,'$INCLUDE',58d,32d,39d ; $INCLUDE: '
str255Static DB 7,'$STATIC'
str255Dynamic DB 8,'$DYNAMIC'
ListRule Lr_Static
mov [fLsDynArrays],0 ;set static flag for AsciiSave
mov ax,LISTOFFSET str255Static
Lr_Static1:
call NewCsStr
call PushRoot
jmp SHORT LrStRem1
ListRule Lr_Dynamic
mov [fLsDynArrays],1 ;set static flag for AsciiSave
mov ax,LISTOFFSET str255Dynamic
jmp SHORT Lr_Static1
; List opcode op_Include, which is generated for syntax: $INCLUDE: 'filename'
; If the global variable psdLsIncl is non-zero, copy include filename
; to psdLsIncl->pb and set psdLsIncl->cb.
;
ListRule Lr_Include
mov ax,LISTOFFSET str255Include
call NewCsStr ;ax = node for ($INCLUDE ')
call PushRoot
lods WORD PTR es:[si] ;ax = cbText
cmp [psdLsIncl],NULL
je NoSdLsIncl
;es = segment of text table
;si = offset into text table to string
;ax = length of string (including terminating 0)
push si
push di
push ax
mov di,si ;es:di points to string
mov cx,-1
mov al,27H ;look for terminating '
repne scasb
not cx ;cx = length including '
dec cx ;cx = filename length
pop ax
mov di,[psdLsIncl] ;di points to destination sd
mov [di.SD_cb],cx ;save length of string
mov di,[di.SD_pb] ;di points to destination buffer
push es
push ds
pop es ;es = DGROUP
pop ds ;ds = text table's segment
assumes DS,NOTHING
rep movsb ;copy string to psdLsIncl's buffer
push es
push ds
pop es ;es = text table's segment
pop ds ;ds = DGROUP
assumes DS,DGROUP
pop di
pop si
;si = offset into text table to string
;ax = length of string to push
NoSdLsIncl:
call PushString ;ax = node for consumed string operand
jmp SHORT J1_Stg1Loop ;return to outer loop
ListRule LrQuoteRem
lods WORD PTR es:[si] ;ax = cbText (including column field)
dec ax ;don't count column field
dec ax
push ax ;save it
lods WORD PTR es:[si] ;ax = column field
call NewCol ;ax = "advance to column(ax)" node
call PushRoot ;list it
mov al,39 ;al = ASCII code for single quote '
call PushRootChar ;list '
pop ax ;restore ax = size of string
call NewEnStr ;ax = offset to new string node
jmp PushRootStg1 ;push node ax to root stack
; and return to outer loop
PushString2 PROC NEAR
dec ax ;don't count link field
dec ax
inc si ;skip link field
inc si
PushString2 ENDP
;fall into PushString
PushString PROC NEAR
call NewStr ;ax = offset to new node
jmp PushRoot ;make it new root of tree
;return to caller
PushString ENDP
ListRule LrStData
call PushRootOpRw ;list DATA
lods WORD PTR es:[si] ;ax = cbText (including link field)
push ax ;save length
dec ax ;don't count 0-terminator
call PushString2 ;ax = node for consumed string operand
pop ax
and ax,1 ;ax = 1 if string was odd length
shl ax,1 ;ax = 2 if string was odd length
add si,ax ;si points beyond 0-terminator
jmp SHORT J1_Stg1Loop
ListRule LrReParse
lods WORD PTR es:[si] ;ax = cbText (including link field)
PushString2Stg1:
call PushString2 ;ax = node for consumed string operand
J1_Stg1Loop:
jmp Stg1Loop ;return to outer loop
;List rule for SQL source lines. Special processing is needed for
;setting colLsCursor in case of error occuring within the SQL statement.
subttl Control Flow Opcodes
;------------------------------------------------------------------
; Control Flow Opcodes
;------------------------------------------------------------------
; [...] ==> [space ELSE space ...] if single line ELSE
; [...] ==> [ELSE ...] if block ELSE
;
ListRule LrStElse
inc si ;skip link field
inc si
ListRule LrStElseNop
mov [lsBosFlagsWord],0 ;reset beginning of stmt flags
test [lsBolFlags],FBOL_GotIf
jne GotSingleElse ;brif we've seen an IF opcode
jmp LrRwSpc ;just list the ELSE
GotSingleElse:
; If listing ELSE after :<spaces>, we don't have to emit a space
; before listing the ELSE reserved word, opBosSp already did.
mov bx,di
add bx,[bdNodes.BD_pb] ; convert offset to ptr
cmp [bx + LN_type - CBLNT_CHAR],LNT_COL
je NoSpc ; brif opBosSp was just listed
call PushRootSpc ;emit blank before reserved word
NoSpc:
call PushRootOpRwSpc ;push opcode's reserved word
jmp SHORT J1_Stg1Loop ;return to outer loop
; [...] ==> [END space <opcode's resword> ...]
;
ListRule LrStEndDef
inc si ;skip filler field operand
inc si
ListRule LrStEndType
inc si ;skip link field operand
inc si
ListRule LrStEndIfBlock
ListRule LrStEndSelect
mov ax,ORW_END
call PushRootRwSpc
jmp LrRw ;list TYPE, IF, SELECT
; and return to outer loop
; [...] ==> [EXIT space <opcode's resword> ...]
;
ListRule LrStExitDo
ListRule LrStExitFor
inc si ;consume oText operand
inc si
mov ax,ORW_EXIT
call PushRootRwSpc
jmp LrRw ;list DO or FOR
; and return to outer loop
; [exp ...] ==> [[THEN space exp space IF/ELSEIF] ...]
;
IfThen PROC NEAR
or [lsBolFlags],FBOL_GotIf ;set static flag for LrStElse
call PushTempOpRwSpc ;push IF/ELSEIF onto temp stack
call PopRootPushTemp ;move expNode from root to temp stk
call PushTempSpc ;emit blank before THEN
mov ax,ORW_THEN
call PushTempRwSpc ;push THEN
call PushList ;move temp stk to root as 1 node
ret
IfThen ENDP
ListRule LrNoList3
inc si ;skip operand
inc si
ListRule LrNoList2
inc si ;skip operand
inc si
ListRule LrNoList1
Skip1Stg1:
inc si ;skip link field
inc si
ListRule LrNoType
ListRule LrNoList
jmp SHORT J2_Stg1Loop ;return to outer loop
; [exp ...] ==> [space [THEN space exp space IF] ...]
;
ListRule LrStIfBlock
ListRule LrStElseIf
ListRule LrStIf
call IfThen ;push [[THEN space exp space IF]]
jmp SHORT Skip1Stg1 ;skip operand
;return to outer loop
; [exp ...] ==> [label space [THEN space exp space IF] ...]
;
; [...] ==> [oNamLabel ...]
;
ListRule LrStIfLab
ListRule LrStIfLabDirect
call IfThen ;push [[THEN space exp space IF]]
ListRule LrStElseLab
ListRule LrStElseLabDirect
PushRootLabelStg1:
call PushRootLabel ;consume and push <label>
jmp SHORT J2_Stg1Loop ;return to outer loop
; [exp ...] ==> [label space [GOTO space exp space IF] ...]
;
ListRule LrStIfGotoLab
or [lsBolFlags],FBOL_GotIf ;set static flag for LrStElse
call PushTempOpRwSpc ;push IF onto temp stack
call PopRootPushTemp ;move expNode from root to temp stk
call PushTempSpc ;emit blank before THEN
mov ax,ORW_GOTO
call PushTempRw
call PushList ;move temp stk to root as 1 node
call PushRootSpc
jmp SHORT LrStElseLab ;consume and push <label> and
; return to outer loop
; [exp ...] ==> [<opcode's resword> space exp ...]
;
ListRule LrEvStop
ListRule LrEvOn
ListRule LrEvOff
call PushRootSpc ;emit blank before opcode's res word
jmp LrRw ;list opcode's reserved word
; and return to outer loop
;***************************************************************************
; LrEvGosub
; Purpose:
; List the opcode opEvGosub(label), for example:
; opLit1 opEvSignal1 opEvGosub(label) ==> ON SIGNAL(1) GOSUB label
; [exp ...] ==> [label space [GOSUB space exp space ON] ...]
;
;***************************************************************************
ListRule LrEvGosub
mov ax,ORW_ON
call PushTempRwSpc ;push ON
call PopRootPushTemp ;move expNode from root to temp stk
call PushTempSpc ;emit blank before THEN
call PushTempOpRw ;push GOSUB onto temp stack
call PushList ;move temp stk to root as 1 node
call PushRootSpc ;emit blank before label's name
jmp short PushRootModLabelStg1 ;consume and push <label>
; and return to outer loop
; [...] ==> [label space GOSUB/GOTO/RESTORE/RESUME/RETURN]
;
ListRule LrRwLabel
ListRule LrStGosub
ListRule LrStGosubDirect
ListRule LrStGoto
ListRule LrStGotoDirect
ListRule LrStReturn1
call PushRootOpRwSpc ;push opcode's resword
jmp PushRootLabelStg1 ;consume and push <label>
; and return to outer loop
ListRule LrStRunLabel
ListRule LrStRestore1
call PushRootOpRwSpc ;push opcode's resword
jmp short PushRootModLabelStg1 ;consume and push <label>
; and return to outer loop
; If operand is UNDEFINED, list RESUME 0
; else list RESUME label
;
ListRule LrStResume
cmp WORD PTR es:[si],UNDEFINED
jne LrRwLabel ;brif not RESUME 0
call PushRootOpRwSpc ;list "RESUME "
Goto0:
inc si ;skip operand
inc si
mov al,'0'
call PushRootChar
J2_Stg1Loop:
jmp Stg1Loop ;return to outer loop
; [...] ==> [label space GOSUB space ERROR space ON]
;
ListRule LrStOnError
mov ax,ORW_ON
call PushRootRwSpc ;push ON
call PushRootOpRwSpc ;push ERROR
mov ax,ORW_GOTO
call PushRootRwSpc ;push GOTO
PushRootModLabelStg1:
cmp WORD PTR es:[si],UNDEFINED
je Goto0 ;brif ON ERROR GOTO 0
call NewModLabel ;ax = module level label node
call PushRoot
jmp SHORT J2_Stg1Loop ;return to outer loop
; [exp] ==> [[label, ..., label GOSUB/GOTO exp ON]]
;
ListRule LrStOnGosub
ListRule LrStOnGoto
mov ax,ORW_ON
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -