Jump to content
IGNORED

Possibly the dumbest programming question ever


eebuckeye

Recommended Posts

Clearly I am not a programmer but was wondering how this basic problem is handled.

 

When you put objects on the screen for a maze, obstacle, etc...  how do you keep track of them when programming a game?  For example, if there are 30 8x8 pixel blocks using a char statement on the screen that your character dies if it hits, how do you track location?  Obviously you place the position of the obstacle specifically but do you have to save it to a variable to do a compare for each one when the character moves?

 

 

  • Like 1
Link to comment
Share on other sites

Clearly I am not a programmer but was wondering how this basic problem is handled.
 
When you put objects on the screen for a maze, obstacle, etc...  how do you keep track of them when programming a game?  For example, if there are 30 8x8 pixel blocks using a char statement on the screen that your character dies if it hits, how do you track location?  Obviously you place the position of the obstacle specifically but do you have to save it to a variable to do a compare for each one when the character moves?
 
 
There's a few ways depending on how you're moving your character around.. if you're using a sprite then you have no way of telling if that sprite is touching anything other than another sprite.. so what you have to do is check the location of the sprite and have a lookup table in data that has the precalculated values of where all the lines are.. ..

Sent from my Pixel 6 Pro using Tapatalk

  • Like 2
Link to comment
Share on other sites

In the very general sense it comes down to having some place in you program where your program "remembers" the location of the character.

In BASIC this is done with numeric variables so two variables called ROW and COL might be all that you need.

 

An important detail of this is that you must always move the character by changing the variables ROW and COL and place the character on the screen using ONLY those variables as well.

 

Apologies if that is too simplistic for your needs. 

So a simple exercise then is to make a program that moves a letter around the screen using this method.

 

Example: 

This line will put letter A  at position ROW,COL 

CALL HCHAR( ROW,COL,65)  

 

How you change ROW and COL is up to you.

Have fun.

  • Like 2
Link to comment
Share on other sites

Lets say you have a block at column nr 23 and row 23.

You can then use "IF statement" to ask if column is 23 and row is 23 then "explosion". When this IF statement set at the right place, it will keep asking if this has happened or not. So more stuff on the screen, the more complex the IF is.

When a rocket is fired against you, the IF statement keeps asking as the rocket is moved over the screen.

A short simple explanation. If I find a program simple program, I will put it up here. Best would be is some of the big guns made a simple example ? hint hint ? hehehehe
 

  • Like 2
Link to comment
Share on other sites

Recommendation... Start with the user manual for Basic that follows with the TI. Start at the beginning and get a overview of how the codes work. Then look at this game... "SteveB52" a short game where a bomb is dropped. Also if you find the TICodEd tread you will find a manual about TICodEd. You will find this game in it and it is broken up into parts to explain it. Also TICodEd in it self is a programming tool. Then go to the nest game you find and go over the code to understand what is dos. Don't remember any maze game. But maybe someone will give you a link or code to a maze game to look at.

It is not that complicated, when you look at the code.

 

Spoiler

