Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Bill Budge's Preshift-Table graphics on Your Apple (from dec 1984 BYTE)

12 views
Skip to first unread message

aiia...@gmail.com

unread,
Oct 16, 2007, 1:48:19 PM10/16/07
to
Has anyone typed in the programs yet?

I'll volunteer for a few pages... I don't want to
type it all in if someone else has started.


Rich

aiia...@gmail.com

unread,
Oct 16, 2007, 2:11:00 PM10/16/07
to
On Oct 16, 10:48 am, aiiad...@gmail.com wrote:
> I'll volunteer for a few pages... I don't want to
> type it all in if someone else has started.

page 1 of assembly:

ORG $5210

;
; PRESHIFT GRAPHICS ROUTINE
; BY ROB MOOORE AND BILL BUDGE
;

;
BASE1 EQU $40 ;BASE PAGE ROW ADDR POINTER
;
;LOOKUP TABLES
;
SHFTSTAY EQU $4000 ;SHIFTOUT TABLES
SHIFTOUT EQU $4700 ;SHIFT TABLES
XDIV7 EQU $4E00 ;INDEX DIV 7
XMOD7 EQU $4F00 ;INDEX MOD 7
ROWTBL EQU $5000 ;SCREEN ROW ADDR LO-BYTES
ROWTBH EQU $50C0 ;SCREEN ROW ADDR HI-BYTES
;
; IMAGE DEFINITION PARAMETERS -- SET BY.USER
;
IROWS EQU $5200 ;# OF ROWS - 1
IDOTS EQU $5201 ;DOT WIDTH - 1
IBWIDTH EQU $5202 ;IMAGE BYTE WIDTH
IBITS EQU $5203 ;ADDR OF IMAGE DATA
X1 EQU $5205 ;IMAGE LEFT X-COORD
Y1 EQU $5206 ;IMAGE TOP Y-COORD
;
;
; FIRST, SET UP THE VARIOUS PARAMETERS TO PREPARE
; FOR THE IMAGE DRAW.
;
DRAWIMAGE STX XSAVE ;SAVE BASIC X-REG
LDA Y1 ;IMAGE TOP ROW #
CLC
ADC IROWS ;+ # OF ROWS - 1
STA Y2 ;= BOTTOM ROW #
;
LDX X1 ;IMAGE LEFT X-COORD
LDA XDIV7,X ;DIVIDED BY 7
STA LBYTE ; = IMAGE LEFT BYTE #
;
LDY XMOD7,X ;IMAGE LEFT BIT #
LDA LMASKS,Y ;INDEXES LMASK TABLE FOR
STA LMASK ;IMAGE LEFT BIT MASK
;
TYA ;IMAGE LEFT BIT#
CLC ;+ SHIFT TABLES ADDRESS
ADC #<SHFTSTAY ;*256
STA PATCH3 ;TO SHIFT PATCH
;
ADC #7 ;OFFSET TO SHIFTOUT TABLES
STA PATCH2 ;SETS UP SHIFTOUT PATCH
;
TYA ;IMAGE LEFT BIT #
CLC
ADC IDOTS ; + IMAGE DOT WIDTH
TAX
LDA XDIV7,X ;DIVIDED BY 7
STA SBWIDTH ; = SHIFTED DATA BYTE WIDTH
;
LDY XMOD7,X ;RIGHT EDGE BIT #

(CONTINUED)

page 2 of assembly:


