Hey, I'm finally learning ASM. (I know, "oh shit! Theres going to be a spam of questions!!")

I was wondering, is there a possibility that someone could post up a simple ASM program they made and its source? I'm planning on doing some game making once I get good. And thats the direction I want to head at the start, so possibly some programs with moving objects? Or just working with keystrokes?

I've been looking over some manuals, including the TI Developers Guide by TI, its pretty good. I'm thinking of downloading the 28 Days Tutorial as well.

Suggestions/Tips on getting me up on my feet?
ASM in 28 Days is by far the best existing tutorial on the subject, when combined with some external references such as the official TI SDK.
Awesome, I'm going to look around for some program sources if possible.

I might replicate this topic on UTI, and see if I can't get some sources to be posted so I can study them.

----------------
Now playing: 30 Seconds to Mars - From Yesterday
via FoxyTunes
/me posts a hunk of (incomplete, untested) source code

Code:

;"Macros?!  When I started coding, we had to make do with zeroes and ones.  Sometimes
;we didn't even have ones!  I wrote an entire database program with zeroes!"
;"You had zeroes?  We had to use the letter 'o'!"
;-Scott Adams (paraphrased, probably misquoted), in the Dilbert Principle

;curRow = 844B, curCol = 844C
#DEFINE text(strptr, x, y) ld hl,(256*x)+y
#DEFCONT            \  ld ($844B),hl
#DEFCONT            \  ld hl,strptr
#DEFCONT            \  bcall(_PutS)
;penCol = 86D7, penRow = 86D8
#DEFINE stext(strptr, x, y) ld hl,(256*y)+x
#DEFCONT            \   ld ($86D7),hl
#DEFCONT            \   ld hl,strptr
#DEFCONT            \   bcall(_vPutS)

.org $9D93
.db $BB,$6D

menuPoint = saferam ;word -pointer in tOpts
runMenu:
   bcall(_ClrLCDFull)
   bcall(_HomeUp)
   ld hl,sMenuTitle
   bcall(_PutS)      ;macros are a waste of space.. for now
   stext(sAuthor,0,58)
   ld hl,(256*5)+2
   ld ($844B),hl
   ld a,$06
   bcall(_PutC)   ;up arrow character
   ld hl,(256*5)+4

menuRedraw:
   ld hl,(256*2)+3
   ld ($844B),hl
   ld hl,(menuPoint)
   ld de,tOpts
   or a
   sbc hl,de
   dec hl
   dec hl      ;actual menu index
   ld e,l
   ld d,h
   add hl,hl   ;2
   add hl,de   ;3
   add hl,hl   ;6
   add hl,hl   ;12
   ld de,sOpts
   add hl,de   
;PutS for 12 characters:
   ld b,12
   ld a,(hl)
   bcall(_PutC)
   inc hl
   djnz $-5
waitKey:
   bcall(_GetCSC)
   halt
   or a
   jr z,waitKey
   cp skUp
   jr z,_mUp
   cp skDown
   jr z,_mDown
   cp skEnter
   jr nz,waitKey
_mEnter:
   ld hl,runMenu
   push hl         ;return point
   ld hl,(menuPoint)
   ld a,(hl)
   inc hl
   ld h,(hl)
   ld l,a
   jp (hl)

_mUp:
   ld hl,(menuPoint)
   dec hl
   dec hl
   ld a,h
   or l
   jr nz,_mMoveSav
   ld hl,tOptsEnd-4
   jr _mMoveSav
_mDown:
   ld hl,(menuPoint)
   inc hl
   inc hl
   ld a,h
   or l
   jr nz,_mMoveSav
   ld hl,tOpts+2
_mMoveSav:
   ld (menuPoint),hl
   jr menuRedraw

sMenuTitle:
   .db "VAT tools 1.0",0
sAuthor:
   .db "By Peter Marheine",0
sOpts:
   .db "Sort VAT    " ;12 characters, for easy division
   .db "Rename prog "
   .db "Exit        "
tOpts:
   .dw 0   ;delimits the menu, for moving around - could always do hard-coded compares, too..
   .dw sortVAT
   .dw renameProg
   .dw EXIT
   .dw 0