100 GOSUB 170
110 GOSUB 220
120 GOSUB 290
130 GOSUB 380
140 IF NOT (Answer=78 OR Answer=110) THEN 110
150 CALL CLEAR
160 END
170 CALL CHAR(124,"00000080C0E070FFFF070F1C3800000000000000000000FEFFC0000000000000")
180 CALL CHAR(128,"2810383838100000000000000000000000000000000000000000000000000000")
190 CALL CHAR(132,"FE929292FE929292FFFFFFFF")
200 CALL MAGNIFY(3) :: DIM A(26) :: RANDOMIZE
210 RETURN
220 CALL ScrInit(16,2) :: DISPLAY AT(23,10):"SteveB52"
230 FOR I=1 to 26 :: A(I)=0 :: NEXT I
240 FOR I=1 to 50 :: J=INT(RND*26)+1 :: A(J)=A(J)+1 :: NEXT I
250 CALL HCHAR(21,1,133,32)
260 FOR I=1 to 26 :: CALL VCHAR(21-A(I),I+3,132,A(I)):: NEXT I
270 CALL SPRITE(#1,124,13,1,1,0,16) :: BOMB=0
280 RETURN
290 CALL POSITION(#1,Y1,X1) :: IF X1>240 THEN CALL LOCATE(#1,Y1+4,1)
300 CALL KEY(3,K,S) :: IF K=32 AND BOMB=0 THEN CALL SPRITE(#2,128,11,Y1,X1,24,0) :: BOMB=1
310 IF BOMB=0 THEN 350
320 CALL POSITION(#2,Y2,X2) :: CALL GCHAR(Y2/8+1,X2/8+1,C2)
330 IF C2=132 OR Y2>155 THEN CALL DELSPRITE(#2):: BOMB=0
340 IF C2=132 THEN CALL HCHAR(Y2/8+1,X2/8+1,32,1) :: CALL SOUND(-250,-7,1)
350 CALL GCHAR(INT((Y1-1)/8)+2,INT((X1-1)/8)+1,C1)
360 IF NOT ((Y1>148 AND X1>200) OR C1<>32) THEN 290
370 RETURN
380 CALL MOTION(#1,0,0)::CALL DELSPRITE(#2)
390 IF C1<>32 THEN DISPLAY AT(8,10):"Game Over" ELSE DISPLAY AT(8,10):"You landed"
400 DISPLAY AT(12,8):"Play again? (Y/N)"
410 CALL KEY(3,Answer,S)
420 IF NOT (S<>0) THEN 410
430 RETURN
440 SUB ScrInit(fg,bg)
450 CALL SCREEN(bg)
460 CALL DELSPRITE(ALL)
470 CALL CLEAR
480 FOR I=0 to 14 :: CALL COLOR(I,fg,1) :: NEXT I
490 SUBEND

 


 

  • Like 4
Link to comment
Share on other sites

24 minutes ago, oddemann said:

It is not that complicated, when you look at the code.
 

  Hide contents


100 GOSUB 170
110 GOSUB 220
120 GOSUB 290
130 GOSUB 380
140 IF NOT (Answer=78 OR Answer=110) THEN 110
150 CALL CLEAR
160 END
170 CALL CHAR(124,"00000080C0E070FFFF070F1C3800000000000000000000FEFFC0000000000000")
180 CALL CHAR(128,"2810383838100000000000000000000000000000000000000000000000000000")
190 CALL CHAR(132,"FE929292FE929292FFFFFFFF")
200 CALL MAGNIFY(3) :: DIM A(26) :: RANDOMIZE
210 RETURN
220 CALL ScrInit(16,2) :: DISPLAY AT(23,10):"SteveB52"
230 FOR I=1 to 26 :: A(I)=0 :: NEXT I
240 FOR I=1 to 50 :: J=INT(RND*26)+1 :: A(J)=A(J)+1 :: NEXT I
250 CALL HCHAR(21,1,133,32)
260 FOR I=1 to 26 :: CALL VCHAR(21-A(I),I+3,132,A(I)):: NEXT I
270 CALL SPRITE(#1,124,13,1,1,0,16) :: BOMB=0
280 RETURN
290 CALL POSITION(#1,Y1,X1) :: IF X1>240 THEN CALL LOCATE(#1,Y1+4,1)
300 CALL KEY(3,K,S) :: IF K=32 AND BOMB=0 THEN CALL SPRITE(#2,128,11,Y1,X1,24,0) :: BOMB=1
310 IF BOMB=0 THEN 350
320 CALL POSITION(#2,Y2,X2) :: CALL GCHAR(Y2/8+1,X2/8+1,C2)
330 IF C2=132 OR Y2>155 THEN CALL DELSPRITE(#2):: BOMB=0
340 IF C2=132 THEN CALL HCHAR(Y2/8+1,X2/8+1,32,1) :: CALL SOUND(-250,-7,1)
350 CALL GCHAR(INT((Y1-1)/8)+2,INT((X1-1)/8)+1,C1)
360 IF NOT ((Y1>148 AND X1>200) OR C1<>32) THEN 290
370 RETURN
380 CALL MOTION(#1,0,0)::CALL DELSPRITE(#2)
390 IF C1<>32 THEN DISPLAY AT(8,10):"Game Over" ELSE DISPLAY AT(8,10):"You landed"
400 DISPLAY AT(12,8):"Play again? (Y/N)"
410 CALL KEY(3,Answer,S)
420 IF NOT (S<>0) THEN 410
430 RETURN
440 SUB ScrInit(fg,bg)
450 CALL SCREEN(bg)
460 CALL DELSPRITE(ALL)
470 CALL CLEAR
480 FOR I=0 to 14 :: CALL COLOR(I,fg,1) :: NEXT I
490 SUBEND

 


 

Is this for Extended BASIC?

There are three errors just loading the lines into the editor on Classic99. :) 

Very sorry.  I pressed 1 by mistake. 

  • Like 1
Link to comment
Share on other sites

1 hour ago, eebuckeye said:

That is how I pretty much expected but man that seems like a lot of work especially if there is a full maze on the screen!?  I do not have programmer logic.. ha

It's actually not that much work. Say you have the coordinates of your player in two variables, x and y. Using those you can look up the character pattern at the position of the player, either directly on the screen using GCHAR, or if you have a map of the screen in an array, you can use that instead. If your player is shown as a sprite you have to divide the coordinates by 8 to get the coordinates of the character pattern. If you need to check a position above/below/to the left of/to the right of you character you just add the offset to the coordinates before the check.

  • Like 4
Link to comment
Share on other sites

Two very simple examples below. Both of them display 30 hash characters on screen, then you have enter the coordinates (row and column) of where you think one is, and you're told if this is a 'hit' or a 'miss'.

 

The first example uses CALL GCHAR to check if the character at your chosen coordinates is a 'hit'. The second example stores the characters in an array and looks in the array to check if the character is a 'hit'. The extra or different lines in the second example are indicated by "!*****" comments.

 

You can apply to same techniques to moving a character around the screen and checking if it walks into an obstacle by adjusting the ROW and COL variables according to the direction of movement, rather than asking for their input.

 

100 CALL CLEAR
110 FOR I=1 TO 30
120 ROW=RND*20
130 COL=RND*32
140 CALL HCHAR(ROW,COL,35)
150 NEXT I
160 DISPLAY AT(22,1):"ENTER ROW:"
170 ACCEPT AT(22,11):ROW
180 DISPLAY AT(23,1):"ENTER COL:"
190 ACCEPT AT(23,11):COL
200 CALL GCHAR(ROW,COL,CHR)
210 IF CHR=35 THEN DISPLAY AT(24,1):"HIT!" ELSE DISPLAY AT(24,1):"MISS!"
220 GOTO 160


100 CALL CLEAR
110 DIM SCR(20,32) !****
120 FOR I=1 TO 30
130 ROW=RND*20
140 COL=RND*32
150 CALL HCHAR(ROW,COL,35)
160 SCR(ROW,COL)=35 !****
170 NEXT I
180 DISPLAY AT(22,1):"ENTER ROW:"
190 ACCEPT AT(22,11):ROW
200 DISPLAY AT(23,1):"ENTER COL:"
210 ACCEPT AT(23,11):COL
220 CHR=SCR(ROW,COL) !****
230 IF CHR=35 THEN DISPLAY AT(24,1):"HIT!" ELSE DISPLAY AT(24,1):"MISS!"
240 GOTO 180

 

Edited by Stuart
  • Like 2
  • Thanks 1
Link to comment
Share on other sites

On 1/8/2022 at 12:50 PM, oddemann said:

Recommendation... Start with the user manual for Basic that follows with the TI. Start at the beginning and get a overview of how the codes work. Then look at this game... "SteveB52" a short game where a bomb is dropped. Also if you find the TICodEd tread you will find a manual about TICodEd. You will find this game in it and it is broken up into parts to explain it. Also TICodEd in it self is a programming tool. Then go to the nest game you find and go over the code to understand what is dos. Don't remember any maze game. But maybe someone will give you a link or code to a maze game to look at.

It is not that complicated, when you look at the code.

 

  Hide contents


100 GOSUB 170
110 GOSUB 220
120 GOSUB 290
130 GOSUB 380
140 IF NOT (Answer=78 OR Answer=110) THEN 110
150 CALL CLEAR
160 END
170 CALL CHAR(124,"00000080C0E070FFFF070F1C3800000000000000000000FEFFC0000000000000")
180 CALL CHAR(128,"2810383838100000000000000000000000000000000000000000000000000000")
190 CALL CHAR(132,"FE929292FE929292FFFFFFFF")
200 CALL MAGNIFY(3) :: DIM A(26) :: RANDOMIZE
210 RETURN
220 CALL ScrInit(16,2) :: DISPLAY AT(23,10):"SteveB52"
230 FOR I=1 to 26 :: A(I)=0 :: NEXT I
240 FOR I=1 to 50 :: J=INT(RND*26)+1 :: A(J)=A(J)+1 :: NEXT I
250 CALL HCHAR(21,1,133,32)
260 FOR I=1 to 26 :: CALL VCHAR(21-A(I),I+3,132,A(I)):: NEXT I
270 CALL SPRITE(#1,124,13,1,1,0,16) :: BOMB=0
280 RETURN
290 CALL POSITION(#1,Y1,X1) :: IF X1>240 THEN CALL LOCATE(#1,Y1+4,1)
300 CALL KEY(3,K,S) :: IF K=32 AND BOMB=0 THEN CALL SPRITE(#2,128,11,Y1,X1,24,0) :: BOMB=1
310 IF BOMB=0 THEN 350
320 CALL POSITION(#2,Y2,X2) :: CALL GCHAR(Y2/8+1,X2/8+1,C2)
330 IF C2=132 OR Y2>155 THEN CALL DELSPRITE(#2):: BOMB=0
340 IF C2=132 THEN CALL HCHAR(Y2/8+1,X2/8+1,32,1) :: CALL SOUND(-250,-7,1)
350 CALL GCHAR(INT((Y1-1)/8)+2,INT((X1-1)/8)+1,C1)
360 IF NOT ((Y1>148 AND X1>200) OR C1<>32) THEN 290
370 RETURN
380 CALL MOTION(#1,0,0)::CALL DELSPRITE(#2)
390 IF C1<>32 THEN DISPLAY AT(8,10):"Game Over" ELSE DISPLAY AT(8,10):"You landed"
400 DISPLAY AT(12,8):"Play again? (Y/N)"
410 CALL KEY(3,Answer,S)
420 IF NOT (S<>0) THEN 410
430 RETURN
440 SUB ScrInit(fg,bg)
450 CALL SCREEN(bg)
460 CALL DELSPRITE(ALL)
470 CALL CLEAR
480 FOR I=0 to 14 :: CALL COLOR(I,fg,1) :: NEXT I
490 SUBEND

 


 

Hello @oddemann 

Did you write this game? 

I used the ideas in it to test the changes in my Forth system and would like to put the author in the comments.

It's a good demo for a new Forth programmer.

 

 

  • Like 1
Link to comment
Share on other sites

54 minutes ago, TheBF said:

Hello @oddemann 

Did you write this game? 

I used the ideas in it to test the changes in my Forth system and would like to put the author in the comments.

It's a good demo for a new Forth programmer.

 

I believe @SteveB wrote “SteveB52” (see Introducing Structured Extended BASIC and TiCodEd).

 

...lee

  • Like 1
  • Thanks 1
Link to comment
Share on other sites

2 hours ago, Lee Stewart said:

 

I believe @SteveB wrote “SteveB52” (see Introducing Structured Extended BASIC and TiCodEd).

 

...lee

Yeah, this is right. It is an example of Structured Extended BASIC converted to regular Extended Basic used and explained here in the Beginners Manual. So aboves code is generated from:

GOSUB GameInit
REPEAT
  GOSUB PaintScreen
  GOSUB PlayGame
  GOSUB GameOver
UNTIL Answer=78 OR Answer=110
END

GameInit:
  CALL CHAR(124,"00000080C0E070FFFF070F1C3800000000000000000000FEFFC0000000000000")
  CALL CHAR(128,"2810383838100000000000000000000000000000000000000000000000000000")
  CALL CHAR(132,"FE929292FE929292FFFFFFFF")
  CALL MAGNIFY(3) :: DIM A(26) :: RANDOMIZE
RETURN

PaintScreen:
  CALL ScrInit(16,2) :: DISPLAY AT(23,10):"SteveB52"
  FOR I=1 to 26 :: A(I)=0 :: NEXT I
  FOR I=1 to 50 :: J=INT(RND*22)+1 :: A(J)=A(J)+1 :: NEXT I
  CALL HCHAR(21,1,133,32)
  FOR I=1 to 26 :: CALL VCHAR(21-A(I),I+3,132,A(i)):: NEXT I
  CALL SPRITE(#1,124,13,1,1,0,16)
RETURN

PlayGame:
   REPEAT
     CALL POSITION(#1,Y1,X1) :: IF X1>240 THEN CALL LOCATE(#1,Y1+4,1)
     CALL KEY(3,K,S) :: IF K=32 AND BOMB=0 THEN CALL SPRITE(#2,128,11,Y1,X1,24,0) :: BOMB=1
     IF BOMB=0 THEN NoBomb
       CALL POSITION(#2,Y2,X2) :: CALL GCHAR(Y2/8+1,X2/8+1,C2) :: IF C2=132 OR Y2>155 THEN CALL DELSPRITE(#2):: BOMB=0
       IF C2=132 THEN CALL HCHAR(Y2/8+1,X2/8+1,32,1) :: CALL SOUND(-250,-7,1)
     NoBomb:
     CALL GCHAR(INT((Y1-1)/8)+2,INT((X1-1)/8)+1,C1)
   UNTIL (Y1>148 AND X1>200) OR C1<>32
RETURN

GameOver:
  CALL MOTION(#1,0,0)
  IF C1<>32 THEN DISPLAY AT(8,10):"Game Over" ELSE DISPLAY AT(8,10):"You landed"
  DISPLAY AT(12,8):"Play again? (Y/N)"
  REPEAT
    CALL KEY(3,Answer,S)
  UNTIL S<>0
  CALL CLEAR
RETURN

@TheBF: This top-down structure reversed may be even more helpful for Forth. Only the CALL ScrInit is added from the standard-library of TiCodEd as

SUB ScrInit(fg,bg)
  CALL SCREEN(bg)
  CALL DELSPRITE(ALL)
  CALL CLEAR
  FOR I=0 to 14 :: CALL COLOR(I,fg,1) :: NEXT I
SUBEND

Cheers!

 

Steve

 

 

 

  • Like 2
  • Thanks 1
Link to comment
Share on other sites

Not to be all "I'll show you mine if you show me yours but..."

I stole ScrInit pretty much wholesale. :)

 

: ScrInit ( fg bg -- )
  DUP SCREEN         \ use bg color for screen
  DELALL
  1 19 2SWAP COLORS  \ does the range of color sets 1..19
  CLEAR
;

 

Link to comment
Share on other sites

If you want a separate memory structure for checking what to do at a certain position, you can pack data into an array. Like if it's a maze and you only want to see if there's a wall or not, then a single bit is enough, and 16 such bits fit in a single word. But the work to unpack the data is usually too time consuming in BASIC, unless it's a turn based game. If you use assembly, it can frequently work out.

 

If you then also want to keep track of if there are dangerous positions, it's sometimes better to make another array of bits, rather than encoding additional information in the same field. Like if you have three conditions:

  • Open space.
  • Solid wall.
  • Some special object.

Then an array with two-bit values can cover this. 0 is free, 1 is a wall and 2 an object. This makes the table twice as large.

But you can also make two single-bit tables, one with 0 free and 1 indicating a wall, the other with 0 free and 1 indicating an object.

The total memory used is the same in this case. But the second approach allows you to easily clear one table without affecting the other. A calculated location of the data (word offset from beginning of table and bit offset inside the word) is then also the same for both tables, so you only need to calculate it once. With the word offset in R1, these instructions will fetch the different data.

MOV @WALL(R1),R2

MOV @OBJECT(R1),R3

 

Edited by apersson850
  • Like 3
Link to comment
Share on other sites

On 1/9/2022 at 4:41 AM, eebuckeye said:

That is how I pretty much expected but man that seems like a lot of work especially if there is a full maze on the screen!?  I do not have programmer logic.. ha

Probably seems more intimidating at first than it actually it. Consider you are a player and you shoot a bullet. You are probably going to monitor only the next position the bullet is about to take. There is either something there or not. While you might be monitoring the entire game area, where you are actually checking at any one time is probably quite focused.

Link to comment
Share on other sites

Similar for an explosion, if you have these. May affect only the immediately adjacent positions (eight, if you also go diagonally). A common trick to make logic for movements and stuff simpler is to include a virtual frame around the playing field. If the maze is the screen, but that's it (no playing field outside the screen), then even if you don't waste the outermost ring of locations to show a fixed, contiguous wall, you may have one in the internal representation of the playing field. Thus the same logic applies to edge encounters as to all other walls you may hit.

 

If you then also simply let the position of you player, which on the screen goes from 0,0 to 31,23, instead go from 1,1 to 32,24, and let the imaginary border range from 0,0 to 33,25, then you don't have any issue with positions becoming negative when you calculate the impact around a position. You simply subtract or add one to the X and Y positions for you player vs. the imaginary playing field. It's more efficient than handling all border cases separately.

Edited by apersson850
  • Like 1
Link to comment
Share on other sites

Join the conversation

You can post now and register later. If you have an account, sign in now to post with your account.
Note: Your post will require moderator approval before it will be visible.

Guest
Reply to this topic...

×   Pasted as rich text.   Paste as plain text instead

  Only 75 emoji are allowed.

×   Your link has been automatically embedded.   Display as a link instead

×   Your previous content has been restored.   Clear editor

×   You cannot paste images directly. Upload or insert images from URL.

Loading...
  • Recently Browsing   0 members

    • No registered users viewing this page.
×
×
  • Create New...