LDA RMASKS,Y ;INDEX RMASKS TABLE FOR
STA RMASK ;IMAGE RIGHT BIT MASK.
;
LDY IBWIDTH ;IMAGE WIDTH IN BYTES
STY PITCH ; IS BITMNAP PITCH
DEY ;SUBTRACT 1 TO GET
STY SHFTINDX ;SHIFT START INDEX
;
LDA IBITS ;COPY IMAGE DATA ADDRESS
STA PATCH1 ;TO SHIFT ROUTINE PATCH1
LDA IBITS+1
STA PATCH1+1
;
; MAIN DRAW LOOP STARTS HERE
;
LDX Y1 ;IMAGE TOP SCRN ROW #
DRAW LDA ROWTBL,X ;SCREENROW ADDR LO-BYTE
CLC
ADC LBYTE ;+LEFT IMAGE BYTE #
STA BASE1; TO SCRN ADDR POINTERR
LDA ROWTBH,X ; SCREEN ROW ADDR HI-BYTE
STA BASE1+1 ;TO POINTER HI-BYTE
STX TEMP ;SAVE CURRENT ROW#
;
; BILL BUDGE'S SHIFT CODE STARTS HERE.
;IT SHIFTS A ROW OF STORED BITMAP DATA INTO A
;SINGLE-LINE BUFFER, WHICH CAN THEN BE DRAWN TO
; THE SCREEN
;
LDA #0 ;SETUP FOR SHIFTING
LDY SHFTINDX
;
PATCH1 EQU *+1
SHIFTIT LDX $FFFF,Y ;GET A BYTE OF IMAGE DATA
PATCH2 EQU *+2
ORA SHIFTOUT,X ;LOOKUP SHIFTED OUT PART
STA BUFFER+1,Y ;AND STORE IN BUFFER
PATCH3 EQU *+2
LDA SHFTSTAY,X ;LOAD THE SHIFTED PART
DEY ;DONE WITH ROW YET?
BPL SHIFTIT LOOP BACK IF NOT
STA BUFFER ;STORE THE LAST SHIFTED PART
;
; ACTUAL DRAW CODE STARTS HERE. NOTE THAT THE
;RIGHTHAND AND LEFTHAND EDGE BYTES ARE TREATED
;DIFFERENTLY BECAUSE THEY MAY BE PARTIAL-BYTE
; WRITE OPERATIONS
;
LDY SBWIDTH ;SHIFTED DATA BYTE WIDTH
LDX TEMP ;GET BACK THE ROW #
;
;DO THE RIGHTHAND IMAGE BYTE
;
LDA (BASE1),Y ;GET A SCREEN BYTE
EOR BUFFER,Y ;XOR WITH IMAGE DATA
AND RMASK ;MASK THE UNWRITTEN AREA
EOR (BASE1),Y ;RESTORE SCRN AND IMAGE
JMP DRAW2
;
; FAST LOOP TO DRAW IN-BETWEEN BYTES
;
DRAW1 LDA BUFFER,Y ;GET AN IMAGE BYTE
DRAW2 STA (BASE1),Y ;WRITE BYTE TO SCREEN
DEY ;DECREMENT COUNT
BNE DRAW1 ;LOOP BACK IF NOT DONE
;
; FINISH UP WITH THE LEFTHAND BYTE
;
DRAW3 LDA (BASE1),Y ;GET A SCREEN BYTE
EOR BUFFER,Y ; XOR WITH IMAGE BYTE
AND LMASK ;MASK UNWANTED PART

(CONTINUED)


page 3 of assembly:


EOR (BASE1),Y ;RESTORE SCRN AND IMAGE
STA (BASE1),Y ;AND WRITE TO SCREEN
;
; TEST FOR LAST ROW COMPLETE
;
CPX Y2 ;WAS LAST ROW DONE
BEQ EXIT ;WUIT IF SO
;
INX ;MOVE TO NEXT ROW
CLC ;ADD THE BITMAP PITCH
LDA PATCH1 ;TO THE SHIFT ROUTINE
ADC PITCH ;POINTER TO MOVE TO
STA PATCH1 ;THE NEXT BITMAP ROW
BCC DRAW ;LOOP AGAIN IF NO CARY
INC PATCH1+1
BCS DRAW ;LOOP AGAIN, ALWAYS
EXIT LDX XSAVE
RTS ;EXIT HERE
;
; RIGHT AND LEFT BIT-MASKS TABLES
;
RMASKS DFB $01,$03,$07,$0F, $1F, $3F,$7F
LMASKS DFB $7F,$7E,$7C,$78,$70,$60,$40
;
;PROGRAM VARIABLES
;
Y2 DFB 0 ;BOTTOM Y-COORD
LBYTE DFB 0 ;LEFT BYTE#
LMASK DFB ; LEFT BIT MASK
RMASK DFB 0 ;RIGHT BIT MASK
SBWIDTH DFB ;SHIFTED IMAGE BYTE WIDTH
PITCH DFB ;BITMAP ROW PITCH
SHFTINDX DFB 0 ;BITMAP WIDTH
TEMP DFB 0 ;TEMP STORAGE
XSAVE DFB 0 ;FOR SAVED X-REG
BUFFER DS 40,0 ;SHIFTED DATA ROW BUFFER