tOptsEnd:

;=====================================================================
;      Wrapper/menu function routines
;=====================================================================
sortVAT:
   jr sort_t3h_VAT   ;it returns.. right to the menu!
;=====================================================================
;      Here be sort routines (dragons too?)
;=====================================================================
;int start, stored, location, temp, VAT[VAT_end]
;for ( start=0; start<VAT_end; start++; ) {
;   stored=start;
;   for ( location=start; location<VAT_end; location++; ) {
;      if ( VAT[location]>VAT[stored] ) {
;         stored=location;
;         }
;      }
;   temp=VAT[stored];
;   VAT[stored]=VAT[start];
;   VAT[start]=temp;
;   }
;;I have no idea if that pseudocode still matches the actual code, but it's the general
;; idea of how this thing should work
;;Thanks go to Christopher Mitchell for the getnext and vatswap routines, the rest
;; is my own work (which was donated to his project)
ProgPtr = $9830
Tvat1begin = saferam
Tvat2begin = saferam+17 ;word
vat1size = saferam+19 ;byte
vat2size = saferam+20 ;byte
vat1begin = saferam+21 ;word
vat1end = saferam+23 ;word
vat2begin = saferam+25 ;word
SavedPtr = saferam+27

sort_t3h_VAT:
   ld hl,(ProgPtr)
for1:
   push hl
      ld (SavedPtr),hl
      call getnext
      push hl
         pop ix
      jr z,end1
      pop hl
   ld de,OP1
   call getname
   push hl
for2:
      push ix
         pop hl
      ld de,OP2
      call getname
      ld hl,OP1
      ld de,OP2
      ld b,8
      call strcomp
      jr nc,for2_2
      ld (SavedPtr),ix
      push ix
      pop hl
      ld de,OP1
      call getname
for2_2:
      push ix
         pop hl
      call getnext
      push hl
         pop ix
      jr nz,for2
for1_more:
      pop hl
   push hl
      ld de,(SavedPtr)
      call local_vatswap
      pop hl
   call getnext
   jr for1

That's the first 190 lines (of 400) for VATTOOLS. Uh.. enjoy?
Thanks for posting the code ^^,

Whats the difference between .dw and .db ? Are they even similar?

