please dont rip this site

Scenix Sasmcond.src

;SAsmCond.src by James Newton 
;Structured conditionals for SASM (SXKey 2.0 version)
;Copyright 2000,2001,2002 James Newton <james@sxlist.com>

; This program is free software; you can redistribute it and/or modify
; it under the terms of the GNU General Public License version 2 as published
; by the Free Software Foundation.  Note that permission is not granted
; to redistribute this program under the terms of any other version of the
; General Public License.
;
; 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, write to the Free Software
; Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
;

;expects
	CPUCarry = 0 ;or 1
;	a variable called temp that can be used for some types of comparisons

;MACROS --------------------------------------------------------------------------

; BinJump <reg>, <Address> [, <Address>]
;  Call with the first parameter of the register to tbe tested and
;  the following parameters a list of addresses to jump to based on
;  the value of the register.
;  More effecient than a long jump table for 4 or fewer addresses

; GotoW <Address> [, <Address>]
;  Implements a jump table using space in the first low half page of memory.
;  must be invoked after all <Address>'s are defined.
;  Uses BinJump for less than 5 addresses

; Condition enum (IsZero,Eq,Lt,LE,IsNotZero,NE,Gt,GE,EqN,LtN,LEN,NEN,GtN,GEN)
;  enum values ending in N indicate that the second operand will be a constant

; Condition := [<reg>, <enum> | <reg>, <enum>, <reg> | <reg>, <enum>, <constant> ]

; Skz <reg>, [IsZero | IsNotZero]
;  Generates a skip if the reg is zero or not zero

; Skc <reg1>, [Eq | Lt | LE | NE | Gt | GE], <reg2>
;  Generates a skip if reg1 compaires as specified to reg2

; Skc <reg>, [EqN | LtN | LEN | NEN | GtN | GEN], <constant>
;  Generates a skip if reg compaires as specified to constant

; StackPUSH, StackPOP, StackTOS and stack1...
;  Provide a compile time stack to record and retrieve the addresses of 
;  locations were jumps need to be compiled once the jump-to address is
;  known. Used by the following macros:

; Repeat 
;	<statements> 
;	[forever | while <condition> | until <condition>]
;
;  compiles Skz or Skc with jumps to implement a structured loop

; DoIf <condition> 
;	<statements> 
; [
; DoElseIf <condition> 
;	<statements>
;	]...
; [
; DoElse 
;	<statements>
;	] 
; 	DoEndIf
;
;  Compiles Skz or Skc with jumps to implement a structured conditional
;  As many DoElseIf statements as desired may be included because each DoElseIf
;   links to the next one at run time so that if the first DoElseIf condition
;   is true, after its statements a jump will be compiled that will jump to
;   the simular jump after the next DoElseIf statements. To avoid this extra
;   run time, use DoSelect.

; DoSelect 
; [
; DoCase <condition>
;	<statements>
;	]...
; [
; DoCaseElse
;	<statements>
;	]
; DoEndSelect
;
;  Compiles Skz or Skc with jumps to implement a structured conditional
;  A limited number of DoCase statments can be compiled because each 
;   case compiles a jump to the end of the select after the statements
;   following the case condition and recording the position were these 
;   jumps must be org'd takes up space on the "stack" provided by 
;   StackPUSH, StackPOP and stack1...15

;See lable "Main" for start of examples