heuser...@freenet.de

unread,
Oct 16, 2007, 11:57:20 PM10/16/07
to

I can do a page or two - but only next week.
We'll see what is left then.

bye
Marcus

aiia...@gmail.com

unread,
Oct 17, 2007, 1:30:38 PM10/17/07
to
On Oct 16, 8:57 pm, heuser.mar...@freenet.de wrote:
> I can do a page or two - but only next week.
> We'll see what is left then.


I have all done except 1,5,6

half of listing 1 is done.

Rich

aiia...@gmail.com

unread,
Oct 17, 2007, 1:51:21 PM10/17/07
to
On Oct 16, 8:57 pm, heuser.mar...@freenet.de wrote:
> I can do a page or two - but only next week.
> We'll see what is left then.


WHAT IS LEFT TODAY: LISTING 6

ALL OTHERS TYPED IN (NOT THE REM STATEMENTS THOUGH!)


rICH

aiia...@gmail.com

unread,
Oct 17, 2007, 2:22:22 PM10/17/07
to
On Oct 16, 8:57 pm, heuser.mar...@freenet.de wrote:
> I can do a page or two - but only next week.
> We'll see what is left then.

How about proof read? You can use an Echo card (?mockingboard?) to
read the text back to you while you read the PDF.

I completed typing in all 6 listings.


LISTING1
200 t2blbgn = 16384
210 rem beginning of table as
220 rem stored in memory
235 tblwdth = 192
236 rem width of each table
240 hi1bgn=8192
250 rem addr of beginning
260 rem of hires page 1
266 addr = t2blbgn
269 rem this pgm calculates
270 rem addresses in ascending
271rem order; addr holds
272 rem the address of the text
273 rem table element to be
274 filled

300 REM MAIN LOOP OF PGM
310 REM
320 FOR I = 0 TO 2
325:FOR J = 0 TO 7
330::FOR K = 0 TO 7
340:::VL = H1BGN + 40 * i + 128 *j+1024*K
353:::VHI = INT (VL/256)
356:::V2LOW = VL - 256 * VHI
359 :::POKE ADDR,V2LOW
362 :::POKE ADDR + TBLWDTH,VHI
366:ADDR = ADDR + 1
370::NEXT K
375 PRINT ".";
380:NEXT J
384 NEXT I
385 PRINT
420 REM SAVE FILE TO DISK
430 REM
440 PRINT CHR$(4);"BSAVE HIRES1 TABLE, A";T2BLBGN;",L384"
450 REM
455 PRINT :PRINT"TABLE SAVED TO DISK"
460 END

LISTING2

listing 2


210 bgntbl = 30720
address of start of
table; must be evenly
divisible by 256


binincr = 7 * 256
distance from beginning
of shiftout(sout)
to shiftstay(sstay)
tables


tblwdth = 256
distance between
any two tables


c1zmaxshf = 6
c2maxbytevl = 255


420 rem main loop
430 rem
450 home:print "creating preshift table (this will take several
minutes) ";
460 for shf = 0 to c1maxshf
480:currtbl = bgntbl + shf * tblwdth
500 : for byte = 0 to c2maxbytevl
520::gosub 1000

calculate shiftout
and shiftstay values
from shf and byte


640::poke currtbl + byte, sstay
660::poke currtbl + byte + bigincr,sout

store values in tables

