Hmm...no one posted here at all for 2009, I hope this isn't a forbidden topic or something now. Anyway here's a few routines that I thought were kinda helpful



Code:

random2:
;input: b= max rand number
;output: a = rand num at max or below
   inc   b
   ld   a,r
randloop:
   add   a,b
   ret   c
   jp   randloop



This one could probably be optimized. Also, ld a,48 could be changed to ld a,c to center text at a manual x co-ordinate


Code:

CenterText:
;hl= start of string, y co-ordinate already loaded
;check how many chars
   ld   b,0
   push   hl
centertext1:
   ld   a,(hl)
   or   a
   jr   z,centertext2
   inc   hl
   cp   'f'   \   jr   z,ctinc3
   cp   't'   \   jr   z,ctinc3
   cp   's'   \   jr   z,ctinc3
   cp   'l'   \   jr   z,ctinc3
   cp   '\''   \   jr   z,ctinc3
   cp   ','   \   jr   z,ctinc3
   cp   'i'   \   jr   z,ctinc2
   cp   '!'   \   jr   z,ctinc2
   cp   '.'   \   jr   z,ctinc2
   cp   'z'   \   jr   z,ctinc5
   cp   'm'   \   jr   z,ctinc6
   cp   'w'   \   jr   z,ctinc6
   cp   ' '   \   jr   z,ctinc1
   jr   ctinc4
ctinc6:
   inc   b
ctinc5:
   inc   b
ctinc4:
   inc   b
ctinc3:
   inc   b
ctinc2:
   inc   b
ctinc1:
   inc   b
   jr   centertext1
centertext2:
   ld   a,48
   srl   b   ;div by 2
   sub   b   ;subtract from 48
   ld   (pencol),a
   pop   hl
   ret
Does that rand routine produce uniformly-distributed numbers?
KermMartian wrote:
Does that rand routine produce uniformly-distributed numbers?
It probably depends on when you call it.
r is a 7 bit value, dependent on the number of opcodes that have been read in.
elfprince13 wrote:
r is a 7 bit value, dependent on the number of opcodes that have been read in.
Indeed it is, but a cursory glance at the routine posted makes me worry that the results would be low-biased.
I've used it between user input to keep r fresh. Its only truly random for up to 256 combinations between inputs but when you don't need to use it that often, its smaller, faster and doesn't kill as many registers as bcall(_random) and whatever code would be put around it to keep it in a certain range.

I guess if you had an interrupt that used a bunch of T-states (like grayscale), then you could add something like this to the end of it to make r more random


Code:

    exx
    ex  af,af'
    ld  r,a
    ret
Here's a floodfill routine for small spaces. Try a large space, and you'll overflow the hardware stack. It also doesn't like reaching the top or bottom of the screen.

Code:
;l = y
;b = x
FloodFill:
   xor a
   ld d,0
   push de;
   push af
   ld a,b
   ld e,l
   ld h,00h
   ld d,h
   add hl,de
   add hl,de
   add hl,hl
   add hl,hl;y offset * 12
   ld e,a
   and 07h; bit offset within byte
   ld c,a
   srl e
   srl e
   srl e
   add hl,de; byte number in which to start
   ld de,gbuf
   add hl,de; address of byte
   ld b,a
   inc b
   xor a
   scf
Loop1:;bit offset to mask
   rla
   djnz Loop1
   push hl;byte
   push af;mask
MainLoop:
   pop bc
   pop hl
   ld a,b
   or h;a = 0 and h = 0
   ret z
   ld a,b
   ;expand left
   rlca
   jp nc,Skip1;jump if bit to left is in same byte
   dec hl
   bit 0,(hl)
   jp nz,Skip2;jump if not expanding there
   set 0,(hl)
   push hl
   push af;mask
Skip2:;inc hl and keep on going
   inc hl
   jp Skip3
Skip1:;expand left if within same byte
   and (hl)
   jp nz,Skip3;jump if not expanding
   ld a,b
   rlca
   push hl
   push af
   or (hl)
   ld (hl),a