ConditionBase equ $0
IsZero	equ	ConditionBase + %0000
Eq	equ	ConditionBase + %0001
Lt	equ	ConditionBase + %0010 ;2
LE	equ	ConditionBase + %0011 ;3
IsNotZero equ	ConditionBase + %0100 ;8
NE	equ	ConditionBase + %0101 ;9
GE	equ	ConditionBase + %0110 ;10
Gt	equ	ConditionBase + %0111 ;11
EqN	equ	ConditionBase + %1001
LtN	equ	ConditionBase + %1010 ;2
LEN	equ	ConditionBase + %1011 ;3
NEN	equ	ConditionBase + %1101 ;9
GEN	equ	ConditionBase + %1110 ;10
GtN	equ	ConditionBase + %1111 ;11
;                                dabc
SkMskConst	equ	%1000
;column "d" (mask 8) shows which compare registers with constants and which with registers.
SkMskSwap	equ	%0100
;column "a" (mask 4) shows which are exact opposites of one another.
; e.g. Eq is the opposite of NE, Lt of GE, LE of Gt
SkMskNeq	equ	%0010
;column "b" (mask 2) shows which are inequalities and which are equalitites
SkMskC		equ	%0001
;column "c" (mask 1) differentiates the inequalities
SkMskFlip	equ	%0101
;Xor with condition to flip the inequality around X op Y becomes Y op X


Skc MACRO 3
	local SkcBank,pX,tst,pY
	noexpand
;Usage: Skc pX, Condition, pY
pX = \1
tst = \2
pY = \3
SkcBank = 0
 IF tst & SkMskConst
  IF pX == WReg && ((tst & SkMskNeq) > 1)
	expand
 mov temp, w	;WARNING! temp modified in macro.
	noexpand
   pX = temp
   ENDIF
  IF tst == GtN || tst == LEN
	expand
 mov w, #(pY + 1)
	noexpand
   ;if tst was GtN its now GE if it was LEN its Lt
   tst = (tst ^ SkMskC) & ~SkMskConst
  ELSE ; tst == GEN, LtN, NEN, EqN
   IF pX == WReg
    pX = pY
   ELSE
	expand
 mov w, #pY
	noexpand
    tst = tst  & ~SkMskConst
    ENDIF
   ENDIF
  pY = WReg
  ENDIF

 IF pX == WReg 
  IF (tst & SkMskNeq) > 1
   ;Flip the operation around.
   tst = tst ^ SkMskFlip
   ENDIF
  pX = pY
  pY = WReg
  ENDIF

;At this point, pX is NOT w

 IF pY != WReg
  IF pY>$0F ;are we about to access a non-global register?
	expand
 bank pY  ;non-global
	noexpand
   SkcBank = pY / $10
   ENDIF
  IF tst == Gt || tst == LE
	expand
 mov w, ++pY
	noexpand
   ;if tst was Gt its now GE if it was LE its Lt
   tst = tst ^ SkMskC
  ELSE ; tst = GE, Lt, Eq, NE
	expand
 mov w, pY
	noexpand
   ENDIF
  pY = WReg
  ENDIF
;At this point, pY is in W. pX is a register or a constant

 IF pX>$0F && (pX / $10) != SkcBank && tst & SkMskConst == 0
  ;are we about to access a non-global register in a new bank?
	expand
 bank pX  ;non-global
	noexpand
  ENDIF

 IF tst == Eq || tst == NE || tst == EqN || tst == NEN
  IF tst == EqN || tst == NEN
	expand
 xor w, #pX
	noexpand
   tst = tst  & ~SkMskConst
  ELSE
	expand
 xor w, pX
	noexpand
   ENDIF
  IF tst == Eq
	expand
 sz
	noexpand
  ELSE
	expand
 snz
	noexpand
   ENDIF
 ELSE
  IF CpuCarry
   IF tst == Gt || tst == LE
	expand
 clc
	noexpand
   ELSE
	expand
 stc
	noexpand
    ENDIF
   ENDIF

	expand
 mov w, pX - w
	noexpand
  IF tst == Lt || (tst == LE && CpuCarry)
	expand
 snc
	noexpand
  ELSE
	expand
 sc
	noexpand
   ENDIF
  ENDIF
  
 IF ( ( tst == Gt) || (tst == LE) ) && ! CpuCarry 
	expand
 snz
	noexpand
  ENDIF
 IF tst == Gt && !CpuCarry
	expand
 skip
	noexpand
  ENDIF
 ENDM