725 ::print ":";
740 :next byte
760 next shf
770 print

save tables as one
large disk file

?chr$(4);"bsave preshift table,a";bgntbl;",l3584"
890 print:print"table saved to disk"

910 rem end of program


subroutine to split
an arbitrary 8-bit
value into its
components; see
text for details

1000 if shf = 0 then sout = 0:sstay = byte:goto 1380

1010 rem the following code
1012 rem done if shf > 0

1015 c3scaleout = 2 ^ (7-shf)
1020 c4scalnw = 2 ^ shf
1030 bsve = byte

1060 if byte > = 128 then signbit = 1:byte = byte - 128:goto 1140
1080 rem (else if byte < 128)
1100 signbit = 0
1110 rem (and byte unchanged)
1120 rem
1140 sout = int (byte / c3scaleout)
1160 rem find shiftout bits
1180 rem by cutting off right
1200 most (7-shf) bits
1210 rem
1220 sstay = 128 * signbit + (byte - sout * c3scaleout)*c4scalnw
1240 rem
1260 byte = bsve
1280 rem restore original
1300 rem value of byte
1320 rem
1340 rem end subroutine
1360 rem
1380 return


LISTING3

ORG $5210

(CONTINUED)

LDA RMASKS,Y ;INDEX RMASKS TABLE FOR

(CONTINUED)

EOR (BASE1),Y ;RESTORE SCRN AND IMAGE

BUFFER DS 40,0 ;SHIFTED DATA ROW BUFFER ORG $5210

(CONTINUED)

LDA RMASKS,Y ;INDEX RMASKS TABLE FOR

(CONTINUED)

EOR (BASE1),Y ;RESTORE SCRN AND IMAGE


LISTING4

100 rem
110 rem divide by 7 quotient
120 rem and remaindertables
130 rem
140 rem by gregg williams
150 rem 24 april 1984
160 rem
200 quotbgn = 16384
210 rem points to memory area
220 rem used to store table
230 rem
240 rmdrbgn = quotbgn+256
250 home:print"creating div7 table..."
300 for i = 0 to 255
310 :qvl = int(i/7)
320:rvl = i - qvl*7
330 poke quotbgn+i,qvl
340 poke rmdrbgn+I,rvl
350 next i
400 ? chr$(4);"bsave div7 table, a";quotbgn;",l512"
420 print:print "table saved to disk"
500 end


listing 5

190 home:print "creating tablpak...."
200 tblsiz = 32
240 d$=chr$(4)
250 print d$;"BLOAD PRESHIFT TABLE,A$4000"
260 PRINT D$;"BLOAD DIV7 TABLE, A$4E00"
270 PRINT D$;"BLOAD HIRES1 TABLE,A$5000"
550 QQ$ = "5180:0D 0D 02 00 00 00 00 00 7C OF 7C 07 7C 03 7C 01 7C 03
7C 07 5C 0F 0C 1F 04 0E 00 04 00 00 00 00
560 GOSUB 63000
610 PRINT D$;"BSAVE TABLPAK,A$4000,L";4480+TBLSIZ
615 PRINT :?"FILE SAVED TO DISK"
620 END
63000 QQ$=QQ$+" ND9C6G"
63010 FOR QQ = 1 TO LEN(QQ$):POKE 511+QQ,128+ASC(MID$(QQ$,QQ,1)):NEXT
63020 POKE 72,0:CALL -144
63030 RETURN


LISTING 6


220 gosub 3000

