<xmp><!-- <body> --></xmp>


droidsnap.


screenshots from the WM8850-mid netbook
droidsnap.zrad.vze.com

[>] fnni

'
' ..... /* ========================================================== */
' ..... /*
' ..... /* PAMAZE.BAS  : Plot ASCII Maze v1.01
' ..... /*
' ..... /* Original    : AppleII users group
' ..... /*               Compuserve public access
' ..... /*
' ..... /* 14 sep 1990 : Gary & Donna McCoy
' ..... /*               Adapted for IBM-PC gwBasic 2.0
' ..... /*
' ..... /* 04 dec 1993 : Hans-Ruedi H. Wernli (Switzerland)
' ..... /*               Adapted for powerBasic 3.00c
' ..... /*               Verbose comments added/style improved
' ..... /*               Moderate improvements to navigation/randomness
' ..... /*               gwBasic compatibility compromised
' ..... /*
' ..... /* 27 oct 1998 : Screaming CuckooBroad Associates
' ..... /*               Adapted for qBasic 1.1:
' ..... /*                 FNM at precompile not runtime
' ..... /*                 REDIM: no. Careful: watch "CLEAR"
' ..... /*                 PB3 directives commented
' ..... /*                 DELAYs removed or changed to SLEEPs
' ..... /*                 LOOPs (not WHILEs) without EXITs
' ..... /*                 INKEY$ scan codes kludged
' ..... /*               Color/display/interface improvements:
' ..... /*                 square brackets act as L/R cursors
' ..... /*                 upCursor acts as spacebar
' ..... /*                 q not  to Quit
' ..... /*                 topviews are toggled
' ..... /*               General cleanup (comments/alignment/spelling)
' ..... /*               ASCII text character plotter (!)
' ..... /*
' ..... /* My purpose was to generate ASCII mazes; I found the internet
' ..... /* laden with algorithmic discussions, pseudocode, completed
' ..... /* adventure games & Csource, yet this is the one basic program
' ..... /* I could locate which generates randomly & displays both from
' ..... /* inside & above. As there is in fact more wrong with the
' ..... /* original PCMAZE.BAS than the failure to renumber it once
' ..... /* (REN 1000,1,10), I used rather a cleaned-up PBMAZE.BAS. My
' ..... /* mods continue the tradition of leaving alone the heart of the
' ..... /* generator, so carefully preserved by so many, whom I thank.
' ..... /*
' ..... /* ---------------------------------------------------------- */
' --------    _/  _/      _/   _/_/  -----------------------------------
' Kevin A    _/ _/      _/_/  _/  _/ :::    kevipow@aztec.asu.edu    :::
'  Powell   _/_/ _/   _/_/_/ _/_/_/  http://members.tripod.com/~kevipow/
' ======== _/     _/o_/  _/o_/    o  ===================================
'
'****************************************************************************
'* PROGRAM NAME: PCMAZE  .BAS   DATE:  4.12.1993   INCLUDE IN: is main      *
'* LANGUAGE: Power BASIC 3.00c (Robert S.Zale / Spectra Publishing)         *
'* PURPOSE: GW-BASIC minimum adaption to PB3                                *
'* INCLUDE FILES: none                                                      *
'* OBJECT FILES:  none                                                      *
'* INPUT FILES:   none                                                      *
'* OUTPUT FILES:  none                                                      *
'* ------------------------------------------------------------------------ *
'* VERSION:  0.03  4-DEC-93                                                 *
'* ------------------------------------------------------------------------ *
'* COMMENTS:  This game was found on the PowerBASIC BBS. It seems that the  *
'*            original game was written for the APPLE II computer. As the   *
'*            listing says, it was converted to GW-BASIC (MicroSoft) by     *
'*            Donna and Gary McCoy at an unknown date. I changed the least  *
'*            necessary to make it run under PowerBASIC 3.00c. Otherwise,   *
'*            this is a nice example for the kind of code that reminds of   *
'*            the Italian antipasto Spaghetti. It is not easy to redo it    *
'*            nicely structured without jump labels as is possible with     *
'*            PowerBASIC. I wonder whether those C-buffs always bragging    *
'*            about structured programming know that PowerBASIC can do that *
'*            as well, and without utility programs that fix the curly      *
'*            bracket mess. Besides, FORTH is the ultimate in structured    *
'*            programming (sorry Nik. Wirth, I was born just over the road  *
'*            where you invented Pascal, but that was more than 20 years    *
'*            earlier).                                                     *
'* As far as this PB3 source code is concerned, I give it to the Public     *
'* Domain as Freeware. Claims from the unknown original author(s) and the   *
'* McCoys are to be respected. The lower cased commands and remarks and     *
'* the compiler directives are guaranteed to be from me and thus free.      *
'* ------------------------------------------------------------------------ *
'* VARIABLES ASSIGNMENT: I couldn't figure out everything on this program,  *
'*                       but a few variables seem to have that function:    *
'* M(x,y) - Maze                                                            *
'* X,Y    - Rat's position in maze                                          *
'* CH     - Cheat counter, how many times [ESC] was pressed to see top view *
'* H      - Number of horizontal rooms                                      *
'* V      - Number of vertical rooms                                        *
'* W(n)   - May store the way taken                                         *
'* NM     - Number of Moves                                                 *
'* A      - Auxiliary variable for X-position                               *
'* B      - Auxiliary variable for Y-position                               *
'* R      - Auxiliary variable for X-position                               *
'* S      - Auxiliary variable for Y-position                               *
'* ======================================================================== *
'* AUTHOR: Hans-Ruedi H. Wernli, Pletschgasse, CH-3952 Susten, Switzerland. *
'****************************************************************************
'
' 931204 0906
' COMPILER DIRECTIVES
'----------------------------------------------------------------------------
'
'$cpu 8086               '8086/80286/80386
'$debug map off          'on/off
'$debug path off         'on/off
'$debug unit off         'on/off
'$debug pbdebug off      'on/off
'$dim none               'all/array/none
'$DYNAMIC                '$STATIC
'$error all off          'bounds/numeric/overflow/stack/all on/off
'$event off              'on/off
'$float procedure        'emulate/npx/procedure
'$lib com-,lpt-,graph+,cga+,ega-,vga-,herc-,fullfloat-,iprint-
'$optimize speed         'size/speed
'$option cntlbreak off   'cntlbreak/gosub on/off
'$stack 1536             '1536...32767
'$com 0                  '0...32767
'$sound 1                '1...4096
'$string 2               '1/2/4/8/16/32
'$compile exe            'memory/exe/chain/unit
'
DEF FNM (X) = INT(X) - INT(INT(X) / 2) * 2 'precompile time, thankyou.
'
DIM M(52, 52)           '-- This must be added for the later REDIM statement
DIM W(400)              '-- ditto
'
0  REM MODIFIED FOR USE ON THE IBM-PC
1  REM BY GARY & DONNA MCCOY
'
'2 KEY OFF               -- Replaced ON KEY(n) GOSUB at 18400 hence
'3 CLEAR,,20000          -- This is like CLEAR and $STACK 20000. It was
'                        -- needed because of the ON KEY (n) GOSUB statments
'                        -- in lines 18400 to 18800. They have no returns!
'                        -- That part has been rewritten.
'
4 SCREEN 0,0,0: WIDTH 40
'                        -- The following two lines are to make maze setup
'                        -- more random.
A% = VAL(RIGHT$(TIME$, 2)) + VAL(MID$(TIME$, 4, 2)) + VAL(LEFT$(DATE$, 2))
RANDOMIZE A%
Abort% = 0
CMAZ = 2: CROD = 1      '-- Colors for Maze / Rodent (& path)
'
200 GOTO 6400
'
'------------------ Subroutine draws the Rat-Perspective --------------------
'
800 N = 2: A = H: B = V: FF = 2 ^ (F - 1): KTOP = 0
900 SCREEN 1: COLOR 0, 1: CLS
1000 Z = M(A, B) * FF
1200  IF FNM(Z / 16) = 0 THEN 1600
1300 RL = -1: GOSUB 5400
1400  GOTO 2000
1600 W = M(A + S, B - R) * FF
1700  IF FNM(W / 128) = 0 THEN 2000
1800 RL = -1: GOSUB 4600
2000  IF FNM(Z / 64) = 0 THEN 2400
2100 RL = 1: GOSUB 5400
2200  GOTO 2800
2400 W = M(A - S, B + R) * FF
2500  IF FNM(W / 128) = 0 THEN 2800
2600 RL = 1: GOSUB 4600
2800  IF FNM(Z / 128) = 1 THEN 3400
3000 N = N + 1: IF N > 8 THEN 3500
3100 A = A + R: B = B + S: IF B < 2 THEN 3500
3200  GOTO 1000
3400  GOSUB 3800
3500  RETURN
'---------------- Perspective of Rodent (RodAnt! Hehe) done -----------------
'
'------------ Subroutine "Draw-1" called from Subroutine at 800 -------------
'
3800  PSET (VX + DX(N), YU(N)), CMAZ
3900  LINE (VX + DX(N), YU(N))-(VX + DX(N), YD(N)), CMAZ
4000  LINE (VX + DX(N), YD(N))-(VX - DX(N), YD(N)), CMAZ
4100  LINE (VX - DX(N), YD(N))-(VX - DX(N), YU(N)), CMAZ
4200  LINE (VX - DX(N), YU(N))-(VX + DX(N), YU(N)), CMAZ
4300  RETURN
'------------------------ End of Subroutine "Draw-1" ------------------------
'
'------------ Subroutine "Draw-2" called from Subroutine at 800 -------------
'
4600  PSET (VX + RL * DX(N - 1), YU(N)), CMAZ
4700  LINE (VX + RL * DX(N - 1), YU(N))-(VX + RL * DX(N), YU(N)), CMAZ
4800  LINE (VX + RL * DX(N), YU(N))-(VX + RL * DX(N), YD(N)), CMAZ
4900  LINE (VX + RL * DX(N), YD(N))-(VX + RL * DX(N - 1), YD(N)), CMAZ
5000  RETURN
'------------------------ End of Subroutine "Draw-2" ------------------------
'
'------------ Subroutine "Draw-3" called from Subroutine at 800 -------------
'
5400  PSET (VX + RL * DX(N - 1), YU(N - 1)), CMAZ
5500  LINE (VX + RL * DX(N - 1), YU(N - 1))-(VX + RL * DX(N), YU(N)), CMAZ
5600  LINE (VX + RL * DX(N), YU(N))-(VX + RL * DX(N), YD(N)), CMAZ
5700  LINE (VX + RL * DX(N), YD(N))-(VX + RL * DX(N - 1), YD(N - 1)), CMAZ
5800  IF N > 2 THEN LINE (VX + RL * DX(N - 1), YD(N - 1))-(VX + RL * DX(N - 1), YU(N - 1)), CMAZ
5900  RETURN
'------------------------ End of Subroutine "Draw-3" ------------------------
'
'===================== The Main program continues here ======================
'
'------------------- The opening Screen with instructions -------------------
'
6400  CLS : COLOR 9, 0: LOCATE 6, 12: PRINT "YOU ARE THE RAT!":    'delay 2
6402  SLEEP 1
6405  LOCATE 4, 1: PRINT "   A DIFFERENT PERSPECTIVE ON MAZES.  ": 'delay 2
6410  LOCATE 1, 1: PRINT "FROM THE COMPUSERVE APPLE USERS' GROUP"
6420  LOCATE 2, 1: PRINT "        PUBLIC ACCESS DATABASE        "
6425  LOCATE 17, 1: PRINT "----------------------------------------"
6430  LOCATE 18, 1: PRINT "    USE <- AND -> OR [ AND ] TO TURN    "
6440  LOCATE 19, 1: PRINT " /  TO MOVE FORWARD"
6450  LOCATE 20, 1: PRINT "   TOGGLES TOP VIEW (TO CHEAT)  "
6455  LOCATE 21, 1: PRINT "   TO QUIT : <=> TOGGLES ASCII PLOT  "
'6500  DEF FNM (X) = INT(X) - INT(INT(X) / 2) * 2 'qBasic; moved up
6600  LOCATE 15, 1: FX = 36: INPUT "PLEASE ENTER MAZE SIZE (H,V) "; H, V
6700 H = INT(H): V = INT(V)
6800  IF H > 2 AND H < 51 AND V > 2 AND V < 51 THEN 7000
6900  PRINT "2 1 THEN I = INT(RND(1) * I) + 1
10100  ON C(I) GOTO 10300, 10800, 11300, 11800
10300 M(R, S) = M(R, S) - FNM(M(R, S) / 1) * 1
10400 R = R - 1
10500 M(R, S) = M(R, S) - FNM(M(R, S) / 4) * 4
10600  GOTO 13400
10800 M(R, S) = M(R, S) - FNM(M(R, S) / 8) * 8
10900 S = S - 1
11000 M(R, S) = M(R, S) - FNM(M(R, S) / 2) * 2
11100  GOTO 13400
11300 M(R, S) = M(R, S) - FNM(M(R, S) / 4) * 4
11400 R = R + 1
11500 M(R, S) = M(R, S) - FNM(M(R, S) / 1) * 1
11600  GOTO 13400
11800 M(R, S) = M(R, S) - FNM(M(R, S) / 2) * 2
11900 S = S + 1
12000 M(R, S) = M(R, S) - FNM(M(R, S) / 8) * 8
12100  GOTO 13400
12300  IF D = -1 THEN 12700
12400  IF R <> H THEN 13100
12500  IF S <> V THEN 13000
12600 R = 2: S = 2: GOTO 13200
12700  IF R <> 2 THEN 13100
12800  IF S <> V THEN 13000
12900 R = H: S = 2: GOTO 13200
13000 S = S + 1: D = -D: GOTO 13200
13100 R = R + D
13200  IF M(R, S) = 15 THEN 12300
13300  GOTO 9000
13400  NEXT IW
13500 MH = H: MV = V
13700 I = INT(RND(1) * (MH - 1)) + 2
13800 M(I, 1) = 0
13900 M(I, 2) = M(I, 2) - FNM(M(I, 2) / 8) * 8
14000 H = INT(RND(1) * (MH - 1)) + 2
14100 H1 = H: V1 = V
14300  COLOR 18: LOCATE 23, 12: PRINT "MAZE COMPLETED.": COLOR 9
14400  GOTO 17000
'========================== The Maze is ready now ===========================
'
'----------------- ASCII text character plotter subroutine ------------------
'-- Copy of cheat (Gods-eye view) display below (doesnt draw rat).
'-- PSETs become LOCATE/PRINT; LINEs become L-loops. :)
'----------------------------------------------------------------------------
'
KPLOT:
 IF KTOP = 2 THEN GOSUB 800: RETURN
 HZ = INT(TX / MH): VZ = INT(TY / MV): KTOP = 2
 SCREEN 0,0,0: WIDTH 80, 50: COLOR 11, 0, 0: CLS
 LOCATE 48, 1: PRINT "...": PRINT "Screaming CuckooBroad Associates";
 ISO8601$ = MID$(DATE$, 7, 4) + "-" + MID$(DATE$, 1, 2) + MID$(DATE$, 3, 3)
 PRINT SPACE$(7); MH - 1; "x"; MV - 1; "Maze "; ISO8601$; " "; TIME$
  LOCATE (1 + VZ), (1 + HZ): PRINT MZ$
  FOR L = 1 + VZ TO MV * VZ + 1: LOCATE L, 1 + HZ: PRINT MZ$: NEXT L
  FOR J = 1 TO MV: FOR I = 2 TO MH
   N = M(I, J): X = I * HZ + 1: Y = J * VZ + 1
   IF FNM(N / 2) <> 0 THEN GOSUB KHORZ
   IF FNM(N / 4) <> 0 THEN GOSUB KVERT
  NEXT I, J