Skz MACRO parm, cond
;Usage: Skz register, [IsZero | IsNotZero]
	noexpand
 IF parm > $0F
	expand
 bank parm ;non-global
	noexpand
  ENDIF
	expand
 test parm
	noexpand
 IF cond == IsZero
	expand
 sz
	noexpand
 ELSE
  IF cond == IsNotZero
	expand
 snz
	noexpand
  ELSE
   error 'Usage: Skz register, [IsZero | IsNotZero]'
   ENDIF
  ENDIF  
 ENDM



StackTOS = -1
stacklet	MACRO ptr, val
	stack??ptr = val
	ENDM

stackget	MACRO ptr
	stackTOS = stack??ptr
	ENDM

stackptr = 0
stackTOS = 0

stackpush	MACRO	parm
	stackptr = stackptr + 1
	stacklet ?(stackptr), ?(stackTOS)
	stackTOS = parm
	ENDM

stackpop	MACRO
	if stackptr == 0 
	error 'stack underflow'
	endif
	stackget ?(stackptr)
	stackptr = stackptr - 1
	ENDM

StackPUSH 1
StackPUSH 2
StackPUSH 3
StackPUSH 4
StackPUSH 5
StackPUSH 6
StackPUSH 7
StackPUSH 8
StackPUSH 9
StackPUSH 10
StackPUSH 11
StackPUSH 12
StackPUSH 13
StackPUSH 14
StackPUSH 15

StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
;StackPOP
expand

Repeat MACRO
 noexpand	;incase expand was already on.
 StackPUSH $
 ENDM

Until MACRO 
	noexpand
 IF \0 == 2
  Skz \1,\2
 ELSE
  Skc \1,\2,\3
  ENDIF
 expand
 jmp @StackTOS
 noexpand
 StackPOP
 ENDM

While	MACRO 
	noexpand
 IF \0 == 2
  Skz \1,\2^SkMskSwap
 ELSE
  Skc \1,\2^SkMskSwap,\3
  ENDIF
	expand
 jmp @StackTOS
	noexpand
 StackPOP
 ENDM

WhileNotZeroDec MACRO 1
 noexpand
 expand
 djnz \1, @StackTOS
 noexpand
 StackPOP
 ENDM

WhileNotZero MACRO 0
 noexpand
 expand
 jnz @StackTOS
 noexpand
 StackPOP
 ENDM

WhileZero MACRO 0
 noexpand
 expand
 jz @StackTOS
 noexpand
 StackPOP
 ENDM

WhileNoCarry MACRO 0
 noexpand
 expand
 jnc @StackTOS
 noexpand
 StackPOP
 ENDM

WhileCarry MACRO 0
 noexpand
 expand
 jc @StackTOS
 noexpand
 StackPOP
 ENDM


Forever	MACRO 
	noexpand	;incase expand was already on.
	expand
 jmp @StackTOS
	noexpand
 StackPOP
 ENDM


link MACRO 2
 local ataddr, toaddr, temp
 noexpand
 ataddr = \1
 toaddr = \2
 temp =  $
 org ataddr  ; go back
 jmp @toaddr ;<- jmp to here
 org temp		; come forward
	ENDM

DoIf MACRO
 local ComeFrom
 noexpand
 IF \0 == 2
  Skz \1,\2
 ELSE
  Skc \1,\2,\3
  ENDIF
;***Save place to link failure of this test to the Else, ElseIf or EndIf code
 StackPUSH $	;save space here for a jmp
expand
:ComeFrom=$
 ;mp +FAIL
noexpand
org $+2 
 ENDM

DoElseIf MACRO
 local ComeFrom, ComeFromTo, FAIL, SUCCEED
 noexpand
;***If there is a previous succeed place, link it to this one
 IF (StackTOS >> 24) > 0
  link (StackTOS - (StackTOS >> 24)), $
  ENDIF
;***Setup place to Link the prev DoIf or DoElseIf success code out to the DoEndIf
 :S = $
expand
:ComeFrom=$
 ;mp +SUCCEED		
noexpand
 org $+2
;***Link the last DoIf or DoElseIf fail to the DoElseIf code
 ComeFromTo = ( (StackTOS & $FFFFFF) << 16 ) + $
 link (StackTOS & $FFFFFF), $