260 GOSUB 2000
570 XVLUE= PDL(0)
580 YVLUE = PDL(1)
620 XINCR = -1*DOTSMOVE*(XVLUE<C1THRLO)+DOTSMOVE*(XVLUE>C2THRHI)
630 YINCR = -1*DOTSMOVE*(YVLUE<C1THRLO)+DOTSMOVE+(YVLUE>C2THRHI)
670 IF (XPSN+XINCR)>=C3XMIN AND (XPSN+XINCR)<=C4XMAX THEN XPSN = XPSN
+XINCR
680 IF (YPSN+YINCR)>=C5YMIN AND (YPSN + YINCR)<=C6YMAX THEN YPSN =
YPSN + YINCR
706 POKE X1,XPSN
708 POKE Y1,YPSN
720 CALL CODEADDR
760 GOTO 530
810 END
2000 DOTSMOVE = 2
2040 XPSN = 100:YPSN = 100
2070 C1THRLO = 100:C2THRHI = 150
2110 C2XMIN = 5:C4XMAX = 235
2120 C5YMIN=65:C6YMAX=175
2160 CODEADDR = 21006
2200 IROWS = 20992
2210 IDOTS = IROWS+1
2220 IWIDTH = IROWS + 2
2230 IBITS = IROWS+3
2240 X1=IROWS+5
2250 Y1 = IROWS + 6
2420 POKE IROWS, PEEK(IMAGTBL)
2430 POKE IDOTS, PEEK(IMAGTBL+1)
2440 POKE IWIDTH,PEEK(IMAGTBL+2)
2450 IP = IMAGTBL+3
2460 C8IPLO = INT(IP/256)
2470 C7IPHI = IP-256*C8IPLO
2480 POKE IBITS, C7IPLO
2490 POKE IBITS+1,C8IPHI
2540 HGR:POKE -16302,0
2570 RETURN

3000 IMAGTBL = 20664
3050 D$=CHR$(4)
3060 PRINT D$;"BLOAD QD.DEMO.0"
3070 PRINT D$;"BLOAD TABLPAK,A$4000"
3080 PRINT D$;"BLOAD IMAGE,A";IMAGTBL
3120 RETURN

winston19842005

unread,
Oct 17, 2007, 2:40:39 PM10/17/07
to
One thing I always wanted to try on my //e was Home Computer Magazine's
graphics routines.

While many of us (me included) bought a cheaper computer that used tile
graphics, requiring some interesting coding to emulate line graphics of the
Apple II line, there _were_ some interesting programs using those tile
graphics. (Yes, believe me, there were some).

These assembly routines added tile graphics. I'm going to have to look up my
magazines and get my //e running again (think I'll skip the //c, it isn't
the same...)

aiia...@gmail.com

unread,
Oct 17, 2007, 4:01:21 PM10/17/07
to
On Oct 17, 11:40 am, winston19842005 <bjjlya...@bellsouth.net> wrote:
> These assembly routines added tile graphics.

"sprites" were done with hardware in the Atari, Commodore, etc..

the closest thing to "sprites" on the apple II is
"preshifted animation".


for some easy to use graphics routines that will draw sprites, see:
http://rich12345.tripod.com/bse/index.html

Some day I'll return to this project, which will display "tile" based
graphics, and allow fast horizontal scroll... vertical scroll is
acheived
by memory moves..
http://rich12345.tripod.com/tilengine/index.html


Rich

aiia...@gmail.com

unread,
Oct 17, 2007, 5:00:57 PM10/17/07
to
On Oct 16, 8:57 pm, heuser.mar...@freenet.de wrote:
> I can do a page or two - but only next week.
> We'll see what is left then.

winston19842005

unread,
Oct 17, 2007, 5:01:38 PM10/17/07
to


On 10/17/07 4:01 PM, in article
1192651281.0...@q5g2000prf.googlegroups.com, "aiia...@gmail.com"
<aiia...@gmail.com> wrote:

> On Oct 17, 11:40 am, winston19842005 <bjjlya...@bellsouth.net> wrote:
>> These assembly routines added tile graphics.
>
> "sprites" were done with hardware in the Atari, Commodore, etc..
>
> the closest thing to "sprites" on the apple II is
> "preshifted animation".

I tried to write assembly code to do what you call "preshifted animation" on
the TI-99, because of the sprite limitations (4 on a line).

Stopped work on it due to the color limitations of bitmap (one foreground,
one background color on each row of a character.)

heuser...@freenet.de

