My daughter Danielle had another interesting lab assignment in her computer class at Drexel. This time they learned about the British mathematician John Horton Conway who created the cellular automaton model known as "The Game of Life" (circa 1970). He recently passed away (04/11/2020) at the age of 82.
As part of the class exercise they had to add some code to a web page using a home grown language called "Tranquility". The first portion of the assignment was to turn a cell on & off - then display it as a red or black cell in a grid. Another part of the exercise was to implement the rules to see which cells survive in the next generation... thus the "Game of Life" title. After reading some of the background material on my own I thought this would be fun & fairly easy to implement using PC/370. The cells need only be a single byte with a very limited screen area approximately 18 rows x 76 columns (other rows are used for displaying controls keys, boxes & borders). I load the initial configuration from a text file that I can change & experiment with as often as I like.
ABOVE: Initial Generation based on file input. <F1> creates the next generation.
Back to the "Game of Life" Rules:
Each rendition of the game is based on an initial grid configuration - with cells either turned on (alive) or off (dead). A strict set of rules determines if future generations survive or die off. Depending on the size of the grid & the initial state of the configuration - the game could go on indefinitely generating chaotic or repetitive sequences of patterns.
The condensed explanation of the rules can be interpreted as follows:
A cell typically sits in the middle of a group of nine neighbors - three above, three below & two on each side - as well as the center. If the sum (Alive=1/Dead=0) of all nine fields in a given neighborhood is three, the
inner field state for the next generation will be life; if the all-field
sum is four, the inner field retains its current state; and every other
sum sets the inner field to death. Cells on the border of the grid will not have as many neighbors but the counting rule is still in effect.
Patterns - Still Lifes, Oscillators... Spaceships and Guns...
A variety of patterns may be formed that could retain their form for infinity - such as the "still life" or "oscillator" categories. A block of four, if left untouched by other creeping cells, will replicate with every generation. Researchers have found formations that generate other smaller formations - as if they were small factories. Read the Wikipedia entry for a detailed explanation. <CLICK HERE>
The "Game of Life" was created over 50 years ago. During this time researchers & enthusiasts have created starting configurations that have gone through millions of generations (or more...much more). They discovered puffer-type "breeders" which create glider "guns" which create "gliders"... It's a fascinating concept that's limited only by your grid/memory size, imagination & the amount of time on your hands. In my case I'm limiting the grid & my time... but still achieved some unexpected results. The "still lifes" & "oscillators" do indeed work as they are described. No time for the breeders, spaceships, guns & gliders. Maybe later...
ABOVE: Oscillating "blinker" - this toggles with every new generation. Categorized as a "period 2" oscillator.
ABOVE: Oscillating "Pulsar" - this repeats in 3 steps. Referred to as a "period 3" oscillator.
It's been great sitting down with Danielle & giving her some guidance - last year in her high school computer class & this year as she embarked on her freshman year at Drexel. There's always something that sparks my curiosity & compels me to write a quickie program.
Let's get started on the PC/370 "Game of Life" program - aptly named TDLIFE.ALC. We'll need a screen design, an input file to pass the initial configuration & the program. That's it...
SCREEN DESIGN/TEMPLATE:
Not much to this one. I reserved some space for a grid 18 rows & 76 columns. Actually 20 rows x 78 columns with zero value cells along the top, bottom, left & right borders. This constrains the boundaries. [X]=Alive while [BLANK]=Dead (i.e. ON or OFF).
xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
x GAME OF LIFE GENERATION[xx,xxx] <F1>=NEXTGEN <F4>=RESET <ESC>=EXIT $x
x ============================================================================$x
x.............................................................................$x
x. X $x
x. XXX $x
x. $x
x. $x
x. $x
x. $x
x. $x
x. $x
x. $x
x. $x
x. $x
x. $x
x. $x
x. $x
x. $x
x. $x
x. $x
x. $x
x.............................................................................$x
xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
TDLIFE.TXT Input Configuration File:
The program will read the input data (below) & populate the initial generation. I can create multiple versions of this file - TDLIFExx.TXT & copy to the main TDLIFE.TXT for processing.
***:1...5...10...15...20...25...30...35...40...45...50...55...60...65...70...75.
R01:X X
R02:X XX XX XX XX X XXX
R03: X XX X X X X X X X X XXX XXX
R04: XX X X X X
R05: X
R06: XXX X
R07: XX X
R08: XX XX XX XXX
R09: XX XX XX X XXX
R10: XX X X X X
R11:
R12: X X
R13:
R14: X X
R15: XXXXXXXX
R16: XXX
R17: XXXXXXXX XXXXX XXX XXXXXXX XXXXX
R18:X X
***:1...5...10...15...20...25...30...35...40...45...50...55...60...65...70...75.
MAIN LOGIC - TDLIFE.ALC:
The main logic is simple. Load the initial "Life Seeding" from the input text file, Build/Display the Screen with the current generation state & determine the next generation of "survivors". Repeat.
***********************************************************************
* MAINLINE PROCEDURE *
***********************************************************************
PRINT NOGEN
SVC @TRACE ISSUE SUPERVISOR CALL
DC CL4'IOF ' KEYBOARD INTERRUPT OFF
RESET EQU *
BAL 6,DATA LOAD INITIAL DATA
LOOP EQU *
BAL 6,BUILD BUILD LIFE GENERATION
BAL 6,SCREEN BUILD SCREEN
*
CLI KEY,@K#ESC KEY = ESCAPE ???
BE LOOPX YES - EXIT PLEASE
CLI KEY,@K#F4 KEY = <F4> ???
BE RESET YES - RESET GAME
*
CLI KEY,@K#F1 KEY = <F1> ???
BNE LOOP NO - DISPLAY SCREEN
*
BAL 6,NEXTGEN NEXT GENERATION
B LOOP DISPLAY SCREEN AGAIN
LOOPX EQU *
B RETURN EXIT PROGRAM PLEASE
***********************************************************************
CREATING the NEXT GENERATION:
To create the next generation I'll need two arrays - LIFETAB (current) & NEXTTAB (future). As the current cells are evaluated within their own relative neighborhoods (up to 9 blocks) the result (alive/dead) is transposed to the new array. Once the entire grid has been evaluated the resulting next generation table [NEXTTAB] is copied to the current generation [LIFETAB].
The dimensions of the table are 20 rows x 78 columns which includes "dead" border zones of Rows 1 & 20 and Columns 1 and 78. This leaves an effective dimension of 18 x 76 - at least where potential "live" cells are concerned. Determining a cell's neighbors is fairly simple given the full X/Y dimensions. Subtracting 79 cells points to the top left. Subtracting 1 cell points to the direct left. Adding 77 points to the bottom left. Keeping in line with that logic it's easy to extract the value (0 or 1) from each cell in the group & accumulate their sum. If the sum is 3 the next generation cell is ALIVE - if it's 4 the cell remains the same (ALIVE or DEAD) - otherwise it is DEAD. The patterns evolve based on that simple rule.
***********************************************************************
* NEXT GENERATION EVOLUTION *
***********************************************************************
DC F'0' RETURN ADDRESS SAVE AREA
NEXTGEN EQU *
ST 6,*-4 SAVE RETURN ADDRESS
*
AP GEN,=P'1' INCREMENT GENERATION
*
LA 2,=X'0F' LOAD SOURCE ADDRESS
LA 3,1 LOAD SOURCE LENGTH
LA 4,NEXTTAB LOAD TARGET ADDRESS
LA 5,1560 LOAD TARGET LENGTH
ICM 3,B'1000',=X'0F' LOAD PAD CHARACTER
MVCL 4,2 INIT RECORD AREA
*
LA 4,18 LOAD ROW COUNT
LA 5,NEXTTAB+79 LOAD NEXT ADDRESS
LA 6,LIFETAB+79 LOAD LIFE ADDRESS
NEXTROW EQU *
LA 3,76 LOAD COLUMN COUNT
NEXTCOL EQU *
ZAP CTR,=P'0' CLEAR NEIGHBOR COUNT
*
LR 7,6 XFER LIFE ADDRESS
SH 7,=Y(79) POINT TO TOP LEFT
AP CTR,0(1,7) ADD TOP LEFT VALUE
AP CTR,1(1,7) ADD TOP CELL VALUE
AP CTR,2(1,7) ADD TOP RIGHT VALUE
*
LR 7,6 XFER LIFE ADDRESS
SH 7,=Y(1) POINT TO DIRECT LEFT
AP CTR,0(1,7) ADD LEFT CELL VALUE
AP CTR,1(1,7) ADD CENTER CELL VALUE
AP CTR,2(1,7) ADD RIGHT CELL VALUE
*
LR 7,6 XFER LIFE ADDRESS
AH 7,=Y(77) POINT TO BOTTOM LEFT
AP CTR,0(1,7) ADD BOTTOM LEFT VALUE
AP CTR,1(1,7) ADD BOTTOM CENTER VALUE
AP CTR,2(1,7) ADD BOTTOM RIGHT VALUE
*
MVC 0(1,5),0(6) DEFAULT CURRENT STATE
CP CTR,=P'3' THREE NEIGHBORS?
BNE *+12 NO - CONTINUE PLEASE
MVI 0(5),X'1F' YES - CELL IS ALIVE
B NEXTCOLB BUMP TABLE POINTERS
*
CP CTR,=P'4' FOUR NEIGHBORS?
BE NEXTCOLB YES - DEFAULT STATE
*
MVI 0(5),X'0F' NO - CELL IS DEAD
NEXTCOLB EQU *
LA 5,1(,5) BUMP NEXT POINTER
LA 6,1(,6) BUMP LIFE POINTER
BCT 3,NEXTCOL LOOP THROUGH COLUMNS
*
LA 5,2(,5) ADJUST NEXT POINTER
LA 6,2(,6) ADJUST LIFE POINTER
BCT 4,NEXTROW LOOP THROUGH ROWS
*
LA 2,NEXTTAB LOAD SOURCE ADDRESS
LA 3,1560 LOAD SOURCE LENGTH
LA 4,LIFETAB LOAD TARGET ADDRESS
LA 5,1560 LOAD TARGET LENGTH
ICM 3,B'1000',=X'0F' LOAD PAD CHARACTER
MVCL 4,2 INIT RECORD AREA
NEXTGENX EQU *
L 6,NEXTGEN-4 RESTORE LINK REGISTER
BR 6 BRANCH ON LINK REGISTER
***********************************************************************
Game of Life Incremental Animation:
When testing I pressed the <F1> key over 200 times taking some incremental snapshots along the way. The pattern had stabilized before 200 was reached with some static still lifes and a single blinking oscillator in the bottom right corner (see generation 250 & 251 in the animation).
ABOVE: Various generational snapshots. 1, 10, 20, 30, 40, 50, 60, 70, 80, 90, 100, 150, 200, 250 & 251.My test file configuration (above) was a combination of still lifes, oscillators & random constructs. As the live cells permeated throughout the board some of the original static still life constructs & oscillators were consumed & metastasized. My experiment was within a very condensed field of play. Researchers have generated massive amounts of generational patterns on a variety of playing fields including 3-Dimensional tubes.
Overpopulation & Explosive Growth:
The rules Conway incorporated into the game were designed to limit growth (as overpopulation does in the real world). Seeding the grid entirely with "live" cells has a dramatic & disastrous effect.
ABOVE: Overpopulation is deadly in "The Game of Life". With a completely full grid total extinction occurs after only 2 generations! Not a single survivor in generation three...
ABOVE: Just a 3D rendor I created of yellow stickman figures - each represents a live cell or "X" on the screen.
TDLIFE.ALC - Full Source Code:
TITLE 'TDLIFE - PC/370 4.2 // DELIA'
***********************************************************************
* *
* MODULE: TDLIFE. *
* AUTHOR: TONY DELIA. *
* DATE: 11/25/2020. *
* DESC: PC/370 "GAME OF LIFE" SIMULATION. *
* NOTE: PC/370 RELEASE 4.2 *
* REFERENCE: https://en.wikipedia.org/wiki/Conway's_Game_of_Life *
* *
***********************************************************************
EJECT
***********************************************************************
* T D L I F E P R O G R A M *
***********************************************************************
TDLIFE START 0 START PROGRAM
STM 14,12,12(13) SAVE REGISTERS
LR 12,15 LOAD PROGRAM ENTRY POINT
USING TDLIFE+0*4096,12 BASE REGISTER 1
L 11,BASE2 LOAD BASE REGISTER 2
USING TDLIFE+1*4096,11 TELL ASSEMBLER ABOUT BASE2
L 10,BASE3 LOAD BASE REGISTER 3
USING TDLIFE+2*4096,10 TELL ASSEMBLER ABOUT BASE3
ST 13,SAVE+4 SAVE EXTERNAL SAVE ADDRESS
LR 14,13 XFER ADDRESS TO TEMP R14
LA 13,SAVE LOAD INTERNAL SAVE ADDRESS
ST 13,8(14) SAVE IN EXTERNAL SAVE AREA
B GO BRANCH TO PROCESSING RTN
***********************************************************************
RETURN EQU * TIME TO RETURN
L 13,SAVE+4 RESTORE REGISTER 13
LM 14,12,12(13) RESTORE REMAINING REGS
SR 15,15 CLEAR RETURN CODE
BR 14 BRANCH TO CALLING PROGRAM
***********************************************************************
SAVE DC 18F'0' S A V E A R E A
***********************************************************************
BASE2 DC A(TDLIFE+1*4096) BASE2 DISPLACEMENT
BASE3 DC A(TDLIFE+2*4096) BASE3 DISPLACEMENT
***********************************************************************
GO EQU * BEGIN PROCESSING ...
***********************************************************************
EJECT
***********************************************************************
* MAINLINE PROCEDURE *
***********************************************************************
PRINT NOGEN
SVC @TRACE ISSUE SUPERVISOR CALL
DC CL4'IOF ' KEYBOARD INTERRUPT OFF
RESET EQU *
BAL 6,DATA LOAD INITIAL DATA
LOOP EQU *
BAL 6,BUILD BUILD LIFE GENERATION
BAL 6,SCREEN BUILD SCREEN
*
CLI KEY,@K#ESC KEY = ESCAPE ???
BE LOOPX YES - EXIT PLEASE
CLI KEY,@K#F4 KEY = <F4> ???
BE RESET YES - RESET GAME
*
CLI KEY,@K#F1 KEY = <F1> ???
BNE LOOP NO - DISPLAY SCREEN
*
BAL 6,NEXTGEN NEXT GENERATION
B LOOP DISPLAY SCREEN AGAIN
LOOPX EQU *
B RETURN EXIT PROGRAM PLEASE
***********************************************************************
EJECT
***********************************************************************
* BUILD SCREEN *
***********************************************************************
DC F'0' RETURN ADDRESS SAVE AREA
SCREEN EQU *
ST 6,*-4 SAVE RETURN ADDRESS
*
MVI VBITS,@BKWT SET BG(BLACK)/FG(WHITE)
BAL 6,VRESET CHANGE SCREEN ATTRIBUTES
*
* DISPLAY SINGLE BOX
*
MVC VBX,VBOX2 LOAD BOX FRAME
MVC VBXRC,BXTAB LOAD BOX COORDINATES
BAL 6,VBOX DISPLAY BOX FRAME
*
* DISPLAY SCREEN TEXT
*
LA 5,SCTAB LOAD TABLE ADDRESS
SC1LP EQU *
CLI 0(5),X'FF' END OF TABLE ???
BE SC1LPX YES - EXIT LOOP PLEASE
*
MVC VXYS,0(5) MOVE CURSOR POSITION
BAL 6,VXYSET SET CURSOR POSITION
L 2,4(5) LOAD MESSAGE ADDRESS
SVC @WTO ISSUE SUPERVISOR CALL
*
LA 5,8(,5) BUMP TABLE POINTER
B SC1LP TEST NEXT TABLE ENTRY
SC1LPX EQU *
*
* ACCEPT KEYSTROKE
*
BAL 6,KBGET READ KEYBOARD INPUT
MVC KEY,KBCHR STORE KEYSTROKE
*
CLI KEY,@K#ESC KEY = ESCAPE ???
BE SC2LPX YES - EXIT ROUTINE
CLI KEY,@K#F1 KEY = F1 ???
BE SC2LPX YES - EXIT ROUTINE
CLI KEY,@K#F4 KEY = F4 ???
BE SC2LPX YES - EXIT ROUTINE
*
B SC1LPX BACK TO KEYBOARD
SC2LPX EQU *
MVI VBITS,@BKWT SET BG(BLACK)/FG(WHITE)
BAL 6,VRESET CHANGE SCREEN ATTRIBUTES
SCREENX EQU *
L 6,SCREEN-4 RESTORE LINK REGISTER
BR 6 BRANCH ON LINK REGISTER
***********************************************************************
EJECT
***********************************************************************
* BUILD CURRENT GENERATION *
***********************************************************************
DC F'0' RETURN ADDRESS SAVE AREA
BUILD EQU *
ST 6,*-4 SAVE RETURN ADDRESS
*
MVC SCRHDR+28(7),ED1 MOVE EDIT PATTERN
ED SCRHDR+28(7),GEN EDIT GENERATION COUNT
*
LA 5,18 LOAD LINE COUNT
LA 6,SCRLN01 LOAD SCREEN ADDRESS
BUILD1 EQU *
MVI 0(6),C' ' MOVE SPACE TO SCREEN
MVC 1(75,6),0(6) PROPAGATE THROUGH LINE
LA 6,77(,6) BUMP SCREEN POINTER
BCT 5,BUILD1 LOOP THROUGH ALL ROWS
*
LA 5,18 LOAD LINE COUNT
LA 6,SCRLN01 LOAD SCREEN ADDRESS
LA 7,LIFETAB+(1*78)+1 LOAD LIFE ADDRESS
BUILD2A EQU *
LA 4,76 LOAD COLUMN COUNT
BUILD2B EQU *
CP 0(1,7),=P'1' CELL ALIVE??
BL *+8 NO - CONTINUE PLEASE
MVI 0(6),C'X' YES - MARK WITH "X"
*
LA 7,1(,7) BUMP LIFE POINTER
LA 6,1(,6) BUMP SCREEN POINTER
BCT 4,BUILD2B LOOP THROUGH COLUMNS
*
LA 7,2(,7) ADJUST LIFE POINTER
LA 6,1(,6) ADJUST SCREEN POINTER
BCT 5,BUILD2A LOOP THROUGH ALL ROWS
BUILDX EQU *
L 6,BUILD-4 RESTORE LINK REGISTER
BR 6 BRANCH ON LINK REGISTER
***********************************************************************
EJECT
***********************************************************************
* NEXT GENERATION EVOLUTION *
***********************************************************************
DC F'0' RETURN ADDRESS SAVE AREA
NEXTGEN EQU *
ST 6,*-4 SAVE RETURN ADDRESS
*
AP GEN,=P'1' INCREMENT GENERATION
*
LA 2,=X'0F' LOAD SOURCE ADDRESS
LA 3,1 LOAD SOURCE LENGTH
LA 4,NEXTTAB LOAD TARGET ADDRESS
LA 5,1560 LOAD TARGET LENGTH
ICM 3,B'1000',=X'0F' LOAD PAD CHARACTER
MVCL 4,2 INIT RECORD AREA
*
LA 4,18 LOAD ROW COUNT
LA 5,NEXTTAB+79 LOAD NEXT ADDRESS
LA 6,LIFETAB+79 LOAD LIFE ADDRESS
NEXTROW EQU *
LA 3,76 LOAD COLUMN COUNT
NEXTCOL EQU *
ZAP CTR,=P'0' CLEAR NEIGHBOR COUNT
*
LR 7,6 XFER LIFE ADDRESS
SH 7,=Y(79) POINT TO TOP LEFT
AP CTR,0(1,7) ADD TOP LEFT VALUE
AP CTR,1(1,7) ADD TOP CELL VALUE
AP CTR,2(1,7) ADD TOP RIGHT VALUE
*
LR 7,6 XFER LIFE ADDRESS
SH 7,=Y(1) POINT TO DIRECT LEFT
AP CTR,0(1,7) ADD LEFT CELL VALUE
AP CTR,1(1,7) ADD CENTER CELL VALUE
AP CTR,2(1,7) ADD RIGHT CELL VALUE
*
LR 7,6 XFER LIFE ADDRESS
AH 7,=Y(77) POINT TO BOTTOM LEFT
AP CTR,0(1,7) ADD BOTTOM LEFT VALUE
AP CTR,1(1,7) ADD BOTTOM CENTER VALUE
AP CTR,2(1,7) ADD BOTTOM RIGHT VALUE
*
MVC 0(1,5),0(6) DEFAULT CURRENT STATE
CP CTR,=P'3' THREE NEIGHBORS?
BNE *+12 NO - CONTINUE PLEASE
MVI 0(5),X'1F' YES - CELL IS ALIVE
B NEXTCOLB BUMP TABLE POINTERS
*
CP CTR,=P'4' FOUR NEIGHBORS?
BE NEXTCOLB YES - DEFAULT STATE
*
MVI 0(5),X'0F' NO - CELL IS DEAD
NEXTCOLB EQU *
LA 5,1(,5) BUMP NEXT POINTER
LA 6,1(,6) BUMP LIFE POINTER
BCT 3,NEXTCOL LOOP THROUGH COLUMNS
*
LA 5,2(,5) ADJUST NEXT POINTER
LA 6,2(,6) ADJUST LIFE POINTER
BCT 4,NEXTROW LOOP THROUGH ROWS
*
LA 2,NEXTTAB LOAD SOURCE ADDRESS
LA 3,1560 LOAD SOURCE LENGTH
LA 4,LIFETAB LOAD TARGET ADDRESS
LA 5,1560 LOAD TARGET LENGTH
ICM 3,B'1000',=X'0F' LOAD PAD CHARACTER
MVCL 4,2 INIT RECORD AREA
NEXTGENX EQU *
L 6,NEXTGEN-4 RESTORE LINK REGISTER
BR 6 BRANCH ON LINK REGISTER
***********************************************************************
EJECT
***********************************************************************
* DATA LOAD - POPULATE INITIAL LIFE TABLE [AND/OR RESET] *
***********************************************************************
DC F'0' RETURN ADDRESS SAVE AREA
DATA EQU *
ST 6,*-4 SAVE RETURN ADDRESS
*
LA 2,=X'0F' LOAD SOURCE ADDRESS
LA 3,1 LOAD SOURCE LENGTH
LA 4,LIFETAB LOAD TARGET ADDRESS
LA 5,1560 LOAD TARGET LENGTH
ICM 3,B'1000',=X'0F' LOAD PAD CHARACTER
MVCL 4,2 INIT RECORD AREA
*
LA 2,=X'0F' LOAD SOURCE ADDRESS
LA 3,1 LOAD SOURCE LENGTH
LA 4,NEXTTAB LOAD TARGET ADDRESS
LA 5,1560 LOAD TARGET LENGTH
ICM 3,B'1000',=X'0F' LOAD PAD CHARACTER
MVCL 4,2 INIT RECORD AREA
*
XFILI STDWKI OPEN INPUT FILE
*
LA 8,LIFETAB+(1*78)+1 LOAD LIFE ADDRESS
GETI EQU *
XREAD IREC,80 READ INPUT RECORD
BNZ EOFI EOF - EXIT ROUTINE
*
CLI IREC,C'R' DATA = CODE???
BNE GETI NO - READ NEXT RECORD
*
LA 7,IREC+4 LOAD INPUT ADDRESS
GETL EQU *
C 7,=A(IREC+80) END OF INPUT RECORD?
BNL GETX YES - EXIT INNER LOOP
*
CLI 0(7),C'X' CHARACTER EQUALS "X"?
BNE *+8 NO - CONTINUE PLEASE
MVI 0(8),X'1F' YES - TURN ON CELL
*
LA 7,1(,7) BUMP INPUT POINTER
LA 8,1(,8) BUMP TABLE POINTER
B GETL LOOP THROUGH INPUT
GETX EQU *
LA 8,2(,8) ADJUST TABLE POINTER
B GETI READ NEXT RECORD
EOFI EQU *
ZAP GEN,=P'1' SET GENERATION = 1
DATAX EQU *
L 6,DATA-4 RESTORE LINK REGISTER
BR 6 BRANCH ON LINK REGISTER
***********************************************************************
EJECT
***********************************************************************
* WORKING STORAGE *
***********************************************************************
DUBB DC D'0' DOUBLEWORD
FULL DC F'0' FULLWORD
HALF DC H'0' HALFWORD
BLANK DC CL1' ' BLANK CHARACTER
KEY DC CL1' ' KEY STROKE (@RDKEY)
CHAR DC CL1' ',C'$' KEY CHARACTER
@YES EQU C'Y' YES
@NO EQU C'N' NO
@ESC EQU 27 ESCAPE KEY
@CR EQU 13 CARRIAGE RETURN
@LF EQU 10 LINE FEED
@KEYLO EQU 32 ASCII KEY - LO VALUE
@KEYHI EQU 126 ASCII KEY - HI VALUE
CTR DC PL2'0' WORK COUNTER
GEN DC PL3'0' GENERATION COUNTER
ED1 DC XL7'4020206B202120' EDIT - ZZZ,ZZ9
***********************************************************************
* DATA CONTROL BLOCK SET UP *
***********************************************************************
STDWKI DC CL64'C:\PC370\TDLIFE.TXT'
***********************************************************************
* INPUT RECORD AREA *
***********************************************************************
IREC DC CL80' ' INPUT RECORD
OREC DS 0CL133 OUTPUT RECORD
OBLANK DC CL1' ' OUTPUT BLANK
OPRT DC CL132' ' OUTPUT PRINT AREA
***********************************************************************
* COPYBOOKS *
***********************************************************************
COPY CPY/TDBOX.CPY COPYBOOK - BOX DISPLAY
COPY CPY/TDVID.CPY COPYBOOK - VIDEO UTILITY
COPY CPY/TDKBD.CPY COPYBOOK - KEYBOARD INPUT
COPY CPY/TDKEY.CPY COPYBOOK - KEYSTROKES
COPY CPY/TDCLR.CPY COPYBOOK - COLORS
COPY CPY/TDSVC.CPY COPYBOOK - SUPERVISOR
***********************************************************************
LTORG LITERAL POOL
***********************************************************************
* BOX COMPONENTS (COORDINATES/FRAME) *
***********************************************************************
BXTAB DS 0F
DC AL1(0,0,23,79) BOX COORDINATES/FRAME
***********************************************************************
* SCREEN DISPLAY COMPONENTS *
***********************************************************************
SCTAB DS 0F
DC AL1(0,0,1,2),A(SCRHDR) SCREEN COORDINATES/MSG
DC AL1(0,0,2,2),A(SCRDASH) SCREEN COORDINATES/MSG
DC AL1(0,0,4,2),A(SCRLN01) SCREEN COORDINATES/MSG
DC AL1(0,0,5,2),A(SCRLN02) SCREEN COORDINATES/MSG
DC AL1(0,0,6,2),A(SCRLN03) SCREEN COORDINATES/MSG
DC AL1(0,0,7,2),A(SCRLN04) SCREEN COORDINATES/MSG
DC AL1(0,0,8,2),A(SCRLN05) SCREEN COORDINATES/MSG
DC AL1(0,0,9,2),A(SCRLN06) SCREEN COORDINATES/MSG
DC AL1(0,0,10,2),A(SCRLN07) SCREEN COORDINATES/MSG
DC AL1(0,0,11,2),A(SCRLN08) SCREEN COORDINATES/MSG
DC AL1(0,0,12,2),A(SCRLN09) SCREEN COORDINATES/MSG
DC AL1(0,0,13,2),A(SCRLN10) SCREEN COORDINATES/MSG
DC AL1(0,0,14,2),A(SCRLN11) SCREEN COORDINATES/MSG
DC AL1(0,0,15,2),A(SCRLN12) SCREEN COORDINATES/MSG
DC AL1(0,0,16,2),A(SCRLN13) SCREEN COORDINATES/MSG
DC AL1(0,0,17,2),A(SCRLN14) SCREEN COORDINATES/MSG
DC AL1(0,0,18,2),A(SCRLN15) SCREEN COORDINATES/MSG
DC AL1(0,0,19,2),A(SCRLN16) SCREEN COORDINATES/MSG
DC AL1(0,0,20,2),A(SCRLN17) SCREEN COORDINATES/MSG
DC AL1(0,0,21,2),A(SCRLN18) SCREEN COORDINATES/MSG
DC XL1'FF' END OF TABLE
***********************************************************************
SCRHDR DC C'GAME OF LIFE GENERATION[xxx,xxx] '
DC C'<F1>=NEXTGEN <F4>=RESET <ESC>=EXIT',C'$'
SCRDASH DC C'==================================='
DC C'=========================================',C'$'
SCRLN01 DC CL76' ',C'$' LIFETAB + 1*78 + 1
SCRLN02 DC CL76' ',C'$' LIFETAB + 2*78 + 1
SCRLN03 DC CL76' ',C'$' LIFETAB + 3*78 + 1
SCRLN04 DC CL76' ',C'$' LIFETAB + 4*78 + 1
SCRLN05 DC CL76' ',C'$' LIFETAB + 5*78 + 1
SCRLN06 DC CL76' ',C'$' LIFETAB + 6*78 + 1
SCRLN07 DC CL76' ',C'$' LIFETAB + 7*78 + 1
SCRLN08 DC CL76' ',C'$' LIFETAB + 8*78 + 1
SCRLN09 DC CL76' ',C'$' LIFETAB + 9*78 + 1
SCRLN10 DC CL76' ',C'$' LIFETAB + 10*78 + 1
SCRLN11 DC CL76' ',C'$' LIFETAB + 11*78 + 1
SCRLN12 DC CL76' ',C'$' LIFETAB + 12*78 + 1
SCRLN13 DC CL76' ',C'$' LIFETAB + 13*78 + 1
SCRLN14 DC CL76' ',C'$' LIFETAB + 14*78 + 1
SCRLN15 DC CL76' ',C'$' LIFETAB + 15*78 + 1
SCRLN16 DC CL76' ',C'$' LIFETAB + 16*78 + 1
SCRLN17 DC CL76' ',C'$' LIFETAB + 17*78 + 1
SCRLN18 DC CL76' ',C'$' LIFETAB + 18*78 + 1
***********************************************************************
* LIFE TABLE 18 ROWS x 76 COLS (PADDED ON EDGES = 20*78) *
***********************************************************************
LIFETAB DC 1560XL1'0F' LIFETAB - CURR GENERATION
DC X'FF' END OF TABLE
NEXTTAB DC 1560XL1'0F' NEXTTAB - NEXT GENERATION
DC X'FF' END OF TABLE
***********************************************************************
END TDLIFE
I truly enjoy sitting with my daughter, answering questions & being able to provide guidance and steer her in the right direction. One of the most important lessons I can pass on to her is to focus on logic, creativity & efficiency - as well as clarity. Code in any language should be well thought out & streamlined. Convoluted spaghetti code is a menace. Also, to enjoy problem solving just as you would with a puzzle or other fun game.
ABOVE: Danielle cranking out the code like her Dad... or just randomly playing around with the mouse (02/2004).
Hope someone out there enjoyed this post...