expand
:FAIL	=ComeFromTo
noexpand
 IF \0 == 2
	Skz \1,\2
 ELSE
	Skc \1,\2,\3
        ENDIF
;***Save place to link failure of this test to the Else, ElseIf or EndIf code
 StackTOS = ($ - :S)<<24 + $
expand
:ComeFrom=$
 ;mp +FAIL
noexpand
 org $+2
 ENDM

DoElse MACRO
	local ComeFrom, ComeFromTo, FAIL
 noexpand
;***If there is a previous succeed place, link it to this one
 IF (StackTOS >> 24) > 0
  link (StackTOS - (StackTOS >> 24)), $
  ENDIF
;***Setup place to Link the prev DoIf or DoElseIf success code out to the DoEndIf
:S = $
expand
:ComeFrom=$
 ;mp +SUCCEED
noexpand
 org $+2		; and leave space for it
;***Link the last DoIf or DoElseIf fail to the DoElse code
 link StackTOS, $
 ComeFromTo = (StackTOS << 16) + $
expand
:FAIL	=ComeFromTo
noExpand
 StackTOS = :S
 ENDM

DoEndIf MACRO
	local SUCCEED, FAIL, ComeFromTo
 noexpand
;***If there is a previous succeed place, link it to this one
 IF (StackTOS >> 24) > 0
  link (StackTOS - (StackTOS >> 24)), $
  ComeFromTo = ( (StackTOS - (StackTOS >> 24)) << 16 ) + $
expand
:SUCCEED=ComeFromTo
noexpand
  ENDIF
 link (StackTOS & $FFFFFF), $
 ComeFromTo = ( (StackTOS & $FFFFFF) << 16 ) + $
expand
:FAIL	=ComeFromTo
noexpand
 StackPOP
 ENDM


DoSelect:Level = 0
DoCase:Count = 0
DoCase:F = 0

DoSelect MACRO
 noexpand
 StackPUSH DoCase:Count - 1	;can't push a zero
 DoCase:Count = 0
 StackPUSH DoCase:F + 1	;can't push a zero
 DoCase:F = 0
 DoSelect:Level = DoSelect:Level + 1
 	ENDM

DoCase MACRO
 local ComeFrom, ComeFromTo, FAIL
 noexpand
 DoCase:Count = DoCase:Count - 1
 IF DoCase:Count < -1
;***Setup place to Link the prev Case success code out to the end
  StackPUSH $
expand
ComeFrom = $
 ;mp +SUCCEED		
noexpand
  org $+2
;***Link the last fail to this DoCase test code
  link DoCase:F, $
ComeFromTo = (DoCase:F << 16 ) + $
expand
:FAIL	=ComeFromTo
noexpand
  ENDIF
 IF \0 == 2
	Skz \1,\2
 ELSE
	Skc \1,\2,\3
        ENDIF
;***Save place to link failure of this test to the Else, ElseIf or EndIf code
 DoCase:F = $
expand
 ;mp +FAIL
noexpand
 org $+2
 ENDM

DoCaseElse MACRO
 local ComeFrom, ComeFromTo, FAIL
 noexpand
;***Setup place to Link the prev DoCase success code out to the DoCaseEnd
 StackPUSH $
expand
ComeFrom = $
 ;mp +SUCCEED
noexpand
 org $+2
;***Link the last fail to the DoCaseElse code
 link DoCase:F, $
 ComeFromTo = (DoCase:F << 16) + $
 DoCase:F = 0
expand
:FAIL	=ComeFromTo
noExpand
 ENDM

DoCaseEnd MACRO
 local ComeFromTo, FAIL, SUCCEED
 noexpand
;***If there is a previous succeed place, link it to this one
 IF DoCase:Count < 0
  REPT 0 - DoCase:Count
   link StackTOS, $
   ComeFromTo = ( StackTOS << 16 ) + $