unread,
Oct 21, 2007, 3:20:44 PM10/21/07
to
On Oct 17, 8:22 pm, aiiad...@gmail.com wrote:
>
> How about proof read?

Good idea! ;-)

> You can use an Echo card (?mockingboard?) to
> read the text back to you while you read the PDF.

Too slow and not accurate enough (for me).

I hope that I found & corrected everything. Included some
REMs, did a bit of formatting and REMmed line 3080 of
listing 6 as it didn't make sense to load a separate image
table file (the image data is part of the TABLTAK file).
Also: The object code of the machine language subroutine
should be saved with the filename QD.DEMO.O to work
with the sample program in listing 6.

Here you go:


Listing 1

200 t2blbgn = 16384
210 rem beginning of table as
220 rem stored in memory
235 tblwdth = 192
236 rem width of each table
240 hi1bgn = 8192
250 rem addr of beginning
260 rem of hires page 1
266 addr = t2blbgn
269 rem this pgm calculates
270 rem addresses in ascending

271 rem order; addr holds


272 rem the address of the text
273 rem table element to be

274 rem filled

300 REM MAIN LOOP OF PGM
310 REM
320 FOR I = 0 TO 2
325:FOR J = 0 TO 7
330::FOR K = 0 TO 7
340:::VL = H1BGN + 40 * i + 128 * j + 1024 * K
353:::VHI = INT (VL / 256)
356:::V2LOW = VL - 256 * VHI
359 :::POKE ADDR,V2LOW
362 :::POKE ADDR + TBLWDTH,VHI
366:ADDR = ADDR + 1
370::NEXT K
375 PRINT ".";
380:NEXT J
384 NEXT I
385 PRINT
420 REM SAVE FILE TO DISK
430 REM
440 PRINT CHR$(4);"BSAVE HIRES1 TABLE, A";T2BLBGN;",L384"
450 REM
455 PRINT :PRINT "TABLE SAVED TO DISK"
460 END


Listing 2

210 bgntbl = 30720
220 rem address of start of
230 rem table; must be evenly
240 rem divisible by 256
250 rem
260 binincr = 7 * 256
270 rem distance from beginning
280 rem of shiftout(sout)
290 rem to shiftstay(sstay)
300 rem tables
310 rem
320 tblwdth = 256
330 rem distance between
340 rem any two tables
350 rem
360 c1zmaxshf = 6
370 c2maxbytevl = 255
380 rem


420 rem main loop
430 rem
450 home:print "creating preshift table (this will take several
minutes) ";
460 for shf = 0 to c1maxshf
480 : currtbl = bgntbl + shf * tblwdth
500 : for byte = 0 to c2maxbytevl
520 ::gosub 1000

530 rem
540 rem calculate shiftout
550 rem and shiftstay values
560 rem from shf and byte
570 rem


640::poke currtbl + byte, sstay
660::poke currtbl + byte + bigincr,sout

670 rem
680 rem store values in tables
690 rem
725 ::print ".";


740 :next byte
760 next shf
770 print

780 rem
790 rem save tables as one
800 rem large disk file
810 rem
820 print chr$(4);"bsave preshift table,a";bgntbl;",l3584"


890 print:print"table saved to disk"

900 rem


910 rem end of program

920 rem
930 rem subroutine to split
940 rem an arbitrary 8-bit
950 rem value into its
960 rem components; see
970 rem text for details
980 rem


1000 if shf = 0 then sout = 0:sstay = byte:goto 1380

1005 rem


1010 rem the following code
1012 rem done if shf > 0

1013 rem


1015 c3scaleout = 2 ^ (7 - shf)
1020 c4scalnw = 2 ^ shf
1030 bsve = byte

1040 rem


1060 if byte > = 128 then signbit = 1:byte = byte - 128:goto 1140
1080 rem (else if byte < 128)
1100 signbit = 0
1110 rem (and byte unchanged)
1120 rem
1140 sout = int (byte / c3scaleout)
1160 rem find shiftout bits
1180 rem by cutting off right

1200 rem most (7-shf) bits