Skip3:;expand right
   ld a,b
   rrca
   jp nc,Skip4;jump if bit to right is in same byte
   inc hl
   bit 7,(hl)
   jp nz,Skip5;jump if not expanding
   set 7,(hl)
   push hl
   push af
Skip5:;finish off expansion
   inc hl
   jp Skip6;done with right, now up
Skip4:;expand right within same byte
   and (hl)
   jp nz,Skip6;expand up
   ld a,b
   rrca
   push hl
   push af
   or (hl)
   ld (hl),a
Skip6:;expand up
   ld a,b
   ld de,12
   or a
   sbc hl,de;hl-12
   and (hl)
   jp nz,Skip7;expand down
   ld a,b
   push hl
   push af
   or (hl)
   ld (hl),a
Skip7:;expand down
   ld a,b
   ld de,24
   add hl,de
   and (hl)
   jp nz,MainLoop
   ld a,b
   push hl
   push af
   or (hl)
   ld (hl),a
   jp MainLoop

[/code]
Input: hl=object name eg. .db 6,"PRGM",0
Output:a=page hl=datastart de=dataend bc=datasize
Find an object regardless of whether or not its the the flash

Code:
FindFlash:
   rst 20h
FindFlashOp1:
   bcall(_chkfindsym)
   ret c
   ex de,hl
   ld a,b
   or a
   jr z,InRam
   push hl
   ld de,8000h
   ld bc,30
   bcall(8054h)
   ld a,(8009h)
   ld hl,800Ah
   add a,l
   ld l,a
   ld c,(hl)
   inc hl
   ld b,(hl)
   inc hl
   ld a,(8008h)
   pop de
   res 7,h
   add hl,de
   bit 7,h
   ret z
   res 7,h
   inc a
   jr FindFlashDone
InRam:
   ld c,(hl)
   inc hl
   ld b,(hl)
   inc hl
FindFlashDone:
   push hl
   add hl,bc
   ex de,hl
   pop hl
   ret


Input: a=getcsc keycode
Output: z=is pressed
Converts a getcsc keycode to both a keygroup and keymask, then checks the key with direct input allowing you to check multiple keys

Code:
CheckKey:
  ld b,$FE
  ld c,$01
ck_loop:
  dec a
  or a
  jr z,ck_getkey
  rlc c
  jr nc,ck_loop
  rlc b
  jr ck_loop
ck_getkey:
  ld a,$FF
  out (1),a
  ld a,b
  out (1),a
  nop \ nop
  in a,(1)
  and c
  ret
Nice ones, Anakclusmos. There's a very similar routine to that first one in the Ion libraries; it's called iDetect and is documented here:

http://dcs.cemetech.net/index.php?title=IDetect
I know Smile I just thought people would rather check by name than a string.
Anakclusmos wrote:
I know Smile I just thought people would rather check by name than a string.
Ah, of course, that's the main difference. Very nice, I'm sure that they would. Smile
Calc84's Optimized Version of My BC-A->BC


Code:
cpl
scf
adc a,c
ld c,a
jr c,$+3
dec b
To clarify why I did a cpl/scf/adc instead of a cpl/inc/add or neg/add, is that it handles the case of A=0 properly. Typically, SUB N and ADD A,-N give opposite carry outputs, but SUB 0 and ADD A,-0 both reset the carry flag. On the other hand, SCF \ ADC A,255 will set the carry flag like we want it to.
calc84maniac wrote:
To clarify why I did a cpl/scf/adc instead of a cpl/inc/add or neg/add, is that it handles the case of A=0 properly. Typically, SUB N and ADD A,-N give opposite carry outputs, but SUB 0 and ADD A,-0 both reset the carry flag. On the other hand, SCF \ ADC A,255 will set the carry flag like we want it to.
Indeed, thanks for that. Smile Needless to say, this code segment will work equally well for HL-A and DE-A as well as its original BC-A.
EDIT: Cleaning up and updating (bug fix and faster)
FindSym