----------------
Now playing: 30 Seconds to Mars - Battle of One
via FoxyTunes
.dw is a word or 4 bits(i think) and .db is a 8 bits(i think though i am more sure than i was on the other)
Close. .db is Data Byte (of something- that's how I think of it), so 8 bits (1 byte), and .dw is Data Word, at 16 bits (2 bytes, little-endian).
Smile

http://www.ticalc.org/archives/files/fileinfo/385/38591.html

(sorry, I'm too lazy to extract the source out of there to post it here Very Happy )
Thanks for the link Kllr! *downloaded!*

I got a link from UTI to another program, and looking at the source, it doesn't look all that hard. It seems pretty easy! Which is always good ^^,

----------------
Now playing: 30 Seconds to Mars - Hunter
via FoxyTunes
Here's some more goodies for you; I'm surprised I'm the first one to point this out to you:

http://www.ticalc.org/pub/83plus/asm/source/
Yeah I have actualy found Ti SDK very helpfull in some cases because it shows some Optimization tricks that improve speed or Bcall alternitives. like a faster Getcsc call.
TheStorm wrote:
Yeah I have actualy found Ti SDK very helpfull in some cases because it shows some Optimization tricks that improve speed or Bcall alternitives. like a faster Getcsc call.
Bleh, direct input for the win. The thing I use the TI SDK for most often is as a function reference for bcalls.
Here is the code to my nibls with sound game (simply ignore the playnote parts; they are for sound only) and the rest will form a simple nibls game. Sorry that it is in OTBP assembler form, but I programmed it entirely on-calc.


Code:
:DEFHDR.HDR
:DI
:BCALL RUNINDICOFF
:RES 5,(IY)
:BCALL CLRSCRNFULL
:LD HL,0202H
:LD (CURROW),HL
:LD HL,STXT3
:BCALL PUTS
:LD D,FFH
:LD E,80H
:LD B,D
:CALL PLAYNOTE
:LD B,FFH
:CALL PLAYNOTE
:CALL QQQ
:LD B,90H
:CALL PLAYNOTE
:CALL QQQ
:LD B,90H
:CALL PLAYNOTE
:CALL QQQ
:LD B,90H
:CALL PLAYNOTE
:LD E,30H
:LD B,FFH
:CALL PLAYNOTE
:CALL QQQ
:LD E,A0H
:LD B,FFH
:CALL PLAYNOTE
:LD E,80H
:LD B,FFH
:CALL PLAYNOTE
:LD B,FFH
:CALL PLAYNOTE
:JP MENU
:QQQ:
:LD B,250
:^:
:DEC B
:DEC B
:JR NZ,{‾1}
:RET
:MENU:
:BCALL CLRSCRNFULL
:BCALL HOMEUP
:LD HL,STXT
:SET 3,(IY+5)
:BCALL PUTS
:LD HL,STXT2
:RES 3,(IY+5)
:BCALL PUTS
:MENUL:
:LD D,FFH
:LD HL,MNOTES
:LD A,(MREF)
:LD C,A
:INC A
:CP 20
:JR NZ,{1}
:XOR A
:^:
:LD (MREF),A
:LD B,0
:ADD HL,BC
:LD A,(HL)
:LD E,A
:LD B,50H
:CALL PLAYNOTE
:LD A,BFH
:OUT (1),A
:IN A,(1)
:ADD A,A
:JP P,END2
:ADD A,A
:JP M,MENUL
:LD A,48
:LD (XPOS),A
:LD A,32
:LD (YPOS),A
:XOR A
:LD (EATEN),A
:LD H,A
:LD L,A
:LD (SCORE),HL
:DEC A
:LD (EATEN+1),A
:NEWLEV:
:XOR A
:LD (EATEN),A
:LD HL,EATEN+1
:INC (HL)
:LD HL,PLOTSSCREEN
:LD DE,PLOTSSCREEN+1
:LD BC,02FFH
:LD (HL),A
:LDIR
:LD HL,CLN
:LD DE,PLOTSSCREEN
:LD BC,12
:LDIR
:LD HL,CLN
:LD DE,PLOTSSCREEN+756
:LD BC,12
:LDIR
:LD D,C
:LD L,1
:LD E,63
:CALL DRAWVERT
:LD D,95
:LD L,1
:LD E,63
:CALL DRAWVERT
:LD A,(EATEN+1)
:OR A
:JP Z,DONESDRAW
:LD D,32
:LD L,10
:LD E,53
:CALL DRAWVERT
:LD D,64
:LD L,10
:LD E,53
:CALL DRAWVERT
:LD A,(EATEN+1)
:DEC A
:JR Z,DONESDRAW
:LD DE,PLOTSSCREEN+384
:LD BC,12
:LD HL,CLN2
:LDIR
:DONESDRAW:
:CALL SAFECOPY
:NEWRAND:
:LD HL,(WINY)
:CALL GETPIX
:CPL
:AND (HL)
:LD (HL),A
:BADRAND:
:LD B,93
:CALL IONRANDOM
:INC A
:LD (WINY+1),A
:LD B,62
:CALL IONRANDOM
:INC A
:LD (WINY),A
:LD HL,(WINY)
:CALL GETPIX
:OR (HL)
:CP (HL)
:JP Z,BADRAND
:LD (HL),A
:MOVE:
:LD HL,NOTES
:LD A,(NREF)
:CP 72
:CALL Z,RESNREF
:LD D,0
:LD E,A
:ADD HL,DE
:INC A
:LD (NREF),A
:LD E,(HL)
:LD D,FFH
:LD B,15H
:CALL PLAYNOTE
:LD HL,(SCORE)
:INC HL
:LD (SCORE),HL
:LD A,(DIR)
:OR A
:JP Z,MDOWN
:DEC A
:JP Z,MLEFT
:DEC A
:JP Z,MUP
:LD HL,XPOS
:INC (HL)
:JP DRAW
:MUP:
:LD HL,YPOS
:DEC (HL)
:JP DRAW
:MLEFT:
:LD HL,XPOS
:DEC (HL)
:JP DRAW
:MDOWN:
:LD HL,YPOS
:INC (HL)
:DRAW:
:LD A,(YPOS)
:LD HL,WINY
:CP (HL)
:JP Z,CHECKX
:NOWIN:
:LD HL,(YPOS)
:CALL GETPIX
:OR (HL)
:CP (HL)
:JP Z,END
:LD (HL),A
:CALL SAFECOPY
:KEY:
:LD A,FFH
:OUT (1),A
:DEC A
:OUT (1),A
:IN A,(1)
:LD HL,MOVE
:PUSH HL
:LD HL,DIR
:RRA
:JR NC,UP
:RRA
:JR NC,LEFT
:RRA
:JR NC,RIGHT
:RRA
:JR NC,DOWN
:RET
:DOWN:
:LD (HL),2
:RET
:LEFT:
:LD (HL),1
:RET
:RIGHT:
:LD (HL),3
:RET
:UP:
:LD (HL),0
:RET
:CHECKX:
:LD A,(XPOS)
:LD B,A
:LD A,(WINY+1)
:CP B
:JP NZ,NOWIN
:LD A,(EATEN+1)
:INC A
:LD B,A
:LD DE,100
:LD HL,0
:CHECKX2:
:ADD HL,DE
:DJNZ CHECKX2
:LD D,H
:LD E,L
:LD HL,(SCORE)
:ADD HL,DE
:LD (SCORE),HL
:LD A,(EATEN)
:INC A
:LD (EATEN),A
:CP 3
:JP Z,NEWLEV
:LD D,FFH
:LD E,2AH
:LD B,90H
:CALL PLAYNOTE
:JP NEWRAND
:END:
:LD HL,STUFF
:RST 20H
:BCALL CHKFINDSYM
:JR NC,FOUNDAPPVAR
:LD HL,5
:BCALL CREATEAPPVAR
:LD H,D
:LD L,E
:XOR A
:INC HL
:INC HL
:LD (HL),A
:INC HL
:LD (HL),A
:INC HL
:LD A,"A"
:LD (HL),A
:INC HL
:LD (HL),A
:INC HL
:LD (HL),A
:FOUNDAPPVAR:
:INC DE
:INC DE
:LD H,D
:LD L,E
:PUSH HL
:LD C,(HL)
:INC HL
:LD B,(HL)
:LD HL,(SCORE)
:OR A
:SBC HL,BC
:ADD HL,BC
:JP C,NOHIGH
:EX DE,HL
:LD (HL),E
:INC HL
:LD (HL),D
:INC HL
:PUSH HL
:BCALL CLRSCRNFULL
:LD HL,0
:LD (CURROW),HL
:POP HL
:LD B,3
:INPUTINITIALS:
:LD C,(HL)
:PUSH HL
:INITLOOP:
:LD A,C
:BCALL PUTMAP
:BCALL GETCSC
:CP 1
:JR Z,INITD
:CP 4
:JR Z,INITU
:CP 9
:JR Z,INITEND
:JR INITLOOP
:INITD:
:INC C
:JR INITLOOP
:INITU:
:DEC C
:JR INITLOOP
:INITEND:
:LD A,C
:POP HL
:LD (HL),A
:INC HL
:LD A,(CURCOL)
:INC A
:LD (CURCOL),A
:DJNZ INPUTINITIALS
:NOHIGH:
:BCALL CLRSCRNFULL
:BCALL HOMEUP
:LD HL,TXT
:BCALL PUTS
:LD HL,(SCORE)
:BCALL DISPHL
:BCALL NEWLINE
:LD HL,TXTH
:BCALL PUTS
:POP HL
:PUSH HL
:BCALL LDHLIND
:BCALL DISPHL
:BCALL NEWLINE
:POP HL
:INC HL
:INC HL
:LD A,(HL)
:BCALL PUTC
:INC HL
:LD A,(HL)
:BCALL PUTC
:INC HL
:LD A,(HL)
:BCALL PUTC
:LD D,FFH
:LD E,0
:LR:
:INC E
:LD B,04H
:CALL PLAYNOTE
:LD A,FDH
:OUT (1),A
:IN A,(1)
:RRA
:JP NC,MENU
:DJNZ LR
:DEC B
:LD E,B0H
:CALL PLAYNOTE
:LD B,C0H
:LD E,80H
:CALL PLAYNOTE
:LD B,FFH
:LD E,B0H
:CALL PLAYNOTE
:JP END
:END2:
:EI
:BCALL CLRSCRNFULL
:BCALL HOMEUP
:RET
:IONRANDOM:
:PUSH HL
:PUSH DE
:LD HL,(FE8DH)
:LD A,R
:LD D,A
:LD E,(HL)
:ADD HL,DE
:ADD A,L
:XOR H
:LD (FE8DH),HL
:LD HL,0
:LD E,A
:LD D,H
:^:
:ADD HL,DE
:DJNZ {‾1}
:LD A,H
:POP DE
:POP HL
:RET
:PLAYNOTE:
:LD C,B
:PLAYN:
:LD B,D
:PLAY2:
:LD A,D1H
:OUT (0),A
:DJNZ PLAY2
:LD B,E
:PLAY3:
:LD A,D0H
:OUT (0),A
:DJNZ PLAY3
:DEC C
:JR NZ,PLAYN
:RET
:DRAWVERT:
:LD A,E
:SUB L
:RET Z
:JR NC,{1}
:LD L,E
:NEG
:^:
:PUSH AF
:LD H,D
:CALL GETPIX
:POP BC
:LD DE,12
:LD C,A
:PLOTLOOP:
:LD A,C
:OR (HL)
:LD (HL),A
:ADD HL,DE
:DJNZ PLOTLOOP
:RET
:GETPIX:
:LD A,H
:LD H,0
:LD E,L
:LD D,H
:ADD HL,DE
:ADD HL,DE
:ADD HL,HL
:ADD HL,HL
:LD E,A
:SRL E
:SRL E
:SRL E
:ADD HL,DE
:LD DE,PLOTSSCREEN
:ADD HL,DE
:AND 7
:INC A
:LD B,A
:LD A,1
:GETPIXLOOP:
:RRCA
:DJNZ GETPIXLOOP
:RET
:RESNREF:
:XOR A
:LD (NREF),A
:RET
:SAFECOPY:
:LD C,10H
:LD A,80H
:CALL LCDDELAY
:OUT (10H),A
:LD A,20H
:CALL LCDDELAY
:OUT (10H),A
:LD HL,9334H
:LD DE,12
:SAFECPY1:
:LD B,64
:EX AF,AF'
:SAFECPY2:
:ADD HL,DE
:LD A,(HL)
:CALL LCDDELAY
:OUT (11H),A
:DJNZ SAFECPY2
:EX AF,AF'
:LD H,93H
:INC L
:INC A
:CALL LCDDELAY
:OUT (10H),A
:CP 2CH
:JR NZ,SAFECPY1
:RET
:LCDDELAY:
:IN (C)
:RET P
:JP LCDDELAY
:STUFF:
:.DB 15H,"NiblsWS1"
:TXTH:
:.DB "High Score:",0
:INITIALS:
:.DB 0,0,0
:EATEN:
:.DB 0,‾1
:WINY:
:.DB 0,0
:MNOTES:
:HEX 7070D0D040404070707070C5C520202020202020
:MREF:
:.DB 0
:NREF:
:.DB 0
:NOTES:
:HEX D0D0D0D0D0D0D0D0D05050505050505050509090909090909090909090505050505050505050506060606060606060E8E8E8E8E8E8E8303030303030303030303030303030303030
:STXT2:
:.DB "[2ND]-Play      [MODE]-Quit",0
:STXT3:
:.DB "(C) 5-2-2007                         A        Penguin Studios    Production",0
:SCORE:
:.DW 0
:MUS:
:.DW 0
:DIR:
:.DB 0
:YPOS:
:.DB 32
:XPOS:
:.DB 48
:TXT:
:.DB "Your Score:     ",0
:CL:
:HEX 000000000000000000000000
:CLN2:
:HEX 80000000FFFFFFFF00000001
:CLN:
:HEX FFFFFFFFFFFFFFFFFFFFFFFF
:STXT:
:.DB "Nibls With Music",0


If you have any questions about it, post them here, pm me, or email me.
Thanks for all the sources and what not. Its helping a lot.

I asked this question on UTI, but I'm going to ask the question on here as well...

Liazon sent me the source for the TurkeyHunt game. I'm looking to work on it a bit, maybe build off of it just so I get the feel for programming (its easier to add to something already created ^^,). My question was, how would I check if the user has two keys pressed? If they do, I think I know how to make the character to go diagonal, but I'm not sure how to check for two keys at one time. Help?

----------------
Now playing: 30 Seconds to Mars - The Fantasy
via FoxyTunes
You have to use the bit register,bit opcode to check the individual bits returned by the direct input in (port) opcode. Bits set (1) mean the key is not pressed; bits are reset (0) when the corresponding key is pressed.
I'm starting to understand some of this Very Happy

But, I'm a bit intimidated when it comes to the "ramifications of not heeding this [leaving the stack in the exact same state is was as when the program started] warning."

Anyone care to explain scenarios of when this happens? and/or how to prevent it? I'm not completely sure if I understand how it all works yet, heh.
For now, just be sure you don't PUSH anything onto the stack without POPping it back out later. When you CALL something, it PUSHes the return address onto the stack, so then when you RET, it basically POPs into PC. If you were to PUSH something without POPping it later, you would be jumping to an unpredictable location, which is a definite no-no.

Here's a quick sample of what you really don't want to be doing with the stack, unless you REALLY want to deal with a debugging nightmare (LIFOS source, macros.asm):

Code:

.module macro_sys
SYSMACRO:
   ex (sp),hl
   push hl      ;preserve the return address.. please?
   inc hl
   push af
    ld a,(hl)
    inc hl
    ld h,(hl)
    ld l,a
    pop af
   ex (sp),hl   ;saved my indirected value
   inc sp
   inc sp
   ex (sp),hl   ;saved the final return address, hl is once again what it was when we started
   dec sp
   dec sp
;this line intentionally left blank
   ex (sp),hl   ;get the indirected value back
   push hl      ;call here, yay
   inc sp
   inc sp
   ex (sp),hl   ;..and here's our initial value again
   dec sp
   dec sp
;another blank line
   dec sp      ;space for 'call' opcode
   push hl      ;for restoring HL
   dec sp      ;for 'ld hl,nnnn' opcode
   ld hl,_IAmYourFather
   push hl
   ld hl,0
   add hl,sp
   push hl
    inc hl
    inc hl
    ld (hl),$21   ;the 'ld hl,nnnn' opcode
    inc hl
    inc hl
    ld (hl),$CD   ;call opcode
    pop hl
   jp (hl)
   
_IAmYourFather:
   inc sp
   inc sp
   inc sp      ;removed hl restoration
   inc sp
   inc sp
   inc sp      ;removed call
   ret      ;surprisingly easy to clean up..

Even with all those comments (much more numerous than they usually are in my code), I dread debugging this.
And now that I think of it, I'll need to rework this, since the hardware won't allow executing from the stack, where it usually is (above $C000).
Could it be a problem with you(or the writer) pushing hl 3-4 times while only popping it once? lol

----------------
Now playing: Muse - Knights of Cydonia
via FoxyTunes
swivelgames wrote:
Could it be a problem with you(or the writer) pushing hl 3-4 times while only popping it once? 0x5


Not necessarily, since he is then manipulating the SP (Stack Pointer) directly to return it to its previous state (hopefully anyway Very Happy ).

<ot>Please turn off that crappy foxytunes post plugin BS - its annoying</ot>
Oh I see. And then "ld h,(hl)" would store the result of hl(results only because its in parenthesis) into h, right? or vise versa? What exactly does ld do?

Its kind of confusing, because at one point I thought I saw ld being used to store/change variables, but then I saw that it was used to call them, and then used as a conditional statement (ld a,label = If A then Label; Not exact).

@kllr: Haha, sorry, I have that on for something else. I'll shut it off for on Cemetech... it gets annoying, but I've been too lazy to disable it. *disabled*
  
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
Page 1 of 2
» 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