Logo Pending


Hold up, let me try that again.

In Leisure Suit Larry 6 – Shape Up or Slip Out, there are many ways to die, much like any other Larry game or indeed any Sierra game. Interestingly, this one has a “Try Again” button! How does that work?

Let’s work it out backwards. Starting from the script that handles the death message, we find it takes two parameters. One we can quickly determine to be the reason Larry died, the other we can tell is some sort of reference to a Script instance. After all, at one point the procedure checks if it’s an object in the first place, and in another it tries to cue the thing:

(while (not theAnswer)
  (Print
    font: gFont
    addTitle: @theTitle
    addText: @theMessage theMessageX theMessageY
    addIcon: frameIcon 0 0 2 0
    addIcon:
      (deathIcon view: theView cel: 0 loop: theLoop yourself:) 0 0
      theIconX
      theIconY
  )
  (switch
    (= theAnswer
      (Print
        addButton: 1 2 0 3 1 (+ theMessageX 1) theButtonY scriptNumber
        addButton: 0 2 0 2 1 (- ((Print dialog?) nsRight?) 75) theButtonY scriptNumber
        init:
      )
    )
    (0 ; Try Again
      (gLarryWindow back: prevBackColor)
      (gLSL6 setCursor: oldCursor)
      (gSounds eachElementDo: #pause false)
      (if rewindScript (rewindScript cue:))
      (= theAnswer -1)
    )
    (1 ; Restore
      (= local19 0)
      (gLSL6 restore: hideControls: drawControls:)
      (= theAnswer 0)
    )
  )
)

So there’s two things that can happen when you click “Try Again”. Either rewindScript is valid and it gets cue‘d before EgoDead returns -1, or it merely returns -1.

Taking a step back, we’ll look at one point where it gets called. In my case, opening the door to the swimming pool:

(instance enterPoolScr of Script
  (method (changeState newState)
    (switchto (= state newState)
      (
        (gGame handsOff:)
        (if (gMusic handle?)
          ; Pause whatever we're playing
          (gMusic pause:)
        )
        (gEgo
          setSpeed: 8
          view: 901 ; Grabbing the door
          loop: 6
          cel: 0
          setCycle: End self
        )
      )
      (
        (sfx
          number: 518
          loop: 1
          play:
        )
        (barDoor
          view: 5101
          setCycle: End self
        )
        (= ticks 10) ; Can you see the possible mistake here?
      )
      (
        (gEgo
          view: 5101 ; \o/
          loop: 2
          cel: 0)
      )
      (
        (= ticks 180)
      )
      (
        ; This is it. This is where we call the death routine.
        (EgoDead 13 self)
      )
      (
        ; "Try Again" was chosen, so we reset everything.
        (if (gMusic handle?)
          ; Unpause
          (gMusic pause: false)
        )
        (gEgo
          normalize: 900 8 1
          cel: 2
        )
        (barDoor
          view: 510
          loop: 0
          cel: 0
        )
        (gGame handsOn:)
        (self dispose:)
      )
    )
  )
)

So! You click the hand on the pool door, it animates a bit, calls EgoDead with the correct reason. That in turn recognizes reason 13, picks out the little animation and window color, fetches the right text from its Message resource (noun 2, verb 0, condition 13, sequence 1 and 2 for the joke and title respectively), and displays the window. If you click “Restore”, it keeps looping until you actually do restore something. If you click “Try Again”, it cues the caller (enterPoolScr in this case), which then sets it up like you never clicked the door in the first place.

And that’s how it works.

[ , , ] Leave a Comment

Yeah? Prove it!

Ah, those gloriously outdated questions at the start of Leisure Larry 1 and 3. You gotta love ’em. But what if you wanted to implement your own, accounting for the simple fact that

  1. we don’t use Text resources any more now that we have Messages;
  2. bitfield magic is weird and unclear.

Couple years ago, I rolled my own. Actually I did so even further back, when we still used SCI Studio, but that was such an ugly hack I’d rather not talk about that. Anyway, here’s my own implementation. I’ll interrupt the source code to explain things as we go. Ready to prove you’re a learnèd adult?

;;; Sierra Script 1.0 - (do not remove this comment)
(script #140)
(include sci.sh)
(use Main)
(use Game)
(use System)
(use Print)
(public
  AgeCheckRm 0
)

Before we go on, you’ll need the following setup in a matching Message resource:

Noun Verb Cond Seq Text
0 0 1 1 Question 1
0 0 1 2 Answer 1-A
0 0 1 3 Answer 1-B
0 0 1 4 Answer 1-C
0 0 1 5 Answer 1-D
0 0 2 1 Question 2
0 0 2 2 Answer 2-A
0 0 2 3 Answer 2-B
0 0 2 4 Answer 2-C
0 0 2 5 Answer 2-D
1 0 0 1 Challenge
1 0 0 2 Correct
1 0 0 3 Wrong
1 0 0 4 Done
1 0 0 5 Cheater

Questions are phrased like this: "3Which of these is not a pokémon?" where the first character is a digit from 0 to 4. If the digit is 0, all answers are equally correct. If it’s not, 1-4 map to answers A-D. The total number of questions should equal the TOTALQUESTIONS definition that now follows:

(define TOTALQUESTIONS    20) ; How many questions you have messages set up for.
(define REQUIREDQUESTIONS  5) ; How many must be answered.
 
; Metrics. Depending on your image, you'll want to edit these to match.
(define QUESTIONLEFT     100) ; Where and how the question is written.
(define QUESTIONTOP       32)
(define QUESTIONWIDTH    150)
(define QUESTIONFONT       4)
(define QUESTIONCOLOR      0)
(define ANSWERLEFT       100) ; Where and how the first possible answer is written.
(define ANSWERTOP         60)
(define ANSWERWIDTH      170)
(define ANSWERSPACING     25) ; How much space goes between each answer.
(define ANSWERFONT         4)
(define ANSWERCOLOR        0) ; Black
(define CORRECTCOLOR      35) ; Green
(define WRONGCOLOR        12) ; Red
 
(define BLACKSCREEN        0) ; Picture # for the black screen. Questions use scriptNumber.
(define CORRECTSOUND     111)
(define WRONGSOUND       112)
 
(local
  questionsAsked = 0 ; Total number of questions asked
  currentQuestion = 0 ; Current question's index
  correctAnswer = 0 ; Current question's correct answer
  answerGiven = 0 ; Player's guess for the current question
  correctSoFar = 0 ; Questions answered correctly so far
; score = 0 ; If you were to put a lady in a swimsuit, this'd simplify things.
  [textBuffer 200]
)

The EndThis procedure is where you’ll want to do things like set a filth level according to the score and inform the player they’ll get to play at that level.

(procedure (EndThis)
  (gRoom newRoom: 120)
)
 
; Larry 1 and 3 use bitfield magic for this. We're keeping it simple, trading
; a bit of extra overhead for readability.
(instance AskedSoFar of List)
 
(procedure (PrepareQuestion &tmp i aTop [cleanQuestion 200])
  ; Try to find a question we haven't asked yet first.
  ; This might cause an infinite loop if the amount of questions is off.
  (while TRUE
    (= currentQuestion (Random 1 TOTALQUESTIONS))
    (breakif (not (AskedSoFar contains: currentQuestion)))
  )
  (AskedSoFar add: currentQuestion)
 
  ; Grab the question we picked and extract the correct answer.
  (Message msgGET scriptNumber 0 0 currentQuestion 1 @textBuffer)
  (= correctAnswer (- (StrAt @textBuffer 0) $30)) ; '2' - '0' = 2
  ; Copy the question *without* the first character (the answer) to our temp space.
  (for ((= i 0)) (< i (StrLen @textBuffer)) ((++ i))
    (StrAt @cleanQuestion i (StrAt @textBuffer (+ i 1)))
  )
 
  ; We can now display it.
  (Display @cleanQuestion dsCOORD QUESTIONLEFT QUESTIONTOP dsCOLOR ANSWERCOLOR dsBACKGROUND -1 dsWIDTH QUESTIONWIDTH dsFONT QUESTIONFONT)
 
  ; Now we can fetch and display the possible answers.
  (for ((= i 0)) (< i 4) ((++ i))
    (DrawAnswer i ANSWERCOLOR)
  )
)
 
; Draw a given answer (0-3) at the correct position and the given color.
; One thing you might want to try to do is to add the "a. b. c. d." bits.
; I left that out as a challenge.
(procedure (DrawAnswer number color)
  (Message msgGET scriptNumber 0 0 currentQuestion (+ answerGiven 1) @textBuffer)
  (Display @textBuffer
    dsCOORD ANSWERLEFT (+ ANSWERTOP (* (- number 1) ANSWERSPACING))
    dsCOLOR color
    dsBACKGROUND -1
    dsWIDTH ANSWERWIDTH
    dsFONT ANSWERFONT
  )
)
 
; Support function to keep the main part a little bit cleaner to read.
(procedure (TimedPrint theSequence theTime)
  (Print
    font: gFont
    ticks: theTime
    addText: 1 0 0 theSequence 0 0 scriptNumber
    init:
  )
)

Now we’re getting to the proper logic of the whole thing! First, we set things up much like you might a title screen, then pass control to a room script.

(instance AgeCheckRm of Room
  (properties
    picture BLACKSCREEN
  )
 
  (method (init)
    (super init:)
    (gOldMH addToFront: self)
    (gOldKH addToFront: self)
    (gIconBar hide: disable:)
    (gUser canInput: FALSE)
    (AskedSoFar init:)
    (HideStatus)
    (self setScript: RoomScript)
  )
 
  (method (dispose)
    (AskedSoFar dispose:)
    (gIconBar hide: enable:)
    (gOldKH delete: self)
    (gOldMH delete: self)
    (super dispose: &rest)
  )
)
 
(instance RoomScript of Script
  (properties)
 
  (method (changeState newState)
    (switch (= state newState)
      (0 ; Starting up
        (Prints 1 0 0 1) ; Give the challenge.
        ; At this exact point, the Larry games would ask for your age.
        (= cycles 1)
      )
 
      (1 ; Redraw the background, grab a new question, and wait for an answer.
        ; For the first question, transition nicely. For the rest, don't.
        (if questionsAsked 
          (DrawPic scriptNumber dpOPEN_NO_TRANSITION)
          ; (aSuit setCel: score forceUpd:)
        else
          (DrawPic scriptNumber dpANIMATION_BLACKOUT)
          ; (aSuit init:)
        )
 
        (PrepareQuestion)
        ; Sit and wait for a cue.
      )
 
      (2 ; Got an answer! Is it right!?
 
        ; First, redraw the given answer in either green or red.
        (DrawAnswer
          answerGiven
          (if (or (== answerGiven correctAnswer)
                  (== correctAnswer 0))
            CORRECTCOLOR
          else
            WRONGCOLOR
          )
        )
 
        ; Now, judge 'em.
        (++ questionsAsked)
        (if (or (== answerGiven correctAnswer)
                (== correctAnswer 0))
          (++ correctSoFar)
          ; (++ score) ; for a Larry 3 lady in a swimsuit
          (gMusic2 number: CORRECTSOUND play: self)
          (TimedPrint 2) ; Correct!
        else
          (gMusic2 number: WRONGSOUND play: self)
          ; (-- score) ; for a Larry 3 lady in a swimsuit
          ; For Larry 1 style, you might want to add a "was it wrong before"
          ; flag or counter. If we *were* wrong twice, exit the game.
          (TimedPrint 3) ; Wrong!
        )
        (= seconds 1)
      )
 
      (3 ; Wait a bit and repeat
        (if (== questionsAsked REQUIREDQUESTIONS)
          (gMusic1 fade:)
          (Prints 1 0 0 4) ; Done!
          (EndThis)
        else
          (= state 0) ; This actually makes state 1 so we get the next question.
          (= cycles 1)
        )
      )
 
    )    
  )

The handleEvent method will respond to lowercase A-D, uppercase A-D, Ctrl-Alt-X, and mouse clicks on the answers. If any of these things happen, it will cue itself, causing the answer to be checked.

(method (handleEvent event &tmp i aTop aBottom)
    (if (!= state 1)
      (super handleEvent: event)
      (return)
    )
    (switch (event type?)
      (evMOUSEBUTTON
        ; Check each answer spot in turn.
        (= aTop ANSWERTOP)
        (= aBottom (+ aTop ANSWERSPACING))
        (for ((= i 0)) (< i 4) ((++ i))
          (if (InRect (- ANSWERLEFT 10) aTop (+ (+ ANSWERLEFT ANSWERWIDTH) 20) aBottom (event x?) (event y?))
            (= answerGiven (+ i 1))
            (self cue:)
            (break)
          )
        )
      )
      (evKEYBOARD
        (event claimed: TRUE) ; Prevent the usual inputs from working.
        (switch (event message?)
          (KEY_a
            (= answerGiven 1)
            (self cue:)
          )
          (KEY_b
            (= answerGiven 2)
            (self cue:)
          )
          (KEY_c
            (= answerGiven 3)
            (self cue:)
          )
          (KEY_d
            (= answerGiven 4)
            (self cue:)
          )
          (KEY_A
            (= answerGiven 1)
            (self cue:)
          )
          (KEY_B
            (= answerGiven 2)
            (self cue:)
          )
          (KEY_C
            (= answerGiven 3)
            (self cue:)
          )
          (KEY_D
            (= answerGiven 4)
            (self cue:)
          )
          (KEY_ALT_x
            (if (& (event modifiers?) 4) ; Holding Control too?
              (TimedPrint 5) ; Cheater
              ; For Larry 3 style, you might want to ask what rating you want.
              (EndThis)
            )
          )
        )
      )
    )
  )
)
 
; Bonus lady in a swimsuit because why not.
;;; (instance aSuit of Prop
;;;   (properties
;;;     y 77
;;;     x 83
;;;     view 140
;;;     loop 1
;;;   )
;;; )

There may yet be some timing issues. I’ll leave fixing those to whoever’s brave enough to use this in the first place.

[ , , ] Leave a Comment

Text, Voice… Both?

“Interesting. I wonder if this is related to the “BOTH” button that got cut in SQ4.” — @ATMcashpoint

I don’t know about the both button that ScummVM adds to some SCI games, but there’s quite literally no way it could work by just adding a third button state. There’s a fair bit of script logic that’d need to be overhauled. Here’s why that is, and here’s how I did it in The Dating Pool.

could have used the SCI Companion template game to compare against and document, but to be honest it’s a bit of a mess, as you could expect from a decompilation. The leaked system scripts are much neater to work with, even though the actual script code is basically identical.

Original Messager.sc:

(method (sayNext theMod theNoun theVerb theCase theSeq &tmp aTalker [theBuf 200] msgkey)
  ; If we were called with arguments, grab the text for that entry.
  ; If not, grab the next entry in the sequence.
  (if argc
    (= aTalker (Message msgGET theMod theNoun theVerb theCase theSeq @theBuf))
  else
    (= aTalker (Message msgNEXT @theBuf))
  )
 
  ; If we have voice enabled, allocate space and grab the entry's tuple.
  ; This block is missing in SQ4CD.
  (if (& gMessageType CD_MSG)
    (= msgkey (Memory memALLOC_CRIT 12))
    (Message msgLAST_MESSAGE msgkey)
  )
 
  (if (and  aTalker
            (or  (not lastSequence)
                 (and  lastSequence
                       (<= curSequence lastSequence)
          )
        )
      )
    ; Look up the Talker (or Narrator) by number.
    ; aTalker was a number, but now it'll be an object pointer.
    (= aTalker (self findTalker: aTalker))
 
    (if (!= aTalker -1)
      (talkerSet add: aTalker)
 
      ; Now let our Talker handle the rest.
      (if (& gMessageType CD_MSG)
        (aTalker
          modNum: theMod,
          say:    msgkey self ;<-- pass ONLY the tuple
        )
      else
        (aTalker
          modNum: theMod,
          say:    @theBuf self ;<-- pass ONLY the string
        )
      )
      ; In SQ4, we just always pass only @theBuf. There's some major
      ; voodoo involved in getting it to work.
 
      (++ curSequence)
    )
    ; Cutting a bit of irrelevant fastcast voodoo
  )
  ; Dispose of the space we allocated for the voice tuple, if needed.
  (if (& gMessageType CD_MSG)
    (Memory memFREE msgkey)
  )
)

Catdate’s Messager.sc:

; Exactly the same as in the template BUT...
(if (!= aTalker -1)
  (talkerSet add: aTalker)
  ; Pass both the buffer AND the tuple, no matter our settings.
  ; That does mean that msgkey may be null, but say won't use it in
  ; that case anyway.
  (aTalker
    modNum: theMod
    say: @theBuf msgkey
  )
  (++ curSequence)
)

In SQ4CD, the Narrator has extra noun, verb, and sequence properties that get set to allow the text to work. It’s really quite a bit of a mess, and my hat’s off to whoever on the ScummVM team got that Both mode to work. I was going to document it but got lost trying, it’s that wild.

On to the Narrator and by extension Talker!

Original Talker.sc:

(method (say theBuf whoCares)
  (if theIconBar (theIconBar disable:))
  (if (not initialized) (self init:))
 
  (= caller
    (if (and (> argc 1) whoCares)
      whoCares
    else
      null
    )
  )
 
  ; Figure out what to do with the message.
  ; Note that in one case, theBuf is a string...
  (if (& gMessageType TEXT_MSG)
    ; (method (startText theBuf &tmp strLength)
    (self startText: theBuf)
  )
  ; ...but in the other it's a tuple!
  (if (& gMessageType CD_MSG)
    ; (method (startAudio theKeys &tmp m n v c s)
    (self startAudio: theBuf)
  )
 
  ; cut a bit...
 
  ; start___ will have set ticks to the length
  ; of the string or recording. We add one more
  ; second regardless.
  (= ticks (+ ticks 60 gameTime))
  (return true)
)

Catdate’s Talker.sc:

; much the same, but
  (method (say theText theAudio whoCares)
    ; ...
    (if (& gMessageType TEXT_MSG)
      (self startText: theText)
    )
    (if (& gMessageType CD_MSG)
      (self startAudio: theAudio)
    )
    ; ...
  )

Now, this works fine. If I record a quick bit of gibberish, then load up the game, switch to Both, and click, I get a perfectly readable message and hear my gibber. But if I were to revert my little change and use the original code…

That’s what we in the business call mistaking a bunch of numbers for a valid string. I specifically get this result because the first value in the tuple is the module number, which is 110 (0x6E ‘n‘) in this case, and all numbers in SCI are 16-bit so there’s a terminating null right after.

What’s funny is that after all this, I can’t see how SQ4 is supposed to support Both mode, and ScummVM only needs to add that third button state. There is no patch to adjust the script, and I can’t for the life of me figure out how this would work:

(method (say theVoodoo whoCares &tmp newEvent)
  ; ...
  (if (& gMessageType TEXT_MSG)
    ; Note: noun, tVerb, and tSequence are properties. theVoodoo is now "case".
    (self startText: modNum noun tVerb theVoodoo tSequence &rest)
  )
  (if (& gMessageType CD_MSG)
    (self startAudio: theVoodoo)
  )
  ; ..
)

The weird part is that I can’t find anywhere those properties are set.

…At least with the KQ6/LB2 patches they actually do overhaul quite a bit of the scripts’ logic, which are otherwise just the same system scripts as above. Not the way I did it for my game, but clearly in a way that works out.

[ , , ] Leave a Comment

AGI, SCI, and combined priority/control screens

This post is dedicated to Cameron.


Last post, I ended with this claim:

This has been the case all the way since AGI.

It’s basically true, but there are some interesting details about AGI’s priority screen. For starters, it’s also the control screen.

Any color over a particular number is considered priority, while the lowest few are control. Thus, black is blocking, green is trigger, and blue is water. But if the control lines are drawn on top of the priority info, how do you not get unsightly gaps? If Gwydion were standing behind that table, wouldn’t you see his legs through that black gap? Turns out no, you wouldn’t. For lack of AGI source, here’s a part of ScummVM:

bool GfxMgr::checkControlPixel(int16 x, int16 y, byte viewPriority) {
  int offset = y * SCRIPT_WIDTH + x;
  byte curPriority;
 
  while (1) {
    y++;
    offset += SCRIPT_WIDTH;
    if (y >= SCRIPT_HEIGHT) {
      // end of screen, nothing but control pixels found
      return true; // draw view pixel
    }
    curPriority = _priorityScreen[offset];
    if (curPriority > 2) // valid priority found?
      break;
  }
  if (curPriority <= viewPriority)
    return true; // view priority is higher, draw
  return false; // view priority is lower, don't draw
}

In plain English, that means that when determining the priority of a given background pixel, if that pixel is a control color, you scan down to the next valid color:

But wait, this introduces errors! There are gaps in the seat and wall! And you know what? This works out fine because you can’t actually get to those points and be standing on a lower priority band. It’s all sneaky design in the end.

In SCI0, the control screen was split off from the priority screen. Black became the default value, white meant blocking, and all the others meant whatever the room programmers wanted them to mean. In a room with water, blue was the obvious choice but in a dry room blue might as well be a trigger. If something wasn’t a trigger, it was the hotspot for non-squarish background features.

In SCI1, vectored visual screens were deprecated. Instead, the background was basically a single Draw Bitmap command, followed by vector commands tracing the priority and control screens.

In SCI11, the control screen was deprecated — it was still available, but hardly used if at all. Walkable areas were now denoted with polygons, as were feature hotspots. Trigger areas were either polygons or IsInRect checks, but the priority screen worked the same as always. Priority screens were still vector traces, though.

It wasn’t until SCI2 that the system would radically change again, dropping the control screen and vectors altogether. Instead, the priority screen would be drawn at the same time as the visual screen: piece by piece.

Quite a difference in technique. They’re not even limited to four bits anymore — these are signed word priorities!


Update: she lives!

[ , ] 1 Comment on AGI, SCI, and combined priority/control screens

Getting your priorities in order

Drawing order that is. How does SCI know which bits of a character or whatever go behind which pieces of the background? It’s quite ingenious really.

You take your background image, first. Ignore the lonely king in the middle there, he’s not important right now.

Divide the screen up into fifteen bands. We use the standard CGA colors by convention and I left out black for a little bit of clarity. I didn’t leave out white — that’s the nearest you can be, in front of everything. Note that each screen can set their own thickness for each individual band. Given this information, we can draw a priority screen.

When View objects are drawn, such as Mr. Built-Like-A-Quarterback up there, they are first sorted by their Y coordinate, from furthest to the north to closest to the south. This implicitly places them on given priority bands. Graham for example is right on the edge of the dark gray band, priority 8. That way, when he’s being drawn, the engine can tell what part of the scenery is in front of him and skip those pixels simply by comparing his priority with that of the priority screen, kinda like—

Hey! Get back here!

As you can see, because basically all of the light colors but gray rank higher than dark gray, much of the view isn’t drawn.

If two Views stand on the same priority band, there’s still no problem — they’re drawn in Y order. This has been the case all the way since AGI. SCI2 and later build their priority screens a little differently, but that’s about as much of a technicality as the difference between AGI and SCI0, in that the specific implementation differs, and quite a lot, but the basic technique stays the same.

 

[ ] Leave a Comment

String functions in SCI11 and SCI2 compared

Leaving out the oddly-named StrSplit in SCI01, let’s get into the other string functions we’ve got. I have an idea that I’d like to ponder, y’see?

First up, in the old 16-bit SCI, or at least SCI11, we have the following kernel functions:

(StrCmp strA strB) Compares strA to strB until a null in strA or a mismatch. Returns 0 if the two strings match, something lower than zero if the first mismatch is lower in strA, something higher if it’s in strB.
(StrCmp strA strB maxLen) Same as (StrCmp strA strB), but only up to the first maxLen characters.
(StrLen str) Returns the number of characters in str.
(StrCpy strDest strSrc) Copies characters from strSrc into strDest, up to and including the null terminator. It’s up to you to ensure it fits.
(StrCpy strDest strSrc maxLen) If maxLen is positive, copies characters from strSrc to strDest up to and including the null terminator or up to maxLen characters. A terminator is ensured. If maxLen is negative, simply copies that many characters and damn the terminators.
(StrEnd str) Returns a pointer to the end of str. Effectively, str += strlen(str);.
(StrCat strA strB) Appends strB at the end of strA. It’s up to you to ensure this fits.
(StrAt str pos) Returns the character at pos in str.
(StrAt str pos newChar) Same as (StrAt str pos), but places newChar at pos, returning what was there.
(Format strDest format args...) Takes the format string and all the args, and prints it all to strDest. The format and any args for an %s placeholder can also be far text pairs.
(ReadNumber str) Tries to parse str as a string of digits and returns their value.

That’s a fair amount. It’s nice to have StrAt when you consider all numbers are inherently 16 bits wide and as such you can’t just manually work your way around a string. We’ve seen it around in hash calculations and dropcaps.

As an aside, the Format entry mentions far text pairs. Those refer to text resources, where instead of doing something like (Display "Hello World!") you’d do something like (Display 100 4) and have a text resource #100, where line #4 is “Hello World!”. This allows for more efficient memory use and ease of translation. In SCI0, you could only have up to 1000 resources of each type, from 0 to 999, while a script’s internal strings would be referenced with pointers that are always higher than 1000. This allows both the interpreter and scripts to tell the difference, fetching the actual string when called for. In the original SC compiler, there were in fact two ways to write strings. You could use "double quotes" as usual, or {curly braces}. One of these would be left as “near” strings in the script resource, the other would be automagically compiled into the script’s matching text resource as “far” strings. Neither SCI Companion nor Studio support this, and you can write any string in either style. I personally prefer the quotes.

Now, in SCI2 and later most of these separate kernel calls were consolidated into a single one with a bunch of subcommands, String. A few of these are wrappers around the Array kernel call, considering SCI2 strings are implemented as arrays of type string, but there are plenty proper string functions. Any function that may resize the string returns its new address.

(String StrNew size) Creates a new string data block (array of type String) of the given size.
(String StrSize str) Returns the size of the string.
(String StrAt str pos) Returns the character at pos in the string, or zero if it’s not that long.
(String StrAtPut str pos newChar) Sets the character at pos in the string, resizing it if it’s not that long.
(String StrFree str) Deallocates the string data block’s memory space.
(String StrFill str startPos length fillVal) Sets a whole range in the string to the given fillVal, resizing if needed.
(String StrCpy strDest destPos strSrc srcPos len) Copies a chunk of characters from strSrc to strDest, resizing if needed.
(String StrCmp strA strB) Compares strA and strB, as in SCI11.
(String StrCmp strA strB maxLen) Compares strA and strB up to maxLen, as in SCI11.
(String StrDup str) Duplicates the string block and returns the address of the duplicate.
(String StrGetData str) Returns a pointer to the string’s actual data.
(String StrLen str) Returns the length of the string’s actual data, up to the null terminator, as opposed to its containing array’s capacity.
(String StrFormat format args...) Takes the format and all args, printing it all to a new string, then returns the address of that new string.
(String StrFormatAt strDest format args...) Same as StrFormat but you provide an existing string to format to.
(String StrToInt str) Tries to parse str as a string of digits and returns their value.
(String StrTrim str flags) Removes whitespace from str. If flags is 1, all whitespace at the end is removed. If it’s 4, all whitespace at the front is removed. If it’s 2, everything inbetween is removed. These can be combined.
(String StrTrim str flags notThis) Same, but doesn’t consider notThis to be whitespace.
(String StrUpr str) Converts the string to uppercase.
(String StrLwr str) Converts the string to lowercase.
(String StrTrn strSrc strSrcPat strDestPat strDest) I honestly haven’t a clue. I never understood this one.

Now consider the following: these are all one and the same kernel call, and they include some functions that aren’t in the 16-bit interpreters such as case-folding and trimming. Wouldn’t it be nice? They don’t even have to be based on arrays, even if that’s a feature I’ve been working on backporting to SCI11+.

[ ] Leave a Comment

SCI01/1 Multilanguage games and telephone country codes

What?

Yeah. Telephone country codes. Those SCI games that let you switch between two languages without exiting? They used telephone country codes internally.

(instance sq4 of Game
  (properties
    parseLang 0
    printLang 0
  )
  ;...
)
 
(procedure (byLang german spanish french italian other)
  (switch (gGame printLang?)
    (49 german)
    (34 spanish)
    (33 french)
    (39 italian)
    (else other)
  )
)

Unfortunately, I don’t have the source code for an SCI interpreter that has the string splitting function needed — it only has the telephone number codes. So I’ll go with what ScummVM does.

Given a call to StrSplit with a parameter like You have an empty jar.#FVous avez un vase vide., the current printLang is matched with a separator character. In this case, if it’s zero we cut off and return the left part of the string. If it’s nonzero (say it’s 33), it’s matched to F for French. Looking for the split marker #, we then look at the next character and see if it’s our request. If it is, if we found a #F, we return the right part of the string. But what if we don’t find the right language? Let’s say for example I took the “see ya on the chronostream” message in the French version of SQ4 and made a Dutch secondary line?

What happens is, the interpreter gives up. ScummVM or the original, they just return the whole string.

But then of course, Dutch isn’t a supported language at all. The interpreter only recognizes the country codes for English, Japanese, German, French, Spanish, Italian, and Portuguese. And two of those aren’t supported by the game script I started this post off with. Surely if I gave the French SQ4 a German line it’d react differently?

Well, yeah. If the split marker is for a language the interpreter can recognize, it just returns the left part.

(Bonus: For no good reason beyond a little harmless pride in my country, I added the number for Dutch to the list in SCI11+. Which is stupid. It has no StrSplit function… but it could get one. Which would be stupid because we have patchDir support and can use it to just switch languages externally.)

… but why telephone numbers though?

Answer: numbers are easy to work with I guess.

[ , ] Leave a Comment

Combining PQ2 and KQ4… in SCI11

If you were so inclined, you can easily take that mashup I just posted and convert it to SCI11.

Just take the doit method from earlier and replace the two Print calls:

(Print
  addText:
    "TO: Detective Bonds\nFROM: Captain Hall\nSUBJECT: ID of evidence photo\n\nPlease provide the LAST name of the person pictured in the attached evidence photo for homicide case 186751.\n\nPlease respond in box below, ASAP!\n"
    40 0
  addIcon: 923 2 myPick 0 0
  addEdit: @yourAnswer 20 40 100
  init:
)

and

(Prints "Sorry Bonds, you'll need to do better than that!")

The main difference is that you’ll have to provide your own coordinates. You can tell that the ones I put are very rough. I mean to port the SCI0 Print procedure to SCI11 as ClassicPrint some day. Don’t be fooled — Prints is merely a simple wrapper procedure:

(procedure (Prints)
  (Print addText: &rest init:)
)
[ , ] Leave a Comment

Combining PQ2 and KQ4’s copy protection scripts

I said I would, right?

(local
  ; Correct answers' hashes, in original order.
  ; Determined by https://helmet.kafuka.org/sci/kq4_cp.html
  [answers 8] = [666 393 526 377 365 453 383 441]
)
 
(instance CopyProtection of Room
  (method (doit &tmp i ch hash myPick [yourAnswer 40])
 
    ; Just like in PQ2, we grab the current time, then mask out
    ; the lower bits to limit the range to a number from 0 to 7.
    (= myPick (& (GetTime gtTIME_OF_DAY) 7))
 
    ; Clear out the first character of our answer to effectively
    ; make it blank.
    (= yourAnswer 0)
 
    ; Request our input as before...
    (Print
      "TO: Detective Bonds\nFROM: Captain Hall\nSUBJECT: ID of evidence photo\n\nPlease provide the LAST name of the person pictured in the attached evidence photo for homicide case 186751.\n\nPlease respond in box below, ASAP!\n"
      #icon 701 0 myPick
      #edit @yourAnswer 20
    )
 
    ; Now we use some trickery from KQ4, but different.
    (= hash 0)
    (= i 0)
    ; While the character at position i is nonzero...
    (while (= ch (StrAt @yourAnswer i))
      ; Anything between 'a' and 'z' gets turned to uppercase.
      ; We don't bother putting it *back* in yourAnswer though.
      (if (and (>= ch 97) (<= ch 122)) (= ch (- ch 32)))
 
      ; Add this value to our running total.
      (= hash (+ hash ch))
      (++ i)
    )
 
    ; Either the hash we calculated is the correct one, or
    ; we entered "bobalu".
    (if (or
          (== hash [answers myPick])
          (== hash 437)
        )
      (gRoom newRoom: 1) ; or wherever your game starts.
    else
      (Print "Sorry Bonds, you'll need to do better than that!")
      (= gQuitGame true)
    )
  )
)

And presto! I’d talk about some of the other games’ copy protection schemes but for example KQ5’s doesn’t pass the decompiler. Probably because of a difficulty involving endless loops. Still, feel free to suggest something.

[ , , ] Leave a Comment

Sorry, Bonds – Police Quest 2 Copy Protection

Last for now in the set on copy protection is Police Quest 2. I might go into some others, I dunno, and I have something planned where I optimize the hell out of the PQ2 copy protection script by means of KQ4. But let’s get down to it.

(local
  [yourAnswer 40]
)
 
(procedure (ToUpper &tmp i ch)
  (= i 0)
  (while (= ch (StrAt @yourAnswer i))
    ; If ch is between 'a' and 'z'...
    (if (and (>= ch 97) (<= ch 122))
      ; ...change it to uppercase.
      (StrAt @yourAnswer i (- ch 32))
    )
    (++ i)
  )
)
 
(instance rm701 of Rm
  (method (doit &tmp myPick)
    (= myPick (& (GetTime gtTIME_OF_DAY) 7))
    (= yourAnswer 0)
 
    (Print "TO: Detective Bonds\n
            FROM: Captain Hall\n
            SUBJECT: ID of evidence photo\n
            \n
            Please provide the LAST name of the person pictured in
            the attached evidence photo for homicide case 186751.\n
            \n
            Please respond in box below, ASAP!\n"
            #icon 701 0 myPick
            #edit @yourAnswer 20
    )
 
    (= gQuit true)
    (ToUpper)
 
    ; Like in C, StrCmp returns zero if the strings are the same.
    ; Zero is false, so we use a not to make equal be true.
    (switch myPick
      (0    (if (not (StrCmp @yourAnswer "GRANANDEZ")) (= gQuit false)))
      (1    (if (not (StrCmp @yourAnswer "SIMMS"))     (= gQuit false)))
      (2    (if (not (StrCmp @yourAnswer "TASELLI"))   (= gQuit false)))
      (3    (if (not (StrCmp @yourAnswer "COLBY"))     (= gQuit false)))
      (4    (if (not (StrCmp @yourAnswer "BAINS"))     (= gQuit false)))
      (5    (if (not (StrCmp @yourAnswer "SNIDER"))    (= gQuit false)))
      (6    (if (not (StrCmp @yourAnswer "JONES"))     (= gQuit false)))
      (else (if (not (StrCmp @yourAnswer "DICKEY"))    (= gQuit false)))
    )
    (if gQuit
      (Print "Sorry Bonds, you'll need to do better than that!")
      ; With gQuit set, we'll exit at the end of this doit cycle.
    else
      (gGame restart:)
      ; The main game object can tell if we're restarting, so it'll
      ; put us in the first playable scene instead of the title screen.
    )
  )
)

Gee, I can think of a way to improve this already. Let’s turn yourAnswer from a local to a temp, and inline ToUpper:

(method (doit &tmp myPick i ch [yourAnswer 40])
  ; ...
  (= gQuit true)
 
  (= i 0)
  (while (= ch (StrAt @yourAnswer i))
    (if (and (>= ch 97) (<= ch 122))
      (StrAt @yourAnswer i (- ch 32))
    )
    (++ i)
  )
  ; ...
)

And that’s just one improvement. It really helps that, unlike the subtitle typing in Larry 5, we only uppercase one thing once. Tune in next time to see what could be done.

[ , , , ] 2 Comments on Sorry, Bonds – Police Quest 2 Copy Protection