This routine has four entry points with different inputs, but they all have the same documented outputs as rFindSym:

Input

Code:

;FindSym:
;Inputs:
;     OP1+1 contains the name of a symbol var. No type byte.
;
;FindVarSymDE
;Inputs:
;     DE points to the name of a symbol var
;
;FindVarSymHL
;Inputs:
;     HL points to the name of a symbol var
;
;findSymBC
;Inputs:
;     BC contains the name of the var to search. For example, if BC was 00AAh, it would search for Str1.


Output
Same as the documented outputs of rFindSym.

Code

Code:

;This routine has four useful entry points, especially findSymBC!

FindSym:
;Inputs:
;     OP1+1 contains the name of a symbol var. No type byte needed.
;Outputs:
;     Same as rFindSym
  ld de,OP1+1

FindVarSymDE:
;Inputs:
;     DE points to the name of a symbol var
;Outputs:
;     Same as rFindSym
  ex de,hl

FindVarSymHL:
;Inputs:
;     HL points to the name of a symbol var
;Outputs:
;     Same as rFindSym
  ld c,(hl)
  inc hl
  ld b,(hl)

findSymBC:
;Inputs:
;     BC contains the name of the var to search.
;     For example, if BC was 00AAh, it would search for Str1.
;Outputs:
;     Same as rFindSym

  ld hl,symtable-6
SearchLoop:
  ld a,c
  cp (hl)
  dec hl
  jr nz,advance_VATsym_ptr
  ld a,b
  cp (hl)
  jr z,Sym_Entry_found
advance_VATsym_ptr:
  ld de,-8
  add hl,de
  ex de,hl
  ld hl,(progPtr)
  sbc hl,de
  ex de,hl
  jr c,SearchLoop
  scf
Sym_Entry_found:
  inc hl
  inc hl
  ld b,(hl)
  inc hl
  ld d,(hl)
  inc hl
  ld e,(hl)
  inc hl
  inc hl
  inc hl
  ld a,(hl)
  ld c,3
  ret
I created a routine which creates a menu just like it's basic counterpart. Although this is very easy, and doesn't include complex coding, I hope it'll be of any use for anyone.

Code:

Menu:
;This routine will make a menu, almost the same as the TI-basic one.
;The screen will be cleared after this routine has been completed.
;INPUT: The text via the code stream.
;For example:
;    .DB "MenuTitle       ", 0   ;Menu Title, 16 bytes in length, followed by a 0.
;    .DB 3                              ;Number of options (max. = 7)
;    .DB "Option1       "         ;Option 1, 14 bytes in length
;    .DB "Option2       "         ;Option 2, 14 bytes in length
;    .DB "Option3       "         ;Option 3, 14 bytes in length
;OUTPUT:
;    If bit 0, (IY + Asm_flag1) is reset, the output is in C
;    If bit 0, (IY + Asm_flag1) is set, the output is in L
    RES AppAutoScroll, (IY + AppFlags)   ;Keep the screen from rolling
    b_call(_ClrLCDFull)      ;Clear the screen
    CALL TextInverseOn      ;Set textinverse
    ld hl, $0000      ;Set cursor to (0,0)
    ld (CurRow), hl
    POP HL         ;Pop the address of the menutitle
    LD D, H         ;Store HL into DE
    LD E, L
    b_call(_PutS)      ;Display the menutitle
    CALL TextInverseOff      ;Reset textinverse
    LD B, 17         ;Seventeen bytes to advance, including the 0
IncrementDE:
    INC DE
    DJNZ IncrementDE

;Drawing the text
    LD HL, $0201      ;Load the cursor for the first string
    LD (CurRow), HL
    LD HL, CurCol      ;Load the address of the cursor in HL
    EX DE, HL         ;Load the address of the number of rows to be drawn into HL
    LD C, (HL)         ;Load that number into C
    PUSH BC         ;Save C, because we are going to need it once more
    INC HL         ;Load the address of the first character of the first option in the menu
    LD B, 14         ;14 characters per string
