/////////////////////////////////////////////////////////////////////////////////////////////////// // Copyright (C) 2015 The 8-Bit Bunch. Licensed under the Apache License, Version 1.1 // (the "License"); you may not use this file except in compliance with the License. // You may obtain a copy of the License at . // Unless required by applicable law or agreed to in writing, software distributed under // the License is distributed on an "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF // ANY KIND, either express or implied. See the License for the specific language // governing permissions and limitations under the License. /////////////////////////////////////////////////////////////////////////////////////////////////// /////////////////////////////////////////////////////////////////////////////////////////////////// // Fixed memory locations const seed = $4E // Incremented continuously by keyboard read routine const displayEngine = $6000 // main mem (raycaster and tile engine at same location) const expandVec = $800 // aux mem (only for raycaster) const fontEngine = $EC00 // main mem LC const fontEngineLen = $F00 // really a bit less, but this leaves space for debug code const fontData = $FB00 // main mem LC const fontDataLen = $4FA // really only $474, but we need to fill all gaps /////////////////////////////////////////////////////////////////////////////////////////////////// // Other constants const CHAR_WND_HEALTH_X = 66 const ANIM_PAUSE_MAX = 300 // Max gold const GOLD_MAX = 20000 include "globalDefs.plh" include "playtype.plh" include "gen_images.plh" include "gen_modules.plh" include "gen_enemies.plh" include "gen_players.plh" include "gen_items.plh" include "combat.plh" include "party.plh" include "store.plh" include "diskops.plh" include "intimate.plh" include "godmode.plh" /////////////////////////////////////////////////////////////////////////////////////////////////// // Data structures include "playtype.pla" export word global // the global heap object, from which all live objects must be reachable /////////////////////////////////////////////////////////////////////////////////////////////////// // Predefined functions, for circular calls or out-of-order calls predef setWindow2, initCmds, nextAnimFrame, checkEncounter, doCombat, clearPortrait, showMapName predef doRender, playerDeath, startGame, showAnimFrame, finalWin, showParty /////////////////////////////////////////////////////////////////////////////////////////////////// // Global variables export byte mapNum = -1 export byte mapIs3D = -1 word mapNameHash = 0 word totalMapWidth word totalMapHeight byte needRender = FALSE byte needShowParty = FALSE byte renderLoaded = FALSE byte texturesLoaded = FALSE byte textDrawn = FALSE byte isPlural = FALSE byte skipEncounterCheck = FALSE export word skyNum = 9 export word groundNum = 10 export byte portraitNum = 1 word triggerOriginX, triggerOriginY word triggerTbl word cmdTbl[96] // ASCII $00..$5F byte frameLoaded = 0 byte heapLocked = FALSE byte allowZoneInit = FALSE word curEngine = NULL word pIntimate = NULL word pResourceIndex = NULL byte curMapPartition = 0 export word pGodModule = NULL // Queue setMap / teleport / start_encounter, since otherwise script might be replaced while executing byte q_mapIs3D = 0 byte q_mapNum = 1 word q_x = 0 word q_y = 0 byte q_dir = 0 // Script tracking const MAX_MAP_SCRIPTS = 4 byte nMapScripts = 0 word mapScripts[MAX_MAP_SCRIPTS] // For decimal conversion and display tabbing byte decimalBuf[7] byte fontPosBuf[4] byte tabBuf[5] // Animation tracking word curPortrait = NULL byte curPortraitNum = 0 word curFullscreenImg = NULL byte animDirCt byte anyAnims = TRUE word animPauseCt // Shared string constants export byte[] S_INTELLIGENCE = "intelligence" export byte[] S_STRENGTH = "strength" export byte[] S_AGILITY = "agility" export byte[] S_STAMINA = "stamina" export byte[] S_CHARISMA = "charisma" export byte[] S_SPIRIT = "spirit" export byte[] S_LUCK = "luck" export byte[] S_HEALTH = "health" export byte[] S_MAX_HEALTH = "max health" export byte[] S_AIMING = "aiming" export byte[] S_HAND_TO_HAND = "hand to hand" export byte[] S_DODGING = "dodging" export byte[] S_GOLD = "gold" export byte[] S_ENTER = "enter" export byte[] S_LEAVE = "leave" export byte[] S_USE = "use" /////////////////////////////////////////////////////////////////////////////////////////////////// // Definitions used by assembly code asm _defs ; Use hi-bit ASCII for Apple II !convtab "../../include/hiBitAscii.ct" ; Headers !source "../../include/global.i" !source "../../include/plasma.i" !source "../../include/mem.i" !source "../../include/fontEngine.i" ; Optional debug printing support DEBUG = 0 ; General use tmp = $2 pTmp = $4 ysav = $34 ysav1 = $35 ; 16-bit random number seed - incremented by ROM kbd routine seed = $4E magic = $2227 ; there are 2048 magic values that work; this one caught my eye. - MH ; NOTE ABOUT ABSOLUTE CODE ADDRESSING (e.g. STA .var, JMP .label, etc.) ; We cannot use it: this code, including variable space, can be loaded *anywhere*. ; So don't JMP to labels, declare any variables as !byte or !word here, etc. end /////////////////////////////////////////////////////////////////////////////////////////////////// // Temporary hack: after scriptDisplayStr is called, generated code calls this to clear the PLASMA // string pool. That way, many long strings can be used in a single function. export asm tossStrings lda framePtr sta outerFramePtr lda framePtr+1 sta outerFramePtr+1 dex rts end /////////////////////////////////////////////////////////////////////////////////////////////////// // API to call rendering engine (same API for raycaster and tile engine) asm initDisplay#0 // params: mapNum, pMapData, x, y, dir +asmPlasmNoRet 6 jmp $6000 end export asm flipToPage1#0 // no params +asmPlasmNoRet 0 jmp $6003 end export asm getPos#0 // params: @x, @y +asmPlasmNoRet 2 jmp $6006 end asm setPos#0 // params: x, y +asmPlasmNoRet 2 jmp $6009 end export asm getDir // no params; returns: dir (0-15) +asmPlasmRet 0 jmp $600C end asm setDir // params: dir (0-15) +asmPlasmRet 1 jmp $600F end asm advance // no params; return: 0 if same pos, 1 if new pos, 2 if new pos and scripted +asmPlasmRet 0 jmp $6012 end asm setColor // params: slot (0=sky/1=ground), color (0-17) +asmPlasmRet 2 jmp $6015 end asm render // no params +asmPlasmRet 0 jmp $6018 end asm texControl // params: load (1=load, 0=unload) +asmPlasmRet 1 jmp $601B end asm getMapScript // params: none +asmPlasmRet 0 jmp $601E end export asm setAvatar // params: tile number (in the global tileset) +asmPlasmRet 1 jmp $6021 end asm swapTile // params: fromX, fromY, toX, toY +asmPlasmRet 4 jmp $6024 end /////////////////////////////////////////////////////////////////////////////////////////////////// export asm memcpy // params: pSrc, pDst, len. Non-overlapping only! +asmPlasmRet 3 lda evalStkL+2,x ; source ptr sta tmp lda evalStkH+2,x sta tmp+1 lda evalStkL+1,x ; dest ptr sta pTmp lda evalStkH+1,x sta pTmp+1 lda evalStkH,x ; len hi pha lda evalStkL,x ; len lo tax ldy #0 .pglup: pla sec sbc #1 bcc .part pha - lda (tmp),y sta (pTmp),y iny bne - inc tmp+1 inc pTmp+1 bne .pglup ; always taken .part: cpx #0 beq .done - lda (tmp),y sta (pTmp),y iny dex bne - .done rts end /////////////////////////////////////////////////////////////////////////////////////////////////// export asm memset // params: pDst, val, len. +asmPlasmRet 3 ldy #0 lda evalStkL+2,x ; dest ptr sta pTmp lda evalStkH+2,x sta pTmp+1 lda evalStkL+1,x ; value sta tmp lda evalStkL,x ; len lo pha lda evalStkH,x ; len hi tax beq + lda tmp - sta (pTmp),y iny bne - inc pTmp+1 dex bne - + pla beq + tax lda tmp - sta (pTmp),y iny dex bne - + rts end /////////////////////////////////////////////////////////////////////////////////////////////////// asm readAuxByte // params: ptr; ret: char +asmPlasmRet 1 ; Create the following subroutine, used to copy one char from aux to main: ;0010- 8D 03 C0 STA $C003 ;0013- AD XX XX LDA $XXXX ;0016- 8D 02 C0 STA $C002 ;0019- 60 RTS sta $14 sty $15 lda #$8D sta $10 sta $16 ldx #2 stx $17 inx stx $11 lda #$C0 sta $12 sta $18 lda #$AD sta $13 lda #$60 sta $19 ; And call the routine ldy #0 jmp $10 end /////////////////////////////////////////////////////////////////////////////////////////////////// asm splitExpander // param: expandVec; returns: remaining lo-aux size +asmPlasmRet 1 ; assumes readAuxByte has just been called, which puts a little routine at $10. ; Adjust that routine to call expander instead of reading a byte. sta $1B sty $1C lda #$6C sta $1A lda #$20 sta $13 lda #$60 sta 2 jsr 2 sei ; prevent interrupts while in aux mem jsr $10 cli rts end /////////////////////////////////////////////////////////////////////////////////////////////////// // String building for display with the font engine. Includes plurality processing to handily // handle things like "Dirt bag(s)" and "his/their" export asm buildString +asmPlasmRet 1 sta cswl sty cswh lda #0 sta inbuf rts end export asm addToString sty ysav1 inc inbuf ldy inbuf sta inbuf,y ldy ysav1 rts end // Complete string building (including plural processing), and return pointer // to the string (in the input buffer) export asm finishString !zone { +asmPlasmRet 1 sta tmp ; save isPlural flag lda #$F0 ; put the cout vector back to default sta cswl lda #$FD sta cswh bit fixedRTS; V flag for prev-is-punctuation ldy #1 ; dest offset in Y ldx #1 ; source offset in X cpx inbuf beq + ; only process if string has at least 1 char bcs .done + sty tmp+1 ; offset of last punctuation .fetch lda inbuf,x cmp #"(" bne .notpar bvs .notpar ; skip paren processing right punctuation lda tmp ; check isPlural flag bne .plurpr - lda inbuf,x ; it's singular, so skip everything in parens cmp #")" beq .next inx cpx inbuf bne - beq .done ; handle missing trailing paren .plurpr inx ; it's plural, so copy everything within the parens lda inbuf,x ; copy characters cpx inbuf ; handle missing trailing paren beq + bcs .store + cmp #")" ; go until we reach ending paren beq .next sta inbuf,y iny bne .plurpr ; always taken .notpar cmp #"/" bne .notsl bvs .notsl ; skip slash processing right after punctuation lda tmp ; check isPlural flag bne .plursl - inx ; loop that skips plural form cpx inbuf beq + bcs .done ; handle end of string + lda inbuf,x cmp #"A" ; eat letters (and stop when we hit punctuation) bcs - bcc .store ; copy the ending punctuation and continue normal processing .plursl ldy tmp+1 ; erase singular form by backing up to prev punc iny ; plus 1 to retain prev punc bne .next ; resume regular copying of the plural form .notsl cmp #"A" ; if <= ASCII "A", consider it punctuation bcc + clv ; clear last-is-punc flag bvc .store ; always taken + bit fixedRTS; set prev-is-punc flag sty tmp+1 ; save dest offset of last punctuation .store sta inbuf,y ; save to dest iny .next inx cpx inbuf ; compare src offset to length bcc .fetch ; loop while less than beq .fetch ; or equal .done dey sty inbuf ; save new length lda #inbuf rts } end /////////////////////////////////////////////////////////////////////////////////////////////////// asm blit // params: srcData, dstScreenPtr, nLines, lineSize +asmPlasmRet 4 ; Save line size sta ysav ; Save nLines lda evalStkL+1,x pha ; Save the dest pointer lda evalStkL+2,x sta pTmp lda evalStkH+2,x sta pTmp+1 ; Save the source pointer lda evalStkL+3,x sta tmp lda evalStkH+3,x sta tmp+1 ; Create the following subroutine, used to copy pixels from aux to main: ; 0010- 8D 03 C0 STA $C003 ; 0013- B1 02 LDA ($02),Y ; 0015- 91 04 STA ($04),Y ; 0017- 88 DEY ; 0018- 10 F9 BPL $0013 ; 001A- 8D 02 C0 STA $C002 ; 001D- 60 RTS lda #$8D sta $10 sta $1A ldx #2 stx $14 stx $1B inx stx $11 lda #$C0 sta $12 sta $1C lda #$B1 sta $13 lda #$91 sta $15 inx stx $16 lda #$88 sta $17 lda #$10 sta $18 lda #$F9 sta $19 lda #$60 sta $1D pla ; line count tax - ldy ysav ; byte count minus 1. There are 18 bytes per line dey jsr $10 ; copy pixel bytes lda tmp ; advance to next row of data clc adc ysav sta tmp bcc + inc tmp+1 + jsr NextScreenLine ; and next screen line dex bne - ; Loop until we've done all rows. rts end /////////////////////////////////////////////////////////////////////////////////////////////////// asm vline // params: dstScreenPtr, val, nLines +asmPlasmRet 3 ; Save number of lines pha ; Save value lda evalStkL+1,x sta tmp ; Save the dest pointer lda evalStkL+2,x sta pTmp lda evalStkH+2,x sta pTmp+1 pla ; line count tax - ldy #0 lda tmp sta (pTmp),y jsr NextScreenLine dex bne - rts end /////////////////////////////////////////////////////////////////////////////////////////////////// // Simply retrieve the X register. Used to double-check that we're not leaking PLASMA eval // stack entries. asm getXReg +asmPlasmRet 0 txa ldy #0 rts end /////////////////////////////////////////////////////////////////////////////////////////////////// // Calculate 16-bit hash of a buffer. arg1=pointer, arg2=length export asm hashBuffer +asmPlasmRet 2 lda evalStkL+1,x ; first arg is buffer pointer sta pTmp lda evalStkH+1,x sta pTmp+1 lda evalStkL,x ; second arg is length tax ldy #0 sty tmp+1 tya clc - adc (pTmp),y ror ror tmp+1 ror ror tmp+1 ror ror tmp+1 iny dex bne - ldy tmp+1 rts end /////////////////////////////////////////////////////////////////////////////////////////////////// // Print a string to the current character output vector export asm puts()#0 +asmPlasmNoRet 1 sta pTmp lda #'!' ldx #1 sty pTmp+1 beq + ; safety: print '!' instead of null string ldy #0 lda (pTmp),y tax iny - lda (pTmp),y + ora #$80 +safeCout iny dex bne - rts end /////////////////////////////////////////////////////////////////////////////////////////////////// // Get a character from the keyboard export asm rdkey +asmPlasmRet 0 +safeRdkey ldy #0 rts end /////////////////////////////////////////////////////////////////////////////////////////////////// // Print part of a string, until we hit the end or a '%' code. Return how far we got, or -1 for end. asm partialPrintf !zone { +asmPlasmRet 2 lda evalStkL+1,x ; get string pointer sta pTmp lda evalStkH+1,x sta pTmp+1 ldy #0 lda (pTmp),y ; get length byte sec sbc evalStkL,x ; minus offset sta tmp ; to count of characters left to print bcc .eos ; avoid overrunning beq .eos lda evalStkL,x ; get desired offset into string tay iny ; increment past length byte - lda (pTmp),y ora #$80 cmp #'%' ; stop if we hit % code beq + +safeCout iny dec tmp ; otherwise go until end of string bne - .eos ldy #$FF ; if we hit end of string, return -1 tya rts + dey ; adjust back for length byte tya ; that's the lo byte of return ldy #0 ; hi byte of return is zero rts } end /////////////////////////////////////////////////////////////////////////////////////////////////// // Print a 16-bit hex value export asm printHex +asmPlasmRet 1 pha tya +safePrbyte pla jmp _safePrbyte end /////////////////////////////////////////////////////////////////////////////////////////////////// // Print a single character asm printChar +asmPlasmRet 1 ora #$80 jmp _safeCout end /////////////////////////////////////////////////////////////////////////////////////////////////// // Print a carriage return asm crout +asmPlasmRet 0 lda #$8D jmp _safeCout end /////////////////////////////////////////////////////////////////////////////////////////////////// // Ring the bell export asm beep +asmPlasmRet 0 +safeBell rts end /////////////////////////////////////////////////////////////////////////////////////////////////// // Read a string from the keyboard, turn it into a PLASMA string and return a pointer to the string. export asm readStr +asmPlasmRet 0 bit setROM jsr ROM_getln1 bit setLcRW+lcBank2 txa pha beq + - lda inbuf-1,x and #$7F sta inbuf,x dex bne - + pla sta inbuf,x lda #inbuf rts end /////////////////////////////////////////////////////////////////////////////////////////////////// // Send a command to the memory manager // Params: cmd, wordParam export asm mmgr +asmPlasmRet 2 lda evalStkL+1,x ; command code pha ldy evalStkH,x ; address (or other param)... hi byte in Y lda evalStkL,x tax ; ...lo byte in X pla jsr mainLoader ; ret value in X=lo/Y=hi txa ; to A=lo/Y=hi for asmPlasm rts end // Aux version of memory manager command export asm auxMmgr +asmPlasmRet 2 lda evalStkL+1,x ; command code pha ldy evalStkH,x ; address (or other param) lda evalStkL,x tax pla jsr auxLoader ; ret value in X=lo/Y=hi txa ; to A=lo/Y=hi for asmPlasm rts end /////////////////////////////////////////////////////////////////////////////////////////////////// // Jump straight to the system monitor // Params: None asm goMon jmp $FF69 end /////////////////////////////////////////////////////////////////////////////////////////////////// // Execute a monitor breakpoint // Params: None export asm brk bit setText bit page1 brk end /////////////////////////////////////////////////////////////////////////////////////////////////// // Set up the font engine // Params: pFont asm setFont +asmPlasmRet 1 jmp SetFont end /////////////////////////////////////////////////////////////////////////////////////////////////// // Use the font engine to clear the current text window. // Parameters: top, bottom, left, right export asm setWindow +asmPlasmRet 4 jmp SetWindow end /////////////////////////////////////////////////////////////////////////////////////////////////// // Save the cursor position (1 save slot) asm saveCursor +asmPlasmRet 0 jmp SaveCursor end /////////////////////////////////////////////////////////////////////////////////////////////////// // Restore the cursor position (1 save slot) asm restoreCursor +asmPlasmRet 0 jmp RestCursor end /////////////////////////////////////////////////////////////////////////////////////////////////// // Read a keyboard string up to 40 chars using the Font Engine. Returns a zero-terminated string // in the input buffer at $200, with the length stored in $2FF. asm rawGetStr +asmPlasmRet 0 jmp GetStr end /////////////////////////////////////////////////////////////////////////////////////////////////// // Use the font engine to clear the current text window // Params: None export asm clearWindow +asmPlasmRet 0 jmp ClearWindow end /////////////////////////////////////////////////////////////////////////////////////////////////// // Use the font engine to copy the current text window to hi-res page 2 // Params: None asm copyWindow +asmPlasmRet 0 jmp CopyWindow end /////////////////////////////////////////////////////////////////////////////////////////////////// // Display a character using the font engine. // Params: ch export asm displayChar +asmPlasmRet 1 jmp DisplayChar end /////////////////////////////////////////////////////////////////////////////////////////////////// // Display a string using the font engine. // Params: pStr export asm displayStr +asmPlasmRet 1 jmp DisplayStr end /////////////////////////////////////////////////////////////////////////////////////////////////// // Calculate string width using the font engine. // Params: pStr export asm calcWidth +asmPlasmRet 1 jmp CalcWidth end /////////////////////////////////////////////////////////////////////////////////////////////////// // Get the address of the given hi-res screen line export asm getScreenLine +asmPlasmRet 1 jmp GetScreenLine end /////////////////////////////////////////////////////////////////////////////////////////////////// // Display a string using the font engine but not its parser. // Params: pStr export asm rawDisplayStr +asmPlasmRet 1 sta pTmp sty pTmp+1 ldy #0 lda (pTmp),y sta tmp - cpy tmp bcc + rts + iny lda (pTmp),y ora #$80 cmp #"^" bne + iny lda (pTmp),y and #$1F ora #$80 + sty tmp+1 jsr DisplayChar ldy tmp+1 bne - end /////////////////////////////////////////////////////////////////////////////////////////////////// // Random number generator // Adapted from http://codebase64.org/doku.php?id=base:small_fast_16-bit_prng export asm rand16 +asmPlasmRet 0 lda seed beq .lowZero ; $0000 and $8000 are special values to test for ; Do a normal shift asl seed lda seed+1 rol bcc .noEor .doEor: ; high byte is in A eor #>magic sta seed+1 tay ; for asmPlasm, return hi byte in Y, lo byte in A lda seed eor #= 'a' and c <= 'z' return c - $20 fin return c end /////////////////////////////////////////////////////////////////////////////////////////////////// // Compare two strings for equality, ignoring case. export def streqi(a, b) word limit, leneq leneq = ^a == ^b limit = a + min(^a, ^b) a++; b++ while a <= limit if charToUpper(^a) <> charToUpper(^b); return FALSE; fin a++; b++ loop return leneq end /////////////////////////////////////////////////////////////////////////////////////////////////// // Copy part of a string export def strncpy(dst, src, maxlen) byte i, l l = ^src if l > maxlen; l = maxlen; fin ^dst = l for i = 1 to l dst->[i] = src->[i] next return l end /////////////////////////////////////////////////////////////////////////////////////////////////// // Read a string from the keyboard using the font manager, and intern it to the heap. export def getStringResponse() word p rawGetStr() rawDisplayStr("\n") // so Outlaw user doesn't have to remember to make a newline for p = ($1FF + ^$2FF) downto $200 p->1 = (^p & $7F) next ^$200 = ^$2FF return mmgr(HEAP_INTERN, $200) end /////////////////////////////////////////////////////////////////////////////////////////////////// // Setter functions for library use export def setPlural(flg) isPlural = flg end /////////////////////////////////////////////////////////////////////////////////////////////////// // Convert signed decimal to string in decimalBuf (@decimalBuf returned) def convertDec(n) word n0 word p p = @decimalBuf + 1 if n < 0; ^p = '-'; p=p+1; n = -n; fin n0 = n if n0 > 9999; ^p = '0' + n/10000; p=p+1; n = n%10000; fin if n0 > 999; ^p = '0' + n/1000; p=p+1; n = n%1000; fin if n0 > 99; ^p = '0' + n/100; p=p+1; n = n%100; fin if n0 > 9; ^p = '0' + n/10; p=p+1; n = n%10; fin ^p = '0' + n; p=p+1 decimalBuf[0] = p - @decimalBuf - 1 // record final length of string return @decimalBuf end /////////////////////////////////////////////////////////////////////////////////////////////////// // Convert byte to 3-char string in decimalBuf, suitable for font engine, e.g. ^T065 // (@fontPosBuf returned so as to not disturb decimalBuf) def convert3Dec(n) fontPosBuf[0] = 3 fontPosBuf[1] = '0' + (n / 100); n = n%100 fontPosBuf[2] = '0' + (n / 10); n = n%10 fontPosBuf[3] = '0' + n return @fontPosBuf end /////////////////////////////////////////////////////////////////////////////////////////////////// // Print a formatted string a'la C printf, with up to three parameters. export def printf3(str, arg1, arg2, arg3)#0 word pos word curArg word p if !str printChar('!') // Safety valve for NULL string pointer return fin pos = 0 curArg = @arg1 while TRUE pos = partialPrintf(str, pos) if pos < 0 break fin p = str + pos + 2 when ^p is 'd' // %d = decimal puts(convertDec(*curArg)); break is 's' // %s = string puts(*curArg); break is 'D' // %D = 3-char decimal suitable for font engine ctrl codes puts(convert3Dec(*curArg)); break is 'c' // %c = character printChar(*curArg); break is 'x' // %x = hex with '$' printHex(*curArg); break is '%' // %% = perfect printChar('%'); break otherwise printHex(^p); fatal("Unknown % code") wend curArg = curArg + 2 pos = pos + 2 loop end export def printf1(str, arg1)#0; printf3(str, arg1, 0, 0); end export def printf2(str, arg1, arg2)#0; printf3(str, arg1, arg2, 0); end // Like printf, but displays text using font engine export def displayf3(str, arg1, arg2, arg3)#0 buildString(@addToString) printf3(str, arg1, arg2, arg3) displayStr(finishString(isPlural)) end export def displayf1(str, arg1)#0; displayf3(str, arg1, 0, 0); end export def displayf2(str, arg1, arg2)#0; displayf3(str, arg1, arg2, 0); end // Like printf, but buffers string in $200 export def sprintf3(str, arg1, arg2, arg3) buildString(@addToString) printf3(str, arg1, arg2, arg3) return finishString(isPlural) end export def sprintf1(str, arg1); return sprintf3(str, arg1, 0, 0); end export def sprintf2(str, arg1, arg2); return sprintf3(str, arg1, arg2, 0); end // Like printf, but displays text using font engine export def rawDisplayf1(str, arg1)#0; rawDisplayStr(sprintf3(str, arg1, 0, 0)); end export def rawDisplayf2(str, arg1, arg2)#0; rawDisplayStr(sprintf3(str, arg1, arg2, 0)); end export def rawDisplayf3(str, arg1, arg2, arg3)#0; rawDisplayStr(sprintf3(str, arg1, arg2, arg3)); end /////////////////////////////////////////////////////////////////////////////////////////////////// export def parseDec(str) word n word pend word p byte neg neg = FALSE n = 0 p = str + 1 pend = p + ^str while p < pend if p == (str+1) and ^p == '-' neg = TRUE elsif ^p >= '0' and ^p <= '9' n = (n*10) + (^p - '0') else break fin p = p+1 loop if neg; return -n; fin return n end /////////////////////////////////////////////////////////////////////////////////////////////////// export def parseDecWithDefault(str, default) if ^str == 0 return default fin return parseDec(str) end /////////////////////////////////////////////////////////////////////////////////////////////////// // Get a keystroke and convert it to upper case export def getUpperKey() byte key while ^kbd < 128 *seed = *seed + 1 animPauseCt = animPauseCt - 1 if animPauseCt < 0 if anyAnims nextAnimFrame() fin animPauseCt = ANIM_PAUSE_MAX fin loop key = ^kbd ^kbdStrobe return charToUpper(key & $7F) end /////////////////////////////////////////////////////////////////////////////////////////////////// // Read a single char from the keyboard, and intern it (as a string) to the heap. export def getCharResponse() if needShowParty; showParty(); fin ^$200 = 1 ^$201 = getUpperKey() return mmgr(HEAP_INTERN, $200) end /////////////////////////////////////////////////////////////////////////////////////////////////// // Pause for a specified count period, advancing the animation periodically. export def pause(count) while count >= 0 animPauseCt = animPauseCt - 1 if animPauseCt < 0 if anyAnims nextAnimFrame() fin animPauseCt = ANIM_PAUSE_MAX fin count-- loop end /////////////////////////////////////////////////////////////////////////////////////////////////// export def encodeDice(nDice, dieSize, add) // ndice=0..15, dieSize=0..15, add=0..255 return (nDice << 12) | (dieSize << 8) | add end /////////////////////////////////////////////////////////////////////////////////////////////////// export def rollDice(encoded) byte i, nDice, dieSize, add, result nDice = encoded >> 12 dieSize = (encoded >> 8) & $F add = encoded & $F result = add for i = 1 to nDice add = (rand16() % dieSize) + 1 result = result + add next return result end /////////////////////////////////////////////////////////////////////////////////////////////////// // Look up the partition for a resource. // sectioNum: 1=map2d, 2=map3d, 3=portrait def lookupResourcePart(sectionNum, resourceNum) word ptr byte n // Skip to the requested section ptr = pResourceIndex while sectionNum > 1 ptr = ptr + readAuxByte(ptr) + 1 sectionNum-- loop // And grab the number from that section's table n = readAuxByte(ptr) if resourceNum > n; fatal("lkupFail1"); fin n = readAuxByte(ptr + resourceNum) // 255 is special code for map that is replicated on every data disk if n == 255 if curMapPartition > 0; return curMapPartition; fin return 2 fin if n < 1 or n > 20; fatal("lkupFail2"); fin return n end /////////////////////////////////////////////////////////////////////////////////////////////////// // Set the sky color (relevant to 3D display only) export def setSky(num)#0 // hack for end-game screen if num == 99 finalWin() fin skyNum = num setColor(0, skyNum) needRender = TRUE end /////////////////////////////////////////////////////////////////////////////////////////////////// // Set the ground color (relevant to 3D display only) export def setGround(num)#0 groundNum = num setColor(1, groundNum) needRender = TRUE end /////////////////////////////////////////////////////////////////////////////////////////////////// // Load the Frame Image, and lock it. export def loadFrameImg(img) // Skip redundant reload if frameLoaded == img; return; fin // Free prev img and/or portrait (if any) clearPortrait() // Make room in aux mem by throwing out textures if renderLoaded flipToPage1() texControl(0) fin // Load the image data into aux mem if img auxMmgr(START_LOAD, 1) // partition 1 is where full screen images live if img == 1 auxMmgr(SET_MEM_TARGET, $4000) // well above where expander loads at startup fin curFullscreenImg = auxMmgr(QUEUE_LOAD, img<<8 | RES_TYPE_SCREEN) auxMmgr(FINISH_LOAD, 0) anyAnims = TRUE // for now; might get cleared if we discover otherwise on advance animDirCt = 1 animPauseCt = ANIM_PAUSE_MAX // And show the first frame of the screen image showAnimFrame() else curFullscreenImg = NULL anyAnims = FALSE fin frameLoaded = img // Do not render over the image needRender = FALSE end /////////////////////////////////////////////////////////////////////////////////////////////////// // Window for the map name bar export def setWindow1() setWindow(8, 17, 35, 119) // Top, Bottom, Left, Right mapNameHash = 0 // on the assumption that it's being set because somebody's going to print there end /////////////////////////////////////////////////////////////////////////////////////////////////// // Window for the large upper right bar export def setWindow2() displayChar('N'-$40) // Set normal mode - clear all special modes (like underline, etc.) setWindow(24, 132, 154, 267) // Top, Bottom, Left, Right end /////////////////////////////////////////////////////////////////////////////////////////////////// // Window for the mid-size lower right bar export def setWindow3() setWindow(144, 180, 154, 267) // Top, Bottom, Left, Right end /////////////////////////////////////////////////////////////////////////////////////////////////// // Window for the map area (used for clearing it) export def setMapWindow() if frameLoaded == 3 // don't check mapIs3D, since we might be in an engine setWindow(24, 153, 14, 140) // Top, Bottom, Left, Right else setWindow(24, 169, 14, 140) // Top, Bottom, Left, Right fin end /////////////////////////////////////////////////////////////////////////////////////////////////// def hline(addr, startByte, midByte, midSize, endByte) ^addr = startByte memset(addr+1, midByte, midSize) ^(addr+midSize+1) = endByte end /////////////////////////////////////////////////////////////////////////////////////////////////// // Window that covers the entire inner area (destroys frame image, so be sure to loadMainFrame // afterwards) export def setBigWindow() // Draw border (if not already drawn) if frameLoaded hline(getScreenLine(BIGWIN_TOP-4)+1, 0, 0, 36, 0) hline(getScreenLine(BIGWIN_TOP-3)+1, $F8, $FF, 36, $8F) hline(getScreenLine(BIGWIN_TOP-2)+1, $FC, $FF, 36, $9F) hline(getScreenLine(BIGWIN_TOP-1)+1, $8C, 0, 36, $98) vline(getScreenLine(BIGWIN_TOP)+1, $8C, 174) vline(getScreenLine(BIGWIN_TOP)+38, $98, 174) hline(getScreenLine(BIGWIN_BOTTOM-1)+1, $8C, 0, 36, $98) hline(getScreenLine(BIGWIN_BOTTOM)+1, $FC, $FF, 36, $9F) hline(getScreenLine(BIGWIN_BOTTOM+1)+1, $F8, $FF, 36, $8F) hline(getScreenLine(BIGWIN_BOTTOM+2)+1, 0, 0, 36, 0) frameLoaded = 0 // since we just destroyed it fin setWindow(BIGWIN_TOP, BIGWIN_BOTTOM, BIGWIN_LEFT, BIGWIN_RIGHT) end /////////////////////////////////////////////////////////////////////////////////////////////////// export def rightJustifyStr(str, rightX) word space space = rightX - calcWidth(str) if (space > 0) rawDisplayStr("^T") // do not use printf variants, since it might overwrite str rawDisplayStr(convert3Dec(space)) fin rawDisplayStr(str) end /////////////////////////////////////////////////////////////////////////////////////////////////// export def rightJustifyNum(num, rightX) rightJustifyStr(convertDec(num), rightX) end /////////////////////////////////////////////////////////////////////////////////////////////////// // Display the party data on the screen export def showParty() word p saveCursor() setWindow3() clearWindow() // Display header rawDisplayf1("^LName^T%DHealth^L\n", CHAR_WND_HEALTH_X) // begin underline mode // Display each character's name and health p = global=>p_players while p if p <> global=>p_players; displayChar('\n'); fin displayStr(p=>s_name) rawDisplayf3("^T%D%d/%d", CHAR_WND_HEALTH_X, p=>w_health, p=>w_maxHealth) p = p=>p_nextObj loop // Finish up if mapIs3D and texturesLoaded copyWindow() fin setWindow2() restoreCursor() needShowParty = FALSE end /////////////////////////////////////////////////////////////////////////////////////////////////// def getArgCount(pFunc) word pBytecode // skip over JMP to plasma interp, get addr in aux mem pBytecode = pFunc=>3 // Check if the function starts with ENTER op if readAuxByte(pBytecode) == $58 return readAuxByte(pBytecode+2) fin // Zero-arg functions sometimes omit ENTER altogether. return 0 end /////////////////////////////////////////////////////////////////////////////////////////////////// // Send an event to the scripts on the current map square export def scriptEvent(event, param) byte i, argCount word script if !nMapScripts; return; fin setWindow2() for i = 0 to nMapScripts-1 script = mapScripts[i] argCount = getArgCount(script) if argCount == 0 and event == @S_ENTER // zero-param scripts are assumed to be strictly 'enter' handlers script() elsif argCount == 1 script(event) elsif argCount == 2 script(event, param) fin next clearPortrait() if needShowParty; showParty(); fin if global=>p_players=>w_health == 0; playerDeath(); fin end /////////////////////////////////////////////////////////////////////////////////////////////////// // Check for script(s) attached to the given location, and establish the array of map scripts. // Does not call any of them -- that's the job of scriptEvent(). def scanScripts(x, y) word p word script word pNext nMapScripts = 0 x = x - triggerOriginX y = y - triggerOriginY p = triggerTbl while p if ^p == $FF break fin pNext = p + p->1 if ^p == y p = p + 2 while p < pNext if x == ^p if nMapScripts == MAX_MAP_SCRIPTS; fatal("maxScpts"); fin mapScripts[nMapScripts] = p=>1 nMapScripts++ fin p = p + 3 loop fin p = pNext loop end /////////////////////////////////////////////////////////////////////////////////////////////////// export def loadMainFrameImg() loadFrameImg(mapIs3D+2) if curFullscreenImg auxMmgr(FREE_MEMORY, curFullscreenImg) curFullscreenImg = NULL fin end /////////////////////////////////////////////////////////////////////////////////////////////////// // Load code and data, set up everything to display a 2D or 3D map def initMap(x, y, dir) word pMap // Reset memory (our module will stay since memory manager locked it upon load) mmgr(RESET_MEMORY, 0) // Load the frame image, then raycaster or tile engine loadMainFrameImg() mmgr(START_LOAD, 1) mmgr(SET_MEM_TARGET, displayEngine) if mapIs3D mmgr(QUEUE_LOAD, CODE_RENDER<<8 | RES_TYPE_CODE) else mmgr(QUEUE_LOAD, CODE_TILE_ENGINE<<8 | RES_TYPE_CODE) fin if global->b_godmode pGodModule = mmgr(QUEUE_LOAD, MOD_GODMODE<<8 | RES_TYPE_MODULE) fin mmgr(FINISH_LOAD, 0) renderLoaded = TRUE // Grab the function table for the godMode module (if enabled) if global->b_godmode; pGodModule = pGodModule(); fin // Set up the command table initCmds() // Load the map curMapPartition = lookupResourcePart(mapIs3D+1, mapNum) mmgr(START_LOAD, curMapPartition) pMap = mmgr(QUEUE_LOAD, mapNum<<8 | (RES_TYPE_2D_MAP+mapIs3D)) mmgr(FINISH_LOAD, 0) // Clear all the windows to the background color (hi-bit set) setWindow1() clearWindow() setWindow2() clearWindow() //setWindow3() // not needed, because showParty() does it for us //clearWindow() // Clear the list of encounter zones from any previous maps if allowZoneInit global=>p_encounterZones = NULL fin // Start up the display engine with map data and starting position. This will also load and // init the script module, if any, which will end up calling us back at the setScriptInfo triggerTbl = NULL setWindow2() initDisplay(curMapPartition, mapNum, pMap, x, y, dir) texturesLoaded = TRUE needRender = FALSE textDrawn = FALSE curEngine = NULL curPortrait = NULL curPortraitNum = 0 curFullscreenImg = NULL if global->b_curAvatar <> 0 and !mapIs3D setAvatar(global->b_curAvatar) doRender() fin // Assume there might be animations until we learn otherwise anyAnims = TRUE // for now; might get cleared if we discover otherwise on advance animDirCt = 1 animPauseCt = ANIM_PAUSE_MAX // Populate script handlers for the current square, so that leave handlers will trigger right. scanScripts(x, y) // Display the party characters showParty() end /////////////////////////////////////////////////////////////////////////////////////////////////// export def scriptSetAvatar(avatarTileNum) global->b_curAvatar = avatarTileNum if renderLoaded; setAvatar(avatarTileNum); fin end /////////////////////////////////////////////////////////////////////////////////////////////////// export def unloadTextures() if renderLoaded and texturesLoaded flipToPage1() texControl(0) texturesLoaded = FALSE fin end /////////////////////////////////////////////////////////////////////////////////////////////////// // Display a portrait drawing (typically called from scripts) export def clearPortrait() if curPortrait auxMmgr(FREE_MEMORY, curPortrait) curPortrait = NULL curPortraitNum = 0 fin if curFullscreenImg auxMmgr(FREE_MEMORY, curFullscreenImg) curFullscreenImg = NULL loadMainFrameImg() fin needRender = TRUE end /////////////////////////////////////////////////////////////////////////////////////////////////// // Perform rendering, copy if necessary, clear appropriate flags def doRender() if curPortrait; clearPortrait(); fin if !texturesLoaded if mapIs3D flipToPage1() texControl(1) fin texturesLoaded = TRUE fin if textDrawn and mapIs3D and texturesLoaded; copyWindow(); fin render() needRender = FALSE end /////////////////////////////////////////////////////////////////////////////////////////////////// // Advance one step forward (works for either 3D or 2D maps) def moveForward() byte val word x, y val = advance() // If not blocked, render at the new position. if val == 0 beep() else if !mapIs3D doRender() else needRender = TRUE fin fin // If we're on a new map tile, clear text from script(s) on the old tile, and run leave handlers. if val >= 2 if textDrawn clearWindow() if mapIs3D and texturesLoaded; copyWindow(); fin textDrawn = FALSE fin scriptEvent(@S_LEAVE, NULL) nMapScripts = 0 fin // If there are script(s) on the new tile, run them. if val == 3 getPos(@x, @y) scanScripts(x, y) if nMapScripts scriptEvent(@S_ENTER, NULL) elsif global=>p_encounterZones and !skipEncounterCheck checkEncounter(x, y, FALSE) fin elsif val >= 2 and global=>p_encounterZones and !skipEncounterCheck getPos(@x, @y) checkEncounter(x, y, FALSE) fin end /////////////////////////////////////////////////////////////////////////////////////////////////// // Adjust player's direction plus or minus n increments def adjustDir(n) setDir((getDir() + n) & 15) end /////////////////////////////////////////////////////////////////////////////////////////////////// // Move backward one step (3D mode). Also actually works in 2D mode. def moveBackward() adjustDir(8) moveForward() adjustDir(8) end /////////////////////////////////////////////////////////////////////////////////////////////////// // Move backward two steps (3D mode), or one step (2D mode). This is often used when exiting a // building or fleeing combat, so we don't want to generate any random encounters. export def moveWayBackward() adjustDir(8) skipEncounterCheck = TRUE moveForward() if mapIs3D moveForward() fin skipEncounterCheck = FALSE adjustDir(8) end /////////////////////////////////////////////////////////////////////////////////////////////////// // Turn left (3D mode) def rotateLeft() adjustDir(-1) needRender = TRUE end /////////////////////////////////////////////////////////////////////////////////////////////////// // Rotate to the right (3D mode) def rotateRight() adjustDir(1) needRender = TRUE end /////////////////////////////////////////////////////////////////////////////////////////////////// // Sidestep to the right (3D mode) def strafeRight() adjustDir(4) moveForward() adjustDir(-4) end /////////////////////////////////////////////////////////////////////////////////////////////////// // Sidestep to the left (3D mode) def strafeLeft() adjustDir(-4) moveForward() adjustDir(4) end /////////////////////////////////////////////////////////////////////////////////////////////////// def moveNorth() word x, y getPos(@x, @y) if y > 4 setDir(0) moveForward() else beep() fin end def moveEast() word x, y getPos(@x, @y) if x < totalMapWidth-5 setDir(4) moveForward() else beep() fin end def moveSouth() word x, y getPos(@x, @y) if y < totalMapHeight-5 setDir(8) moveForward() else beep() fin end def moveWest() word x, y getPos(@x, @y) if x > 4 setDir(12) moveForward() else beep() fin end /////////////////////////////////////////////////////////////////////////////////////////////////// // Switch to a new map (2D or 3D) and establish position on it export def setMap(is3D, num, x, y, dir) if is3D == mapIs3D and num == mapNum setPos(x, y) setDir(dir) needRender = TRUE else flipToPage1() showMapName("Traveling...") setMapWindow(); clearWindow() setWindow2(); clearWindow() mapIs3D = is3D mapNum = num allowZoneInit = TRUE initMap(x, y, dir) allowZoneInit = FALSE fin // Don't send enter event, because we often land on an "Exit to wilderness?" script //NO:scriptEvent(S_ENTER, NULL) end /////////////////////////////////////////////////////////////////////////////////////////////////// export def queue_setMap(is3D, num, x, y, dir)#0 q_mapIs3D = is3D q_mapNum = num q_x = x q_y = y q_dir = dir end /////////////////////////////////////////////////////////////////////////////////////////////////// export def queue_teleport(x, y, dir)#0 queue_setMap(mapIs3D, mapNum, x, y, dir) end /////////////////////////////////////////////////////////////////////////////////////////////////// // Get a key and dispatch it to a command. Then do it again, forever. def kbdLoop() word key, func byte xreg, tmp xreg = getXReg() while TRUE // If the asm routines all work correctly, by the time we get to the top of this loop // the X register should always have the same value. tmp = getXReg() if tmp <> xreg printHex(xreg<<8 | tmp) fatal("xRegChg") fin key = getUpperKey() if key >= 0 and key < $60 func = cmdTbl[key] if func; func(); fin fin if q_mapNum setMap(q_mapIs3D, q_mapNum, q_x, q_y, q_dir) q_mapNum = 0 fin if needRender doRender() fin loop end /////////////////////////////////////////////////////////////////////////////////////////////////// def hashString(str) return hashBuffer(str+1, ^str) end /////////////////////////////////////////////////////////////////////////////////////////////////// export def showMapName(mapName) word newNameHash newNameHash = hashString(mapName) if newNameHash <> mapNameHash setWindow1() clearWindow() displayChar('Y'-$40) // center mode displayStr(mapName) displayChar('N'-$40) // normal mode if mapIs3D and texturesLoaded; copyWindow(); fin mapNameHash = newNameHash fin end /////////////////////////////////////////////////////////////////////////////////////////////////// // Set initial info for the scripts on this map: the name of the map, its trigger table, and the // maximum extent (width, height). This is called by the init function for the scripts. export def setScriptInfo(mapName, trigTbl, wdt, hgt)#0 // Grab the trigger table origins (used so the table can be more compact) triggerOriginX = trigTbl=>0 triggerOriginY = trigTbl=>2 // Record the trigger table pointer triggerTbl = trigTbl + 4 // Record the maximum width and height totalMapWidth = wdt totalMapHeight = hgt // Display map name global=>s_mapName = mmgr(HEAP_INTERN, mapName) showMapName(mapName) // Get ready for new encounter zones if allowZoneInit global=>p_encounterZones = NULL fin // Back to the main text window. setWindow2() end /////////////////////////////////////////////////////////////////////////////////////////////////// // Called by scripts to display a string. We set the flag noting that something has been // displayed, then use an assembly routine to do the work. // Also, clear the keyboard strobe, so the player has time to read the text. export def scriptDisplayStr(str)#0 if pIntimate pIntimate=>intimate_displayStr(str) else textDrawn = TRUE flipToPage1() displayStr(str) fin ^kbdStrobe // No: tossString() // Doesn't work here, because we need to toss strings in the *parent's* frame end export def scriptDisplayStrNL(str)#0 scriptDisplayStr(str) displayStr("\n") end /////////////////////////////////////////////////////////////////////////////////////////////////// // Called by scripts to swap a map tile. We set a flag noting we need to re-render, then use an // assembly routine to do the work. export def scriptSwapTile(fromX, fromY, toX, toY) needRender = TRUE swapTile(fromX, fromY, toX, toY) end /////////////////////////////////////////////////////////////////////////////////////////////////// // Get a key, and don't return until it's Y or N (or lower-case of those). Returns 1 for Y. export def getYN() byte key while TRUE key = getUpperKey() if key == 'Y' return 1 elsif key == 'N' clearWindow() if textDrawn and mapIs3D; clearWindow(); fin textDrawn = FALSE return 0 fin beep() loop end /////////////////////////////////////////////////////////////////////////////////////////////////// // Show the current animation frame def showAnimFrame() if curPortrait // Blit portrait to the appropriate area on the screen if frameLoaded == 3 // 3D-mode frame? Note: don't check mapIs3D, because we might be in an engine blit(curPortrait + 2, getScreenLine(24)+2, 128, 18) // start at 3rd text line else blit(curPortrait + 2, getScreenLine(32)+2, 128, 18) // start at 4th text line fin needRender = FALSE // suppress display of map for this frame elsif curFullscreenImg blit(curFullscreenImg + 2, getScreenLine(0), 192, 40) // the +2 is to skip anim hdr offset needRender = FALSE // suppress display of map for this frame elsif mapIs3D if textDrawn and mapIs3D and texturesLoaded; copyWindow(); fin render() fin end /////////////////////////////////////////////////////////////////////////////////////////////////// // Advance to next frame of current animation, if any def nextAnimFrame() word flags if !anyAnims; return; fin // Choose a new direction based on the flags. Do this the first time, and once every 3-7 frames. animDirCt = animDirCt - 1 if animDirCt <= 0 animDirCt = (rand16() % 5) + 3 fin // Advance animations. // First part is whether to switch directions on fwd/back anims. // Second part is how many frames to advance random anims. flags = auxMmgr(ADVANCE_ANIMS, ((animDirCt==1) & 1) | (((rand16() % 10)+1)<<8)) if (flags >> 8) // An animation was changed -- display it showAnimFrame() elsif (flags & $FF) == 0 // No animations in memory; turn off future checking anyAnims = FALSE fin // Reset the animation pause animPauseCt = ANIM_PAUSE_MAX end /////////////////////////////////////////////////////////////////////////////////////////////////// // Display a portrait drawing (typically called from scripts) export def setPortrait(portraitNum) word srcData byte part, cx, cy clearPortrait() // We're going to switch windows. Save the cursor pos in the text window. saveCursor() // Make room by unloading the textures (only if renderer is loaded) unloadTextures() // Now clear out the map area setMapWindow() clearWindow() // Restore the cursor position setWindow2() restoreCursor() // Load the portrait image and display it part = lookupResourcePart(3, portraitNum) if part > 1; part = curMapPartition; fin // Look on disk 1 or current disk only mmgr(START_LOAD, part) curPortrait = auxMmgr(QUEUE_LOAD, portraitNum<<8 | RES_TYPE_PORTRAIT) curPortraitNum = portraitNum mmgr(FINISH_LOAD, 0) anyAnims = TRUE // for now; might get cleared if we discover otherwise on advance animDirCt = 1 animPauseCt = ANIM_PAUSE_MAX // And show the first frame showAnimFrame() // Clear the keyboard strobe in case the player was moving at high speed ^kbdStrobe // Do not render over the portrait needRender = FALSE end /////////////////////////////////////////////////////////////////////////////////////////////////// export def countList(p) byte n n = 0 while p n++ p = p=>p_nextObj loop return n end /////////////////////////////////////////////////////////////////////////////////////////////////// export def countListFiltered(p, offset, filterFunc) byte n n = 0 while p if filterFunc(p) n++ fin p = *(p + offset) loop return n end /////////////////////////////////////////////////////////////////////////////////////////////////// // Find the end of a null-terminated array export def countArray(arr) byte count for count = 0 to 127 if !*arr; return count; fin arr = arr + 2 next end /////////////////////////////////////////////////////////////////////////////////////////////////// export def randomFromListFiltered(p, offset, filterFunc) byte n n = rand16() % countListFiltered(p, offset, filterFunc) while p if filterFunc(p) if n == 0; return p; fin n++ fin p = *(p + offset) loop return NULL end /////////////////////////////////////////////////////////////////////////////////////////////////// // Call like this: addToList(@player=>p_items, itemToAdd) export def addToList(addTo, p)#0 // Get to the end of the list while *addTo addTo = (*addTo) + p_nextObj loop p=>p_nextObj = *addTo *addTo = p end /////////////////////////////////////////////////////////////////////////////////////////////////// // Call like this: removeFromList(@player=>items, itemToRemove) export def removeFromList(pList, toRemove) word p p = *pList while p and p <> toRemove pList = p + p_nextObj p = *pList loop if p *pList = p=>p_nextObj p=>p_nextObj = NULL else fatal("InvalUnlink") fin end /////////////////////////////////////////////////////////////////////////////////////////////////// def saveMapPos() global->b_mapIs3D = mapIs3D global->b_mapNum = mapNum getPos(@global=>w_mapX, @global=>w_mapY) global->b_mapDir = getDir() end /////////////////////////////////////////////////////////////////////////////////////////////////// def restoreMapPos() mapIs3D = global->b_mapIs3D mapNum = global->b_mapNum initMap(global=>w_mapX, global=>w_mapY, global->b_mapDir) end /////////////////////////////////////////////////////////////////////////////////////////////////// def loadEngine(moduleNum) if curEngine; fatal("dblEng"); fin clearPortrait() unloadTextures() flipToPage1() mmgr(START_LOAD, 1) // code is in partition 1 curEngine = mmgr(QUEUE_LOAD, moduleNum<<8 | RES_TYPE_MODULE) // For combat module, pre-load some global funcs if moduleNum == MOD_COMBAT mmgr(QUEUE_LOAD, GS_COMBAT_INTRO<<8 | RES_TYPE_MODULE) mmgr(QUEUE_LOAD, GS_COMBAT_PROMPT<<8 | RES_TYPE_MODULE) mmgr(QUEUE_LOAD, GS_ENEMY_INTRO<<8 | RES_TYPE_MODULE) fin mmgr(FINISH_LOAD, 0) return curEngine() // return function table end /////////////////////////////////////////////////////////////////////////////////////////////////// def returnFromEngine(render) if curEngine mmgr(FREE_MEMORY, curEngine) curEngine = NULL loadMainFrameImg() clearPortrait() if renderLoaded; texControl(1); fin mapNameHash = 0; showMapName(global=>s_mapName) setWindow2(); clearWindow() if render; doRender(); fin showParty() setWindow2() // in case we're mid-script fin end /////////////////////////////////////////////////////////////////////////////////////////////////// export def callGlobalFunc(moduleNum, arg1, arg2, arg3) word pModule, pFunc, ret // First load the module flipToPage1() mmgr(START_LOAD, 1) // code is in partition 1 pModule = mmgr(QUEUE_LOAD, moduleNum<<8 | RES_TYPE_MODULE) mmgr(FINISH_LOAD, 0) // Call the function, passing it the number of args it expects pFunc = pModule() when getArgCount(pFunc) is 0; ret = pFunc(); break is 1; ret = pFunc(arg1); break is 2; ret = pFunc(arg1, arg2); break is 3; ret = pFunc(arg1, arg2, arg3); break otherwise fatal("maxGlobParams") wend // Unload the module and we're done. mmgr(FREE_MEMORY, pModule) return ret end /////////////////////////////////////////////////////////////////////////////////////////////////// // Load the Party engine and show data for the given player def showPlayerSheet(num) word pItemToUse pItemToUse = loadEngine(MOD_PARTY)=>party_showPlayerSheet(num) returnFromEngine(TRUE) // General 'use' handled here in case it triggers graphical effects if pItemToUse scriptEvent(@S_USE, pItemToUse=>s_name) fin end def showPlayer1() showPlayerSheet(0) end def showPlayer2() showPlayerSheet(1) end def showPlayer3() showPlayerSheet(2) end /////////////////////////////////////////////////////////////////////////////////////////////////// export def addEncounterZone(code, x, y, dist, chance)#0 word p if allowZoneInit p = mmgr(HEAP_ALLOC, TYPE_ENCOUNTER_ZONE) p=>s_name = mmgr(HEAP_INTERN, code) p=>w_encX = x p=>w_encY = y p=>w_encMaxDist = dist p=>w_encChance = chance addToList(@global=>p_encounterZones, p) fin end /////////////////////////////////////////////////////////////////////////////////////////////////// export def clearEncounterZones() global=>p_encounterZones = NULL end /////////////////////////////////////////////////////////////////////////////////////////////////// // Called by user-defined map scripts to initiate a combat encounter. export def scriptCombat(mapCode) return doCombat(mapCode, TRUE) end /////////////////////////////////////////////////////////////////////////////////////////////////// def playerDeath() callGlobalFunc(GS_DEATH, 0, 0, 0) startGame(FALSE) // don't ask, just load end /////////////////////////////////////////////////////////////////////////////////////////////////// def doCombat(mapCode, backUpOnFlee) word result // Handled in a separate module. Clear enemies out of the heap when finished. result = loadEngine(MOD_COMBAT)=>combat_zoneEncounter(mapCode) global=>p_enemyGroups = NULL mmgr(HEAP_COLLECT, 0) if (result == -99) playerDeath() return fin returnFromEngine(TRUE) // If the party fled the combat instead of winning, back up to previous square. if !result and backUpOnFlee moveWayBackward() fin return result end /////////////////////////////////////////////////////////////////////////////////////////////////// // Check for a random encounter at this position export def checkEncounter(x, y, force) word p word p_bestZone, bestDist word d // Find the zone that's closest, but not too far. bestDist = INT_MAX p_bestZone = NULL p = global=>p_encounterZones while p d = min(abs(x - p=>w_encX), abs(y - p=>w_encY)) if d < bestDist and (p=>w_encMaxDist == 0 or d < p=>w_encMaxDist)) p_bestZone = p bestDist = d fin p = p=>p_nextObj loop // Roll for an encounter in the zone. d = rand16() % 1000 if p_bestZone and (d < p_bestZone=>w_encChance or force) // Encounter! doCombat(p_bestZone=>s_name, !force) fin end /////////////////////////////////////////////////////////////////////////////////////////////////// def saveGame saveMapPos() loadEngine(MOD_DISKOPS)=>diskops_saveGame() returnFromEngine(TRUE) end /////////////////////////////////////////////////////////////////////////////////////////////////// def loadGame loadEngine(MOD_DISKOPS)=>diskops_loadGame() restoreMapPos() end /////////////////////////////////////////////////////////////////////////////////////////////////// def help flipToPage1() setMapWindow(); clearWindow() loadEngine(GS_HELP)() returnFromEngine(TRUE) end /////////////////////////////////////////////////////////////////////////////////////////////////// def enableGodMode() while ^kbd < 128; loop if ^kbd == $8F // ctrl-O ^kbdStrobe while ^kbd < 128; loop if ^kbd == $84 // ctrl-D ^kbdStrobe global->b_godmode = 1 beep; beep // A little audio feedback saveMapPos(); restoreMapPos() // reload everything, including god module fin fin end /////////////////////////////////////////////////////////////////////////////////////////////////// export def finalWin() flipToPage1() loadFrameImg(4) // total hack while 1 // 1 infinite loop getUpperKey() loop end /////////////////////////////////////////////////////////////////////////////////////////////////// export def setCmd(key, func) cmdTbl[key] = func end /////////////////////////////////////////////////////////////////////////////////////////////////// // Set up the command table for 3D mode def initCmds() // Clear the command table byte i for i = 0 to 95 cmdTbl[i] = 0 next // Commands common to both 2D and 3D cmdTbl['1'] = @showPlayer1 cmdTbl['2'] = @showPlayer2 cmdTbl['3'] = @showPlayer3 cmdTbl[$13] = @saveGame // ctrl-S cmdTbl[$0c] = @loadGame // ctrl-L cmdTbl['?'] = @help if global->b_godmode pGodModule=>godmode_setCheatCmds() else cmdTbl[$07] = @enableGodMode // ctrl-G fin // Commands handled differently in 3D vs 2D if mapIs3D cmdTbl['W'] = @moveForward cmdTbl['A'] = @rotateLeft cmdTbl['D'] = @rotateRight cmdTbl['S'] = @moveBackward cmdTbl['X'] = @moveBackward cmdTbl['Z'] = @strafeLeft cmdTbl['C'] = @strafeRight cmdTbl['I'] = @moveForward cmdTbl['J'] = @rotateLeft cmdTbl['L'] = @rotateRight cmdTbl['K'] = @moveBackward cmdTbl[','] = @moveBackward cmdTbl['M'] = @strafeLeft cmdTbl['.'] = @strafeRight cmdTbl[11] = @moveForward // up-arrow cmdTbl[8] = @rotateLeft // left-arrow cmdTbl[21] = @rotateRight // right-arrow cmdTbl[10] = @moveBackward // down-arrow else cmdTbl['W'] = @moveNorth cmdTbl['D'] = @moveEast cmdTbl['S'] = @moveSouth cmdTbl['X'] = @moveSouth cmdTbl['A'] = @moveWest cmdTbl['I'] = @moveNorth cmdTbl['J'] = @moveWest cmdTbl['L'] = @moveEast cmdTbl['K'] = @moveSouth cmdTbl[','] = @moveSouth cmdTbl[11] = @moveNorth // up-arrow cmdTbl[8] = @moveWest // left-arrow cmdTbl[21] = @moveEast // right-arrow cmdTbl[10] = @moveSouth // down-arrow fin end /////////////////////////////////////////////////////////////////////////////////////////////////// // Load and display the title screen. def loadTitle() word pEngine, pFont, expanderSize puts("Loading game.\n") // Allocate and permanently lock mem for the font engine and its font (up in LC ram) mmgr(START_LOAD, 1) // partition 1 is where code lives mmgr(SET_MEM_TARGET, fontEngine) mmgr(REQUEST_MEMORY, fontEngineLen) mmgr(LOCK_MEMORY, fontEngine) mmgr(SET_MEM_TARGET, fontData) mmgr(REQUEST_MEMORY, fontDataLen) mmgr(LOCK_MEMORY, fontData) // Load them into lo mem pEngine = mmgr(QUEUE_LOAD, CODE_FONT_ENGINE<<8 | RES_TYPE_CODE) pFont = mmgr(QUEUE_LOAD, 1<<8 | RES_TYPE_FONT) mmgr(FINISH_LOAD, 0) // Relocate font engine and font data to their final spots up in the language card memcpy(pEngine, fontEngine, fontEngineLen) memcpy(pFont, fontData, fontDataLen) // Load the title screen and show it. loadFrameImg(1) // title screen is fixed at #1 ^$C050 // graphics ^$C057 // hi-res ^$C054 // page 1 ^$C052 // full screen // Hack for real (not emulated) IIc: sometimes displays only lo-bit graphics // unless we do this. *HUGE* thanks to Brendan Robert for the fix! ^$C07E=0 // disable double-hi-res ^$C05F // disable double-hi-res // While we're loading, let's get the expander into aux RAM. auxMmgr(SET_MEM_TARGET, expandVec) auxMmgr(QUEUE_LOAD, CODE_EXPAND<<8 | RES_TYPE_CODE) // Also grab the resource index (put it in aux) pResourceIndex = auxMmgr(QUEUE_LOAD, CODE_RESOURCE_INDEX<<8 | RES_TYPE_CODE) auxMmgr(LOCK_MEMORY, pResourceIndex) mmgr(FINISH_LOAD, 0) // Tell the font engine where to find its font setFont(fontData) // And free up the font low mem mmgr(FREE_MEMORY, pEngine) mmgr(FREE_MEMORY, pFont) // Split the expander (relocating most of it to aux LC ram) readAuxByte($1A) // sets up aux routine expanderSize = splitExpander(expandVec) // Lock in the part of the expander that remains in low aux mem. auxMmgr(FREE_MEMORY, expandVec) auxMmgr(SET_MEM_TARGET, expandVec) auxMmgr(REQUEST_MEMORY, expanderSize) auxMmgr(LOCK_MEMORY, expandVec) end /////////////////////////////////////////////////////////////////////////////////////////////////// // Set up the small-object heap. Set loadedSize to zero on initial, or non-zero for loaded game. export def initHeap(loadedSize) byte i word typeHash if !heapLocked mmgr(SET_MEM_TARGET, HEAP_BOTTOM) mmgr(REQUEST_MEMORY, HEAP_SIZE) mmgr(LOCK_MEMORY, HEAP_BOTTOM) heapLocked = TRUE fin if loadedSize <> 0 mmgr(SET_MEM_TARGET, HEAP_BOTTOM + loadedSize) fin mmgr(HEAP_SET, HEAP_BOTTOM) i = 0 while typeTbls[i] mmgr(HEAP_ADD_TYPE, typeTbls[i]) i = i+1 loop typeHash = hashBuffer(@typeTbl_Global, @typeTbls - @typeTbl_Global) ^ HEAP_BOTTOM if loadedSize <> 0 global = HEAP_BOTTOM if global=>w_typeHash <> typeHash fatal("Incompatible saved game") fin else global = mmgr(HEAP_ALLOC, TYPE_GLOBAL) global=>w_typeHash = typeHash fin end /////////////////////////////////////////////////////////////////////////////////////////////////// // Return a random entry from an array which is terminated by a zero entry export def randomFromArray(arr) byte siz siz = 0 while *((siz << 1) + arr) siz++ loop return *(((rand16() % siz) << 1) + arr) end /////////////////////////////////////////////////////////////////////////////////////////////////// // Constructor: create a modifier given its name and value export def makeModifier(name, value) word p; p = mmgr(HEAP_ALLOC, TYPE_MODIFIER) p=>s_name = mmgr(HEAP_INTERN, name) p=>w_modValue = value return p end /////////////////////////////////////////////////////////////////////////////////////////////////// // Recalculate player's armor score based on their currently equipped armor export def calcPlayerArmor(player) word pItem player->b_armor = 0 pItem = player=>p_items while pItem if pItem->t_type == TYPE_ARMOR and pItem->b_flags & ITEM_FLAG_EQUIP player->b_armor = player->b_armor + pItem->b_armorValue fin pItem = pItem=>p_nextObj loop end /////////////////////////////////////////////////////////////////////////////////////////////////// // Add gold export def addGold(amount) if global=>w_gold + amount > GOLD_MAX amount = GOLD_MAX - global=>w_gold fin global=>w_gold = global=>w_gold + amount return amount end // Pay out gold export def payGold(amount) if amount > global=>w_gold return 0 fin global=>w_gold = global=>w_gold - amount return amount end /////////////////////////////////////////////////////////////////////////////////////////////////// export def scanForNamedObj(p_obj, name) while p_obj if streqi(p_obj=>s_name, name); return p_obj; fin p_obj = p_obj=>p_nextObj loop return NULL end /////////////////////////////////////////////////////////////////////////////////////////////////// export def addUnique(pList, p_thing) if !scanForNamedObj(*pList, p_thing=>s_name) addToList(pList, p_thing) return TRUE fin return FALSE end /////////////////////////////////////////////////////////////////////////////////////////////////// export def createAndAddUnique(moduleID, creationFuncNum, pList) word p_module, funcTbl, func, p_thing // Unload textures to make room for the module (also flips to page 1 if needed) unloadTextures() // Load the module that is capable of creating the thing mmgr(START_LOAD, 1) // code is in partition 1 p_module = mmgr(QUEUE_LOAD, moduleID<<8 | RES_TYPE_MODULE) mmgr(FINISH_LOAD, 0) // Figure out which creation function to call there, and create the thing funcTbl = p_module() func = *(funcTbl + creationFuncNum) p_thing = func() // full // Avoid adding duplicate things. addUnique(pList, p_thing) // Finished with the module now. mmgr(FREE_MEMORY, p_module) return p_thing end /////////////////////////////////////////////////////////////////////////////////////////////////// export def giveItemToPlayer(p_player, itemFuncNum) createAndAddUnique(MOD_GEN_ITEMS, itemFuncNum, @p_player=>p_items) end /////////////////////////////////////////////////////////////////////////////////////////////////// export def addPlayerToParty(playerFuncNum)#0 word p if countList(global=>p_players) == MAX_PARTY displayStr("Party too large.") return fin p = createAndAddUnique(MOD_GEN_PLAYERS, playerFuncNum, @global=>p_players) p->b_playerFlags = p->b_playerFlags | PLAYER_FLAG_NPC needShowParty = TRUE end /////////////////////////////////////////////////////////////////////////////////////////////////// export def removeNamed(name, pList) word p_thing p_thing = scanForNamedObj(*pList, name) if p_thing removeFromList(pList, p_thing) else printf1("Warning: couldn't find '%s' to remove.\n", name) fin end /////////////////////////////////////////////////////////////////////////////////////////////////// export def takeItemFromPlayer(p_player, itemName) removeNamed(itemName, @p_player=>p_items) // default to first player end /////////////////////////////////////////////////////////////////////////////////////////////////// export def removePlayerFromParty(playerName) removeNamed(playerName, @global=>p_players) needShowParty = TRUE end /////////////////////////////////////////////////////////////////////////////////////////////////// export def playerHasItem(itemName) return scanForNamedObj(global=>p_players=>p_items, itemName) <> NULL end /////////////////////////////////////////////////////////////////////////////////////////////////// export def partyHasPlayer(playerName) return scanForNamedObj(global=>p_players, playerName) <> NULL end /////////////////////////////////////////////////////////////////////////////////////////////////// export def getStat(player, statName) when statName is @S_INTELLIGENCE; return player->b_intelligence is @S_STRENGTH; return player->b_strength is @S_AGILITY; return player->b_agility is @S_STAMINA; return player->b_stamina is @S_CHARISMA; return player->b_charisma is @S_SPIRIT; return player->b_spirit is @S_LUCK; return player->b_luck is @S_HEALTH; return player=>w_health is @S_MAX_HEALTH; return player=>w_maxHealth is @S_AIMING; return player->b_aiming is @S_HAND_TO_HAND; return player->b_handToHand is @S_DODGING; return player->b_dodging is @S_GOLD; return global=>w_gold otherwise puts(statName); fatal("Unknown stat") wend end /////////////////////////////////////////////////////////////////////////////////////////////////// def clampByte(val) return max(0, min(255, val)) end /////////////////////////////////////////////////////////////////////////////////////////////////// export def setStat(player, statName, val) when statName is @S_INTELLIGENCE; player->b_intelligence = clampByte(val); break is @S_STRENGTH; player->b_strength = clampByte(val); break is @S_AGILITY; player->b_agility = clampByte(val); break is @S_STAMINA; player->b_stamina = clampByte(val); break is @S_CHARISMA; player->b_charisma = clampByte(val); break is @S_SPIRIT; player->b_spirit = clampByte(val); break is @S_LUCK; player->b_luck = clampByte(val); break is @S_HEALTH; player=>w_health = max(0, min(player=>w_maxHealth, val)); needShowParty = TRUE; break is @S_MAX_HEALTH; player=>w_maxHealth = max(0, val); break is @S_AIMING; player->b_aiming = clampByte(val); break is @S_HAND_TO_HAND; player->b_handToHand = clampByte(val); break is @S_DODGING; player->b_dodging = clampByte(val); break is @S_GOLD; global=>w_gold = max(0, val); needShowParty = TRUE; break otherwise puts(statName); fatal("Unknown stat") wend end /////////////////////////////////////////////////////////////////////////////////////////////////// export def setGameFlag(flagName, val) word p_flag p_flag = scanForNamedObj(global=>p_gameFlags, flagName) if p_flag if val == 0 // setting flag to zero removes it removeFromList(@global=>p_gameFlags, p_flag) else p_flag=>w_modValue = val fin elsif val <> 0 addToList(@global=>p_gameFlags, makeModifier(flagName, val)) fin end /////////////////////////////////////////////////////////////////////////////////////////////////// export def getGameFlag(flagName) word p_flag p_flag = scanForNamedObj(global=>p_gameFlags, flagName) if p_flag return p_flag=>w_modValue else return 0 fin end /////////////////////////////////////////////////////////////////////////////////////////////////// export def setIntimateMode(enable) if enable pIntimate = loadEngine(MOD_INTIMATE) pIntimate=>intimate_setMode(enable) else pIntimate=>intimate_setMode(enable) returnFromEngine(TRUE) pIntimate = NULL fin end /////////////////////////////////////////////////////////////////////////////////////////////////// export def benchPlayer() loadEngine(MOD_PARTY)=>party_benchPlayer() returnFromEngine(TRUE) end /////////////////////////////////////////////////////////////////////////////////////////////////// export def unbenchPlayer() loadEngine(MOD_PARTY)=>party_unbenchPlayer() returnFromEngine(TRUE) end /////////////////////////////////////////////////////////////////////////////////////////////////// export def buySell(storeCode, profitRatio) word portrait portrait = curPortraitNum if storeCode loadEngine(MOD_STORE)=>store_buyFromStore(storeCode, profitRatio) else loadEngine(MOD_STORE)=>store_sellToStore(profitRatio) fin returnFromEngine(FALSE) // no render, we're mid-script if portrait; setPortrait(portrait); fin end /////////////////////////////////////////////////////////////////////////////////////////////////// def startGame(ask) word p_module // Create a new game or load an existing one mmgr(START_LOAD, 1) // code is in partition 1 p_module = mmgr(QUEUE_LOAD, MOD_DISKOPS<<8 | RES_TYPE_MODULE) mmgr(FINISH_LOAD, 0) if p_module()=>diskops_newOrLoadGame(ask) mapIs3D = q_mapIs3D mapNum = q_mapNum q_mapNum = 0 allowZoneInit = TRUE initMap(q_x, q_y, q_dir) allowZoneInit = FALSE else q_mapNum = 0 restoreMapPos() fin crout() end /////////////////////////////////////////////////////////////////////////////////////////////////// // Main code. // loadTitle() startGame(TRUE) // ask whether new or load kbdLoop() done