RETURN
KHORZ:
   LOCATE Y, X: PRINT MZ$
   FOR L = X TO X - HZ STEP -1: LOCATE Y, L: PRINT MZ$: NEXT L
RETURN
KVERT:
   LOCATE Y, X: PRINT MZ$
   FOR L = Y TO Y - VZ STEP -1: LOCATE L, X: PRINT MZ$: NEXT L
RETURN
'
'---------------- Subroutine draws "God's-eye view" of Maze -----------------
'-- (I got that expression for a map from an article in the magazine
'-- "Aviation Week & Space Technology" (McGraw-Hill), 29 November 1993, p57.
'-- "Air Warrior Training System adds Realism to Exercises". It's the left
'-- console of Air Warrior/National Training Center at Nellis Air Force Base
'-- in Nevada. Boy, what computer games they've got there!
'-- Oh, Lloyd and Erik: they are still working out software glitches.)
'----------------------------------------------------------------------------
'
14700 IF KTOP = 1 THEN GOSUB 800: RETURN
14710 HZ = INT(MX / MH): VZ = INT(MY / MV): KTOP = 1
14800 SCREEN 1: COLOR 0, 1: CLS
14850 CH = CH + 1
14900  PSET (1 + HZ, 1 + VZ), CMAZ
15000  LINE (1 + HZ, 1 + VZ)-(1 + HZ, MV * VZ + 1), CMAZ
15100  FOR J = 1 TO MV: FOR I = 2 TO MH
15200   N = M(I, J): X = I * HZ + 1: Y = J * VZ + 1
15300   IF FNM(N / 2) = 0 THEN 15700
15500   PSET (X, Y), CMAZ
15600   LINE (X, Y)-(X - HZ, Y), CMAZ
15700   IF FNM(N / 4) = 0 THEN 16100
15900   PSET (X, Y), CMAZ
16000   LINE (X, Y)-(X, Y - VZ), CMAZ
16100  NEXT I, J
16200 '------------------------( Draw the Rat )------------------------------
16300  X = H * HZ - 1: Y = V * VZ - 1
16400  PSET (X + 1, Y + 1), CROD
16500  LINE (X + 1, Y + 1)-(X - HZ + 2, Y - VZ + 2), CROD
16600  PSET (X - HZ + 2, Y + 1), CROD
16700  LINE (X - HZ + 2, Y + 1)-(X + 1, Y - VZ + 2), CROD
16800 RETURN
'------------------------- End of "God's-eye view" --------------------------
'
'===================== The Main program continues here ======================
'
17000  FOR X = 1 TO MH: FOR Y = 1 TO MV
17100 M(X, Y) = M(X, Y) + M(X, Y) * 16
17200  NEXT Y, X
17500 F = INT(RND(1) * 4) + 1
17600  ON F GOTO 17700, 17800, 17900, 18000
17700 R = 0: S = -1: GOTO 18100
17800 R = 1: S = 0: GOTO 18100
17900 R = 0: S = 1: GOTO 18100
18000 R = -1: S = 0
18100  GOSUB 800
'
'------------------------ Start of outer input loop -------------------------
'
'18300 DEF SEG : POKE 106,0     '-- I couldn't figure out that one, but
18300 REM                       '-- seems obsolete. Had to put a label here
'
'------------------------- Start of Key-Input loop --------------------------
'
'18400 WHILE NOT instat: WEND            '-- This key-scheme is more efficient
'      IK$ = INKEY$                      '-- particularly on stack usage
18400 DO: IK$ = INKEY$: LOOP UNTIL IK$ <> ""     '-- qBasic
      IF LEN(IK$) = 2 THEN IK$ = MID$(IK$, 2, 1) '-- qBasic
      SELECT CASE IK$