DisplayText:
    LD A, (HL)         ;Load the first character of the string into A
    b_call(_PutC)      ;Display the character, and advance the cursor
    INC HL         ;Set the address for the next character
    DJNZ DisplayText      ;Repeat this 14 times
    EX DE, HL         ;HL = Address of cursor, DE = Address of MenuText
    LD (HL), 2         ;Set (CurCol) to 2
    EX DE, HL         ;HL = Address of MenuText, DE = Address of cursor
    LD B, 14         ;14 characters again.
    DEC C         ;Decline number of times to repeat this
    JR NZ, DisplayText      ;If the number of times to repeat this <> 0, repeat this
    POP BC         ;Restore C, the number of options in the menu
    PUSH HL         ;Store the address to jump to after the procedure has ended
    ld b, c         ;Store the number of options into B
    ld h, b         ;Save this number in h

;Drawing the numbers next
DrawNumbersComplete:
    ld c, 1                     ;C keeps track of the current option selected
DrawNumbersSet:
    ld b, h         ;Restore the number of numbers to be drawn into b.
    xor a         ;Reset CurCol to 0
    ld (CurCol), A
    ld l, $31         ;load the hexvalue of "1" in L
    ld de, CurRow      ;load the address of CurRow in DE
    ld a, 1         ;A keeps track of the current row to be drawn
DrawNumbers:
    ld (DE), a         ;CorRow now equals the number to be drawn
    cp c         ;If C = A
    CALL Z, TextInverseOn   ;Textinverse = on
    cp c         ;If C <> A
    CALL NZ, TextInverseOff   ;Textinverse = off
    PUSH AF         ;Save A because it is needed to display characters
    ld a, l         ;load the ASCII code of the number into A
    b_call(_PutC)      ;Display the character, and advance the cursor
    ld a, Lcolon      ;load the ASCII code of the ":" into A
    b_call(_PutMap)      ;Display the character, not advance the cursor
    xor a         ;Reset CurCol
    ld (CurCol), a
    inc hl         ;Incline the number, because the numbers are placed right behind each other in ROM
    POP AF         ;Recover A
    inc A         ;Incline the row
    DJNZ DrawNumbers      ;Repeat this, the number of times of the number of options

UserInput:
    RES 0, (IY + Asm_Flag1)   ;Resets the flag
    PUSH HL         ;Save HL temporarely, because b_call(_getKey) messes it up
    b_call(_getKey)      ;Gets the key pressed, and saves it in A
    POP HL         ;Restore HL
    CP kDown         ;If down is pressed...
    JR Z, InclineMenu      ;Incline C
    CP kUP         ;If up is pressed...
    JR Z, DeclineMenu      ;Decline C
    CP kEnter         ;If enter is pressed...
    RET Z         ;Exit the procedure
    SET 0, (IY + Asm_Flag1)   ;Sets the flag
    LD L, 1         ;L will save the option selected, if it was accessed by a number key
    LD B, H         ;Load the number of options into B
    LD E, 7         ;7 keys to check max
    LD D, k1         ;Load the address of the first key into D
CheckForNumber:
    CP D         ;Substract D (only modifying flags)
    RET Z         ;Exit the procedure if the right key is met
    DEC B         ;Decline B
    JR Z, UserInput      ;If 0, go to the userinput
    INC L         ;Incline L
    INC D         ;Incline D
    DEC E         ;Decline E
    JR NZ, CheckForNumber   ;Repeat this until either B or E met 0
    JR UserInput      ;Go to userinput

InclineMenu:
    INC C
    LD A, C
    DEC A
    CP H
    JP Z, DrawNumbersComplete
    JP DrawNumbersSet
DeclineMenu:
    DEC C
    JP NZ, DrawNumbersSet
    LD C, H
    JP DrawNumbersSet

TextInverseOn:
    SET TextInverse, (IY + TextFlags)
    RET
TextInverseOff:
    RES TextInverse, (IY + TextFlags)
    RET