expand
:SUCCEED=ComeFromTo
noexpand
   StackPOP
   ENDR
  ENDIF
 IF DoCase:F > 0 
  link DoCase:F, $
  ComeFromTo = (DoCase:F << 16) + $
expand
:FAIL	=ComeFromTo
noexpand
  ENDIF
 DoSelect:Level = DoSelect:Level - 1
 DoCase:F = StackTOS - 1
 StackPOP
 DoCase:Count = StackTOS + 1 ;correct for -1 when pushed.
 StackPOP
 ENDM

doifadr = 0
doendifadr = 0
doelsifadr = 0
doifl = 0

pageaddr = -1

;Can't use binjmp2 with forward references 
; because of a bug in SASM, 
; where MAIN:FOUR is a forward reference
;   361   m   ifdef MAIN:FOUR
;   362   m    if (pageaddr == MAIN:FOUR >> 9)
;****** macrotest.SRC(219) Line 362, Error 3, Pass 1:
; Symbol <MAIN:FOUR> is not defined
;if you really need forward references use this instead:

;binjmp2 MACRO index, one, two
; expand
; jnb index.0,@one
; jmp @two
; noexpand
; endm


binjmp2 MACRO index, one, two
;assumes that pageaddr is set to current value of page bits on entry.
 noexpand
 pageaddr = $>>9
 ifdef one
  if (pageaddr == one >> 9)
   expand
 jnb index.0,one
   noexpand
  else
   pageaddr = $ >> 9
   expand
 jnb index.0,@one
   noexpand
   endif
 else
   pageaddr = $ >> 9
  expand
 jnb index.0,@one
  noexpand
  endif
 ifdef two
  if (pageaddr == two >> 9)
   expand
 jmp two
   noexpand
  else
   pageaddr = $ >> 9
   expand
 jmp @two
   noexpand
   endif
 else
  pageaddr = $ >> 9
  expand
 jmp @two
  noexpand
  endif
 endm

binjmp4 MACRO index, one, two, three, four
	local :1set
;assumes that pageaddr is set to current value of page bits on entry.
 if (pageaddr == ($+9)>>9) ;:1set can't be more than 9 words away.
  expand
 jb index.1, :1set
  noexpand
 else
  expand
 sb index.1 
 page :1set
 jmp :1set
  noexpand
  endif
 binjmp2 index, one, two
 expand
:1set
 noexpand
 pageaddr = $ >> 9	;can't get here except by jump and so must be paged
 binjmp2 index, three, four
 endm

binjump MACRO
 local :2Set, :1Set, parms, index
parms = \0 - 1
index = \1
;Call with the first parameter of the register to tbe tested and
;the following parameters a list of addresses to jump to based on
;the value of the register.
;More effecient than a long jump table for 4 or fewer addresses
 expand
 page $
 noexpand
 pageaddr = $ >> 9
 if parms > 4
  if parms == 5
   expand
 jb \1.2, @\6	;=4
   noexpand
   binjmp4 \1,\2,\3,\4,\5
  else ;6 or more
   if (pageaddr == ($+19)>>9)
    expand
 jb \1.2, :2Set ;>4 ;@$+16
    noexpand
   else
    expand
 sb \1.2 
 page :2set
 jmp :2set ;>4 ;@$+16
    noexpand
    endif
   binjmp4 \1,\2,\3,\4,\5
   expand
:2Set
   noexpand
   pageaddr = $ >> 9	;can't get here except by jump and so must be paged
   if parms > 6
    if parms > 7
     binjmp4 \1,\6,\7,\8,\9
    else ;7
     expand
 jb \1.2, @\8 ;=2 or 6
     noexpand
     binjmp4 \1,\2,\3,\6,\7
     endif
   else ;6
    binjmp2 \1,\6,\7
    endif
   endif
 else ;4 or less
  if parms > 2
   if parms == 3
    expand
 jb \1.1, @\4 ;=2 or 6
    noexpand
    binjmp2 \1,\2,\3
   else ;4
    binjmp4 \1,\2,\3,\4,\5
    endif
 else ;2
  binjmp2 \1, \2, \3
  endif
 endif
 endm