'       CASE CHR$(0,75)                 '-- Left arrow key
'         GOTO 19100
'       CASE CHR$(0,77)                 '-- Right arrow key
'         GOTO 19400
	CASE CHR$(75)
	  GOTO 19100                    '-- Left arrow key
	CASE CHR$(77)
	  GOTO 19400                    '-- Right arrow key
	CASE "["
	  GOTO 19100                    '-- Left bracket key
	CASE "]"
	  GOTO 19400                    '-- Right bracket key
	CASE " "
	  GOTO 20100                    '-- Spacebar
	CASE CHR$(72)
	  GOTO 20100                    '-- Up arrow key
	CASE CHR$(27)
	  GOTO 21300                    '-- Escape key
	CASE "="
	  GOTO 21410                    '-- Equals key
	CASE "q"                        '-- q key to quit should the
	   Abort% = -1                  '-- player get fed up with it
	   GOTO 21500
      END SELECT
'
'18400 IK$=INKEY$                       -- Replaced with the above
'18410 KEY(12) ON                       -- We are not working with
'18420 KEY(13) ON                       -- KEYs here to prevent that
'18500 ON KEY(12) GOSUB 19100           -- disgusting ON KEY(n) GOSUB
'18600 ON KEY(13) GOSUB 19400           -- without RETURNs
'18700 IF IK$ = " " THEN 20100
'18800 IF IK$ = CHR$(27) THEN 21300
'
18900 GOTO 18400
'-------------------------- End of Key Input loop ---------------------------
'
19100 F = F - 1: IF F < 1 THEN F = 4             '-- Turn
19200  GOTO 19500
19400 F = F + 1: IF F > 4 THEN F = 1
19500  ON F GOTO 19600, 19700, 19800, 19900
19600 R = 0: S = -1: GOTO 21000
19700 R = 1: S = 0: GOTO 21000
19800 R = 0: S = 1: GOTO 21000
19900 R = -1: S = 0: GOTO 21000
20100 Z = M(H, V)                                '-- Forward
20200 T = Z * 2 ^ (F - 1): T = FNM(T / 128)
20300  IF T = 0 THEN 20600
20500   GOTO 18300
20600 NM = NM + 1: LOCATE 22, 24: PRINT "MOVE "; NM
'20650 FOR Q=1 TO 500:NEXT      '-- Replaced by delay for even fast machines
'delay .25
20700  IF NM < 400 THEN W(NM) = F
20800 H = H + R: V = V + S
20900  IF V < 2 THEN 21500
21000  GOSUB 800                '-- Plot RatView
21100  GOTO 18300
21300  GOSUB 14700              '-- Plot GodView
21400  GOTO 18300
21410  GOSUB KPLOT              '-- Plot ASCII TextView!
21420  GOTO 18300
'------------------------- End of outer input loop --------------------------
'-- Loops to POKE, what for? More malintentioned memory manipulation...
'----------------------------------------------------------------------------
'
'-------------------- End of Game, show number of moves ---------------------
'
21500  SCREEN 1: COLOR 0, 0: CLS '-- Black BG Brown FG
KTOP = 0
IF Abort% THEN                  '-- Added this one if player gets tired
 LOCATE 12, 6
 PRINT "AWWW...YOU QUIT AFTER"; NM; "STEPS."