That's quite good, thanks for sharing!
No problem!
I'm still planning to make a scrollable one, with multiple menu's at the top of the screen.
arriopolis wrote:
No problem!
I'm still planning to make a scrollable one, with multiple menu's at the top of the screen.
Cool, I look forward to seeing that one as well. You should check out the DCS GUI API, too.
Hey,

I updated my MenuProcedure a bit. It will now automatically store the result into A, instead of saving the place where it's stored in Asm_flag1. So here it is, enjoy!
Edit: I forgot I added a second call, so the codestream didn't work anymore. But now it does. Everything comes at a price though, register IX is destroyed aswell, as it wasn't in the previous version.

Code:
Menu: 
;This routine will make a menu, almost the same as the TI-basic one. 
;The screen will be cleared after this routine has been completed. 
;INPUT: The text via the code stream. 
;For example: 
;    .DB "MenuTitle       ", 0   ;Menu Title, 16 bytes in length, followed by a 0. 
;    .DB 3                              ;Number of options (max. = 7) 
;    .DB "Option1       "         ;Option 1, 14 bytes in length 
;    .DB "Option2       "         ;Option 2, 14 bytes in length 
;    .DB "Option3       "         ;Option 3, 14 bytes in length 
;OUTPUT: 
;    A: Option selected.
;DESTROYS:
;    Registers HL, DE, BC, AF, IX
;    Flag: 0, (IY + Asm_flag1)
    CALL Menu2                          ;Start the procedure
    BIT 0, (IY + Asm_flag1)             ;If the bit is 0...
    JR Z, OutputInC                     ;...then the output is in C
    LD A, L            ;If not, load L into A
    RET                                 ;Return
OutputInC:
    LD A, C                             ;Load C into A
    RET                                 ;Return

Menu2:
    RES AppAutoScroll, (IY + AppFlags)  ;Keep the screen from rolling 
    b_call(_ClrLCDFull)                 ;Clear the screen 
    CALL TextInverseOn                  ;Set textinverse 
    ld hl, $0000                        ;Set cursor to (0,0) 
    ld (CurRow), hl 
    POP IX
    POP HL                              ;Pop the address of the menutitle 
    LD D, H                             ;Store HL into DE 
    LD E, L 
    b_call(_PutS)                       ;Display the menutitle 
    CALL TextInverseOff                 ;Reset textinverse 
    LD B, 17                            ;Seventeen bytes to advance, including the 0 
IncrementDE: 
    INC DE 
    DJNZ IncrementDE 
 
;Drawing the text 
    LD HL, $0201                        ;Load the cursor for the first string 
    LD (CurRow), HL 
    LD HL, CurCol                       ;Load the address of the cursor in HL 
    EX DE, HL                           ;Load the address of the number of rows to be drawn into HL 
    LD C, (HL)                          ;Load that number into C 
    PUSH BC                             ;Save C, because we are going to need it once more 
    INC HL                              ;Load the address of the first character of the first option in the menu 
    LD B, 14                            ;14 characters per string 
DisplayText: 
    LD A, (HL)                          ;Load the first character of the string into A 
    b_call(_PutC)                       ;Display the character, and advance the cursor 
    INC HL                              ;Set the address for the next character 
    DJNZ DisplayText                    ;Repeat this 14 times 
    EX DE, HL                           ;HL = Address of cursor, DE = Address of MenuText 
    LD (HL), 2                          ;Set (CurCol) to 2 
    EX DE, HL                           ;HL = Address of MenuText, DE = Address of cursor 
    LD B, 14                            ;14 characters again. 
    DEC C                               ;Decline number of times to repeat this 
    JR NZ, DisplayText                  ;If the number of times to repeat this <> 0, repeat this 
    POP BC                              ;Restore C, the number of options in the menu 
    PUSH HL                             ;Store the address to jump to after the procedure has ended
    PUSH IX 
    ld b, c                             ;Store the number of options into B 
    ld h, b                             ;Save this number in h 
 