1210 rem
1220 sstay = 128 * signbit + (byte - sout * c3scaleout)*c4scalnw
1240 rem
1260 byte = bsve
1280 rem restore original
1300 rem value of byte
1320 rem
1340 rem end subroutine
1360 rem
1380 return

Listing 3


ORG $5210

;
; PRESHIFT GRAPHICS ROUTINE
; BY ROB MOORE AND BILL BUDGE
;

EOR (BASE1),Y ;RESTORE SCRN AND IMAGE
STA (BASE1),Y ;AND WRITE TO SCREEN
;
; TEST FOR LAST ROW COMPLETE
;
CPX Y2 ;WAS LAST ROW DONE
BEQ EXIT ;WUIT IF SO
;
INX ;MOVE TO NEXT ROW
CLC ;ADD THE BITMAP PITCH
LDA PATCH1 ;TO THE SHIFT ROUTINE
ADC PITCH ;POINTER TO MOVE TO
STA PATCH1 ;THE NEXT BITMAP ROW
BCC DRAW ;LOOP AGAIN IF NO CARY
INC PATCH1+1
BCS DRAW ;LOOP AGAIN, ALWAYS
EXIT LDX XSAVE
RTS ;EXIT HERE
;
; RIGHT AND LEFT BIT-MASKS TABLES
;
RMASKS DFB $01,$03,$07,$0F,$1F,$3F,$7F
LMASKS DFB $7F,$7E,$7C,$78,$70,$60,$40
;
;PROGRAM VARIABLES
;
Y2 DFB 0 ;BOTTOM Y-COORD
LBYTE DFB 0 ;LEFT BYTE#

LMASK DFB 0 ;LEFT BIT MASK


RMASK DFB 0 ;RIGHT BIT MASK

SBWIDTH DFB 0 ;SHIFTED IMAGE BYTE WIDTH
PITCH DFB 0 ;BITMAP ROW PITCH


SHFTINDX DFB 0 ;BITMAP WIDTH
TEMP DFB 0 ;TEMP STORAGE
XSAVE DFB 0 ;FOR SAVED X-REG
BUFFER DS 40,0 ;SHIFTED DATA ROW BUFFER

Listing 4

100 rem
110 rem divide by 7 quotient
120 rem and remaindertables
130 rem
140 rem by gregg williams
150 rem 24 april 1984
160 rem
200 quotbgn = 16384
210 rem points to memory area
220 rem used to store table
230 rem
240 rmdrbgn = quotbgn+256
250 home:print"creating div7 table..."
300 for i = 0 to 255
310 :qvl = int(i/7)
320 :rvl = i - qvl*7
330 poke quotbgn+i,qvl
340 poke rmdrbgn+I,rvl
350 next i

400 print chr$(4);"bsave div7 table, a";quotbgn;",l512"


420 print:print "table saved to disk"
500 end

Listing 5

190 home:print "creating tablpak...."
200 tblsiz = 32
240 d$=chr$(4)
250 print d$;"BLOAD PRESHIFT TABLE,A$4000"
260 PRINT D$;"BLOAD DIV7 TABLE, A$4E00"
270 PRINT D$;"BLOAD HIRES1 TABLE,A$5000"

550 QQ$ = "5180:0D 0D 02 00 00 00 00 7C OF 7C 07 7C 03 7C 01 7C 03


7C 07 5C 0F 0C 1F 04 0E 00 04 00 00 00 00
560 GOSUB 63000
610 PRINT D$;"BSAVE TABLPAK,A$4000,L";4480+TBLSIZ
615 PRINT :?"FILE SAVED TO DISK"
620 END
63000 QQ$=QQ$+" ND9C6G"
63010 FOR QQ = 1 TO LEN(QQ$):POKE 511+QQ,128+ASC(MID$(QQ$,QQ,1)):NEXT
63020 POKE 72,0:CALL -144
63030 RETURN

Listing 6

220 GOSUB 3000
260 GOSUB 2000
570 XVLUE = PDL(0)


