Festive Coding with Mainframe Languages
Holiday spirit & Mainframe Coding fun π¨π»βπ»
Henri Kuiper, CTO @ Mainframe Society
Part of IBM ZDay 2025
A global holiday coding tradition made by Eric Wastl
Santa is trying to deliver presents in a large
apartment building. He starts on the ground
floor (0) and then follows the instructions one
character at a time.
( ==> go up one floor
) ==> go down one floor
The apartment building is very tall,
Santa will never find the top or bottom floors.
For example: ((( results in floor 3
To what floor do the instructions take Santa?
instruction_set = "((((()(..."
floor = 0
for instruction in instruction_set:
if instruction == "(":
floor = floor +1
elif instruction == ")":
floor = floor -1
print("Santa is at floor: {}".format(floor))
What if we solved them⦠on z/OS?
/* REXX */
INST = "((((()(..."
floor = 0
do i = 1 to length(INST)
inst = substr(INST,i,1)
if inst = "(" then floor = floor + 1
if inst = ")" then floor = floor - 1
end
say "Santa is at floor" floor
SANTAFLOOR: PROC OPTIONS(MAIN);
DCL instructions CHAR(100) INIT('((((()(...');
DCL i FIXED BIN(31);
DCL floor FIXED BIN(31) INIT(0);
DCL c CHAR(1);
DO i = 1 TO LENGTH(instructions);
c = SUBSTR(instructions, i, 1);
IF c = '(' THEN
floor = floor + 1;
ELSE IF c = ')' THEN
floor = floor - 1;
END;
PUT SKIP LIST('Santa is at floor:', floor);
END SANTAFLOOR;
IDENTIFICATION DIVISION.
PROGRAM-ID. SANTAFLOOR.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 INSTRUCTION-SET PIC X(100) VALUE "((((()(...".
01 I PIC 9(3) VALUE 1.
01 LEN PIC 9(3).
01 CHAR PIC X.
01 FLOOR PIC S9(5) VALUE 0.
PROCEDURE DIVISION.
COMPUTE LEN = FUNCTION LENGTH(INSTRUCTION-SET)
PERFORM VARYING I FROM 1 BY 1 UNTIL I > LEN
MOVE INSTRUCTION-SET(I:1) TO CHAR
EVALUATE CHAR
WHEN "("
ADD 1 TO FLOOR
WHEN ")"
SUBTRACT 1 FROM FLOOR
END-EVALUATE
END-PERFORM
DISPLAY "Santa is at floor: " FLOOR
STOP RUN.
SANTAFLR CSECT
USING SANTAFLR,R15 Establish base register
STM R14,R12,12(R13) Save caller registers
LR R12,R15 Set up base
LA R11,SAVEAREA Get save area
ST R13,4(R11) Chain back
ST R11,8(R13)
LR R13,R11
***********************************************************************
* WORKING STORAGE
***********************************************************************
INSTRSET DC C'((((()(...' Instruction string
INSTRLEN DC F'11' Length of the string
FLOOR DC F'0' Current floor counter
I DC F'1' Loop index
CHAR DS CL1 Current character
MSG DC C'Santa is at floor: '
***********************************************************************
* MAIN LOGIC
***********************************************************************
MAINLOOP DS 0H
L R1,I Load loop index
C R1,INSTRLEN Compare to length
BH DONE If higher, weβre done
LA R2,INSTRSET Load address of string
AR R2,R1 Add index
SR R2,=F'1' Adjust for 0-based
MVC CHAR(1),0(R2) Get character
CLI CHAR,'('
BE UP
CLI CHAR,')'
BE DW
B NX
UP L R3,FLOOR
LA R3,1(R3)
ST R3,FLOOR
B NEXT
DW L R3,FLOOR
LA R3,-1(R3)
ST R3,FLOOR
NX LA R1,1(R1)
ST R1,I
B MAINLOOP
***********************************************************************
* PRINT RESULT
***********************************************************************
DONE WTO 'Santa is at floor:' Print message
MVC BUF(4),FLOOR Move floor value to buffer
***********************************************************************
* CLEANUP AND RETURN
***********************************************************************
L R13,4(R13)
LM R14,R12,12(R13)
BR R14
SAVEAREA DS 18F
BUF DS CL10
END SANTAFLR
Many organisations sponsor this event.
Help us code, celebrate, and spread the cheer
ππ₯° Have donated usage of their z/OS image π₯°π
ππππ
It's learning, teamwork, and competition
Show 'the world' the Mainframe community can play this global game too!
Sign up and join the fun!
mfaoc.mainframe.community
#MFAOC #AdventOfCode #REXXTheHalls@Mainframe Society on LinkedIN posts!Henri Kuiper β Mainframe Society
π» mfaoc.mainframe.community
https://www.linkedin.com/in/wizardofzos
henri@mainframesociety.com
#REXXTheHalls #MFAOC
π