;Drawing the numbers next 
DrawNumbersComplete: 
    ld c, 1                             ;C keeps track of the current option selected 
DrawNumbersSet: 
    ld b, h                             ;Restore the number of numbers to be drawn into b. 
    xor a                               ;Reset CurCol to 0 
    ld (CurCol), A 
    ld l, $31                           ;load the hexvalue of "1" in L 
    ld de, CurRow                       ;load the address of CurRow in DE 
    ld a, 1                             ;A keeps track of the current row to be drawn 
DrawNumbers: 
    ld (DE), a                          ;CorRow now equals the number to be drawn 
    cp c                                ;If C = A 
    CALL Z, TextInverseOn               ;Textinverse = on 
    cp c                                ;If C <> A 
    CALL NZ, TextInverseOff             ;Textinverse = off 
    PUSH AF                             ;Save A because it is needed to display characters 
    ld a, l                             ;load the ASCII code of the number into A 
    b_call(_PutC)                       ;Display the character, and advance the cursor 
    ld a, Lcolon                        ;load the ASCII code of the ":" into A 
    b_call(_PutMap)                     ;Display the character, not advance the cursor 
    xor a                               ;Reset CurCol 
    ld (CurCol), a 
    inc hl                              ;Incline the number, because the numbers are placed right behind each other in ROM 
    POP AF                              ;Recover A 
    inc A                               ;Incline the row 
    DJNZ DrawNumbers                    ;Repeat this, the number of times of the number of options 
 
UserInput: 
    RES 0, (IY + Asm_Flag1)             ;Resets the flag 
    PUSH HL                             ;Save HL temporarely, because b_call(_getKey) messes it up 
    b_call(_getKey)                     ;Gets the key pressed, and saves it in A 
    POP HL                              ;Restore HL 
    CP kDown                            ;If down is pressed... 
    JR Z, InclineMenu                   ;Incline C 
    CP kUP                              ;If up is pressed... 
    JR Z, DeclineMenu                   ;Decline C 
    CP kEnter                           ;If enter is pressed... 
    RET Z                               ;Exit the procedure 
    SET 0, (IY + Asm_Flag1)             ;Sets the flag 
    LD L, 1                             ;L will save the option selected, if it was accessed by a number key 
    LD B, H                             ;Load the number of options into B 
    LD E, 7                             ;7 keys to check max 
    LD D, k1                            ;Load the address of the first key into D 
CheckForNumber: 
    CP D                                ;Substract D (only modifying flags) 
    RET Z                               ;Exit the procedure if the right key is met 
    DEC B                               ;Decline B 
    JR Z, UserInput                     ;If 0, go to the userinput 
    INC L                               ;Incline L 
    INC D                               ;Incline D 
    DEC E                               ;Decline E 
    JR NZ, CheckForNumber               ;Repeat this until either B or E met 0 
    JR UserInput                        ;Go to userinput 
 
InclineMenu: 
    INC C 
    LD A, C 
    DEC A 
    CP H 
    JP Z, DrawNumbersComplete 
    JP DrawNumbersSet 
DeclineMenu: 
    DEC C 
    JP NZ, DrawNumbersSet 
    LD C, H 
    JP DrawNumbersSet 
 
TextInverseOn: 
    SET TextInverse, (IY + TextFlags) 
    RET 
TextInverseOff: 
    RES TextInverse, (IY + TextFlags) 
    RET
  
Register to Join the Conversation
Have your own thoughts to add to this or any other topic? Want to ask a question, offer a suggestion, share your own programs and projects, upload a file to the file archives, get help with calculator and computer programming, or simply chat with like-minded coders and tech and calculator enthusiasts via the site-wide AJAX SAX widget? Registration for a free Cemetech account only takes a minute.

» Go to Registration page
» Goto page Previous  1, 2, 3, 4, 5, 6, 7, 8  Next
» View previous topic :: View next topic  
Page 3 of 8
» All times are UTC - 5 Hours
 
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum

 

Advertisement