580 YVLUE = PDL(1)
620 XINCR = -1 * DOTSMOVE * (XVLUE < C1THRLO) + DOTSMOVE * (XVLUE >
C2THRHI)

630 YINCR = -1 * DOTSMOVE * (YVLUE < C1THRLO) + DOTSMOVE * (YVLUE >
C2THRHI)
670 IF (XPSN + XINCR) >= C3XMIN AND (XPSN + XINCR) <= C4XMAX THEN XPSN
= XPSN + XINCR
680 IF (YPSN + YINCR) >= C5YMIN AND (YPSN + YINCR) <= C6YMAX THEN YPSN


= YPSN + YINCR
706 POKE X1,XPSN
708 POKE Y1,YPSN
720 CALL CODEADDR
760 GOTO 530
810 END
2000 DOTSMOVE = 2
2040 XPSN = 100:YPSN = 100
2070 C1THRLO = 100:C2THRHI = 150

2110 C3XMIN = 5:C4XMAX = 235
2120 C5YMIN = 5:C6YMAX = 175
2160 CODEADDR = 21008


2200 IROWS = 20992
2210 IDOTS = IROWS + 1
2220 IWIDTH = IROWS + 2
2230 IBITS = IROWS + 3
2240 X1 = IROWS + 5
2250 Y1 = IROWS + 6
2420 POKE IROWS, PEEK(IMAGTBL)
2430 POKE IDOTS, PEEK(IMAGTBL + 1)
2440 POKE IWIDTH,PEEK(IMAGTBL + 2)
2450 IP = IMAGTBL+3
2460 C8IPLO = INT(IP / 256)
2470 C7IPHI = IP - 256 * C8IPLO
2480 POKE IBITS, C7IPLO
2490 POKE IBITS + 1, C8IPHI
2540 HGR:POKE -16302,0
2570 RETURN

3000 IMAGTBL = 20864
3050 D$=CHR$(4)
3060 PRINT D$;"BLOAD QD.DEMO.O"


3070 PRINT D$;"BLOAD TABLPAK,A$4000"

3080 rem PRINT D$;"BLOAD IMAGE,A";IMAGTBL
3120 RETURN


--

bye
Marcus

aiia...@gmail.com

unread,
Oct 22, 2007, 1:13:56 PM10/22/07
to
On Oct 21, 12:20 pm, heuser.mar...@freenet.de wrote:
>
> Here you go:

Great, thanks!

Rich

aiia...@gmail.com

unread,
Oct 22, 2007, 2:19:18 PM10/22/07
to
On Oct 21, 12:20 pm, heuser.mar...@freenet.de wrote:
> I hope that I found & corrected everything. Included some
> REMs, did a bit of formatting and REMmed line 3080 of
> listing 6 as it didn't make sense to load a separate image
> table file (the image data is part of the TABLTAK file).
> Also: The object code of the machine language subroutine
> should be saved with the filename QD.DEMO.O to work
> with the sample program in listing 6.
>
> Listing 6


I got everything to run except for listing 6. The other listings are
saved on a DSK image if anyone wants them.

Listing 6 is corrupting itself (the end of the basic program is
getting
overwritten with garbage... one of the pokes is POKEing in the
wrong spot, or perhaps it has something to do with running it
in PRODOS that isn't working (filling up RAM map))

Rich

Michael J. Mahon

unread,
Nov 12, 2007, 10:09:44 AM11/12/07
to
aiia...@gmail.com wrote:
> On Oct 16, 8:57 pm, heuser.mar...@freenet.de wrote:
>
>>I can do a page or two - but only next week.
>>We'll see what is left then.
>
>
> How about proof read? You can use an Echo card (?mockingboard?) to
> read the text back to you while you read the PDF.

I'll bet that the text-to-speech algorithm sounds pretty weird
reading a program, with all its non-word words.

-michael

NadaPong: Network game demo for Apple II computers!
Home page: http://members.aol.com/MJMahon/

"The wastebasket is our most important design
tool--and it's seriously underused."

0 new messages