GotoW MACRO
 local _SaveAddr, _GotoWPage, _GotoWTableBegin
 noexpand
;must be invoked after all parameters are defined 
;i.e. no forward references.
;if you manually expand the macro, forward refs may work?
 _SaveAddr = $
 _GotoWPage = _SaveAddr >> 9
 REPT \0
  IF (\% >> 9) != (_SaveAddr >> 9)
   _GotoWPage = (\% >> 9) ;
   ENDIF
  ENDR
;Do we need long jumps?
; we do if any of the jumps are to pages other than where the table is built.
; and we have to build the table in page 0 if we are not in a low half page
 IF _GotoWPage != (_SaveAddr >> 9) || ((_SaveAddr // $200) > $FF) ;has to be a long jump table
  IF \0 > 127
   ERROR 'Long jumps must be used so no more than 127 entries can be supported'
   ENDIF
  IF \0 == 2
   binjump WReg, \1, \2
   EXITM
   ENDIF
  IF \0 == 3
   binjump WReg, \1, \2, \3
   EXITM
   ENDIF
  IF \0 == 4
   binjump WReg, \1, \2, \3, \4
   EXITM
   ENDIF
;find a place to build the table
; how about right here? are we in a low half page? Do we have room?
  IF (($ & $100) == 0) && ( (\0*2) < ( $100 - ($ & $FF) ) )
   expand
 clc
   noexpand
   if myopts & ~OptRTCisW == 0 then
    expand
 rl WReg ;need long jumps
 ;WARNING: Insure OPTION:RWT = 0
    noexpand
   else
    expand
 mov temp, w
 add w, temp
 ;WARNING: temp modified by Macro
    noexpand
    endif
  ELSE
;can't build it where we are... how about in the space we set aside?
   IF LowHalfPage + (\0*2) + 1 > HighHalfPage
     ERROR 'Out of LowHalfPage Space'
     ENDIF
   expand
 org LowHalfPage
   noexpand
   _GotoWPage = -1
   ENDIF
 ELSE
;wow! All the destinations are in this page!
  IF \0 > 255
   ERROR 'No more than 255 entries can be supported'
   ENDIF
  IF \0 == 2
   binjump WReg, \1, \2
   EXITM
   ENDIF
  expand
 page $+2
  noexpand
  ENDIF
 expand	
 _GotoWTableBegin = $
 add PC,W ;jump to the jump
 noexpand
 REPT \0
  IF _GotoWPage == -1
   expand
 jmp @\%
   noexpand
  ELSE
 expand
 jmp \%
 noexpand
   ENDIF
  ENDR

 IF _GotoWPage == -1 ;located in low half page space
  LowHalfPage = $
  expand
 org _SaveAddr
 clc
  noexpand
  if myopts & ~OptRTCisW == 0 then
   expand
 rl WReg ;need long jumps
 ;WARNING: Insure OPTION:RWT = 0
   noexpand
  else
   expand
 mov temp, w
 add w, temp
 ;WARNING: temp modified by Macro
   noexpand
   endif
  expand
 page _GotoWTableBegin
 jmp _GotoWTableBegin
  noexpand
  ENDIF
 ENDM



file: /Techref/scenix/sasmcond.src, 17KB, , updated: 2002/12/19 17:56, local time: 2025/10/23 22:41,
TOP NEW HELP FIND: 
216.73.216.53,10-2-207-162:LOG IN

 ©2025 These pages are served without commercial sponsorship. (No popup ads, etc...).Bandwidth abuse increases hosting cost forcing sponsorship or shutdown. This server aggressively defends against automated copying for any reason including offline viewing, duplication, etc... Please respect this requirement and DO NOT RIP THIS SITE. Questions?
Please DO link to this page! Digg it! / MAKE!

<A HREF="http://www.massmind.org/Techref/scenix/sasmcond.src"> scenix sasmcond</A>

Did you find what you needed?

 

Welcome to massmind.org!

 

Welcome to www.massmind.org!

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

  .