ELSE
 LOCATE 12, 6
 PRINT "CONGRATS, IT TOOK YOU"; NM; "STEPS."
 IF CH = 1 THEN LOCATE 14, 9: PRINT "(BUT YOU CHEATED ONCE.)"
 IF CH > 1 THEN LOCATE 14, 8: PRINT "(BUT YOU CHEATED"; CH; "TIMES.)"
END IF
'21560 FOR I=1 TO 5000:NEXT     '-- Replaced by delay
'delay 2
21570 LOCATE 23, 14: PRINT ""
21580 DO: IK$ = INKEY$: LOOP UNTIL IK$ <> ""
21600 '-----------------------( Plot the path )------------------------------
21700 V = V1: H = H1: GOSUB 14700
21900 X = INT(H * HZ - HZ / 2) + 1: Y = INT(V * VZ - VZ / 2) + 1
22000  PSET (X, Y), CROD
22100  FOR N = 1 TO NM
22200  IF N > 400 THEN 22900
22300 F = W(N)
22400  IF F = 1 THEN V = V - 1
22500  IF F = 2 THEN H = H + 1
22600  IF F = 3 THEN V = V + 1
22700  IF F = 4 THEN H = H - 1
22800  LINE (X, Y)-(INT(H * HZ - HZ / 2) + 1, INT(V * VZ - VZ / 2) + 1), CROD
22850 X = INT(H * HZ - HZ / 2) + 1: Y = INT(V * VZ - VZ / 2) + 1
22900  NEXT N
'
'----------------- Replaced the following to add a way out ------------------
'
'22920 LOCATE 1,1:PRINT "PRESS ANY KEY TO CONTINUE"
'22950 IK$=INKEY$
'23000  KEY(12) OFF:KEY(13) OFF: IF IK$ = "" THEN 22950
'
22920 LOCATE 1, 1               '-- Replaced the above to be able to end game
PRINT " for another game or  to Quit"
DO: IK$ = INKEY$
LOOP UNTIL (IK$ = CHR$(13) OR IK$ = "q" OR IK$ = "Q")
IF IK$ = CHR$(13) THEN
23100  CLEAR : GOTO 4
END IF
'
'-------------------- Reset Screen and return to OpSys ----------------------
'
SCREEN 0,0,0: WIDTH 80: COLOR 7, 0: CLS
PRINT
PRINT SPACE$(16); "      Original Game for Apple II Computer       "
PRINT
PRINT SPACE$(16); "    Converted into GW-BASIC for PC/MS-DOS by    "
PRINT SPACE$(16); "              Gary and Donna McCoy              "
PRINT
PRINT SPACE$(16); "       Rewritten for PowerBASIC 3.00c by        "
PRINT SPACE$(16); "              Hans-Ruedi H. Wernli              "
PRINT SPACE$(16); "PCMAZE found on PowerBASIC BBS ++1 813 629 91 45"
PRINT
PRINT SPACE$(16); "           Adapted for qBasic 1.1 by            "
PRINT SPACE$(16); "        Screaming CuckooBroad Associates        "
PRINT SPACE$(16); "  PBMAZE found via HotBot at ftp://ftp.leo.org  "
PRINT
PRINT
PRINT
PRINT SPACE$(16); "        (Please press any key to exit.)         "
'delay 5
DO: IK$ = INKEY$: LOOP UNTIL IK$ <> ""
CLS
SYSTEM
'
50000  REM
'
'=====================-<931204 HoroSoft, Switzerland>-=======================
'
'--( pam )--------!---------!---------O---------!---------!---------( aze )--
END

GPL
Last update: 2013feb08pm2013gmt-0800 © 2013 Screaming CuckooBroad Associates

Free Web Hosting
<noscript> <!-- ooo