home *** CD-ROM | disk | FTP | other *** search
/ Source Code 1994 March / Source_Code_CD-ROM_Walnut_Creek_March_1994.iso / compsrcs / games / vmsnet / mineswp1 / part01 < prev    next >
Text File  |  1992-06-16  |  47KB  |  1,508 lines

  1. Newsgroups: vmsnet.sources.games
  2. Path: uunet!munnari.oz.au!bruce.cs.monash.edu.au!monu6!vcp1.vcp.monash.edu.au!pb
  3. From: pb@vcp1.vcp.monash.edu.au (Peter Bury)
  4. Subject: Minesweeper for VMS v1.01 part1/1
  5. Message-ID: <1992Jun17.135711.1@vcp1.vcp.monash.edu.au>
  6. Lines: 1497
  7. Sender: news@monu6.cc.monash.edu.au (Usenet system)
  8. Organization: 
  9. Date: Wed, 17 Jun 1992 03:57:11 GMT
  10.  
  11. Minesweeper
  12.  
  13.  
  14. This is a reverse-engineered version of the Minesweeper for Windows program.
  15. It runs on VT100 compatible terminals under VMS.
  16.  
  17. Conversion for VAX BASIC by Peter Bury, April 1992
  18. Reposted, as original never got beyond Monash Clayton campus
  19. Usual disclaimers apply!
  20. $! ------------------ CUT HERE -----------------------
  21. $ v='f$verify(f$trnlnm("SHARE_VERIFY"))'
  22. $!
  23. $! This archive created by VMS_SHARE Version 7.2-007  22-FEB-1990
  24. $!   On 15-JUN-1992 14:53:33.62   By user PB 
  25. $!
  26. $! This VMS_SHARE Written by:
  27. $!    Andy Harper, Kings College London UK
  28. $!
  29. $! Acknowledgements to:
  30. $!    James Gray       - Original VMS_SHARE
  31. $!    Michael Bednarek - Original Concept and implementation
  32. $!
  33. $! TO UNPACK THIS SHARE FILE, CONCATENATE ALL PARTS IN ORDER
  34. $! AND EXECUTE AS A COMMAND PROCEDURE  (  @name  )
  35. $!
  36. $! THE FOLLOWING FILE(S) WILL BE CREATED AFTER UNPACKING:
  37. $!       1. BUILD.COM;41
  38. $!       2. GET_CHAR.BAS;9
  39. $!       3. HELP_MATE.BAS;2
  40. $!       4. MENU.BAS;25
  41. $!       5. MINESWEEPER.BAS;22
  42. $!       6. MINESWEEPER.HLP;3
  43. $!       7. MSW_SCORE_FILES.BAS;11
  44. $!       8. VID_ATTRIB.BAS;19
  45. $!
  46. $set="set"
  47. $set symbol/scope=(nolocal,noglobal)
  48. $f=f$parse("SHARE_TEMP","SYS$SCRATCH:.TMP_"+f$getjpi("","PID"))
  49. $e="write sys$error  ""%UNPACK"", "
  50. $w="write sys$output ""%UNPACK"", "
  51. $ if f$trnlnm("SHARE_LOG") then $ w = "!"
  52. $ ve=f$getsyi("version")
  53. $ if ve-f$extract(0,1,ve) .ges. "4.4" then $ goto START
  54. $ e "-E-OLDVER, Must run at least VMS 4.4"
  55. $ v=f$verify(v)
  56. $ exit 44
  57. $UNPACK: SUBROUTINE ! P1=filename, P2=checksum
  58. $ if f$search(P1) .eqs. "" then $ goto file_absent
  59. $ e "-W-EXISTS, File ''P1' exists. Skipped."
  60. $ delete 'f'*
  61. $ exit
  62. $file_absent:
  63. $ if f$parse(P1) .nes. "" then $ goto dirok
  64. $ dn=f$parse(P1,,,"DIRECTORY")
  65. $ w "-I-CREDIR, Creating directory ''dn'."
  66. $ create/dir 'dn'
  67. $ if $status then $ goto dirok
  68. $ e "-E-CREDIRFAIL, Unable to create ''dn'. File skipped."
  69. $ delete 'f'*
  70. $ exit
  71. $dirok:
  72. $ w "-I-PROCESS, Processing file ''P1'."
  73. $ if .not. f$verify() then $ define/user sys$output nl:
  74. $ EDIT/TPU/NOSEC/NODIS/COM=SYS$INPUT 'f'/OUT='P1'
  75. PROCEDURE Unpacker ON_ERROR ENDON_ERROR;SET(FACILITY_NAME,"UNPACK");SET(
  76. SUCCESS,OFF);SET(INFORMATIONAL,OFF);f:=GET_INFO(COMMAND_LINE,"file_name");b:=
  77. CREATE_BUFFER(f,f);p:=SPAN(" ")@r&LINE_END;POSITION(BEGINNING_OF(b));
  78. LOOP EXITIF SEARCH(p,FORWARD)=0;POSITION(r);ERASE(r);ENDLOOP;POSITION(
  79. BEGINNING_OF(b));g:=0;LOOP EXITIF MARK(NONE)=END_OF(b);x:=ERASE_CHARACTER(1);
  80. IF g=0 THEN IF x="X" THEN MOVE_VERTICAL(1);ENDIF;IF x="V" THEN APPEND_LINE;
  81. MOVE_HORIZONTAL(-CURRENT_OFFSET);MOVE_VERTICAL(1);ENDIF;IF x="+" THEN g:=1;
  82. ERASE_LINE;ENDIF;ELSE IF x="-" THEN IF INDEX(CURRENT_LINE,"+-+-+-+-+-+-+-+")=
  83. 1 THEN g:=0;ENDIF;ENDIF;ERASE_LINE;ENDIF;ENDLOOP;t:="0123456789ABCDEF";
  84. POSITION(BEGINNING_OF(b));LOOP r:=SEARCH("`",FORWARD);EXITIF r=0;POSITION(r);
  85. ERASE(r);x1:=INDEX(t,ERASE_CHARACTER(1))-1;x2:=INDEX(t,ERASE_CHARACTER(1))-1;
  86. COPY_TEXT(ASCII(16*x1+x2));ENDLOOP;WRITE_FILE(b,GET_INFO(COMMAND_LINE,
  87. "output_file"));ENDPROCEDURE;Unpacker;QUIT;
  88. $ delete/nolog 'f'*
  89. $ CHECKSUM 'P1'
  90. $ IF CHECKSUM$CHECKSUM .eqs. P2 THEN $ EXIT
  91. $ e "-E-CHKSMFAIL, Checksum of ''P1' failed."
  92. $ ENDSUBROUTINE
  93. $START:
  94. $ create 'f'
  95. X$! procedure to compile minesweeper for private or public use
  96. X$! procedure assumes you have set your default directory to where the files
  97. V are.
  98. X$! logical name pub will point to this, for compiling %includes
  99. X$ msg = "write sys$output"
  100. X$ where_is = f$environment("default")
  101. X$ define pub 'where_is'
  102. X$!
  103. X$ savevf = 'f$verify(0)'
  104. X$ inquire ans "Is this a local, private installation  `5By`5D?"
  105. X$ if ans .eqs. "N" then goto public
  106. X$ open/write file scorebase.bas
  107. X$ write file "scorebase$ = ""''where_is'"""
  108. X$ close file
  109. X$ set verify
  110. X$ bas minesweeper
  111. X$ bas help_mate
  112. X$ lin minesweeper,help_mate
  113. X$ bas msw_score_files
  114. X$ lin msw_score_files
  115. X$ run msw_score_files
  116. X$ set noverify
  117. X$ del scorebase.bas;*
  118. X$ msg "Include the lines "
  119. X$ msg "$ define mine_help ''where_is'`20
  120. X$ msg "$ minesweeper :== run ''where_is'minesweeper"
  121. X$ msg "in your login.com"
  122. X$ msg ""
  123. X$ inquire ans "Do you want others to be able to play?"
  124. X$ if ans .nes. "Y" .and. ans .nes. "YES" then goto fini
  125. X$ inquire ans "Group or World  (G or W)"
  126. X$ if ans .eqs. "G"
  127. X$ then
  128. X$   set prot=g:e pub:minesweeper.exe/log
  129. X$   set prot=g:r pub:minesweeper.hlp/log
  130. X$   set prot=g:rw pub:mine*score.da/log
  131. X$ else
  132. X$   if ans .eqs. "W"
  133. X$   then
  134. X$     set prot=w:e pub:minesweeper.exe/log
  135. X$     set prot=w:r pub:minesweeper.hlp/log
  136. X$     set prot=w:rw pub:mine*score.da/log
  137. X$   else
  138. X$     goto fini
  139. X$   endif
  140. X$ endif
  141. X$ msg "They will also need the commands"
  142. X$ msg "$ define mine_help ''where_is'"
  143. X$ msg "$ minesweeper :== run ''where_is'minesweeper"
  144. X$ msg ""
  145. X$ msg "You must also set the protection of this directory and the chain lead
  146. Ving"
  147. X$ msg "to it so that others have read access to the directory"
  148. X$ msg ""
  149. X$fini:
  150. X$ if savevf then $ exit  f$verify(1) + 1
  151. X$ exit 1
  152. X$!
  153. X$!
  154. X$public:
  155. X$! Notes for system managers
  156. X$!`20
  157. X$! The scoring section can be deleted completely, but adds much to
  158. X$! the fun while involving little overhead. Approximately 45 scores are kept
  159. V`20
  160. X$! for each of the three levels. The username is kept as part of the score,
  161. V so`20
  162. X$! that each user gets his/her invividual scores highlighted, but the name i
  163. Vs`20
  164. X$! never displayed.
  165. X$! The scoring system needs a directory that has world read access, but not
  166. X$! world execute. It will create three files  (one for each level) with
  167. X$! world read and write access. (NB. It is left to the system manager to set
  168. V`20
  169. X$! the protection of the directory itself to w:r to prevent wildcard`20
  170. X$! searching). The protection is only 'security through obscurity.' In `20
  171. X$! principle, users could write their own routines for updating these files,
  172. X$! so the file names and directories must not be known. Note that the only
  173. X$! reference to the directory is deleted later in this procedure.`20
  174. X$! The scoring files are VAX indexed files, indexed by score. As entries are
  175. X$! created and deleted, they may benefit from a convert/rebuild occasionally
  176. V.
  177. X$! Finally, if you don't want to add yet another logical name to the system,
  178. X$! then edit the word "mine_help" on line 91 in minesweeper.bas to
  179. X$! wherever you keep public games and their help files.
  180. X$ msg ""
  181. X$ msg "The scoring system needs a directory that has world read access,"
  182. X$ msg "but not world execute. "
  183. X$ msg "Please input the location where the scoring files will be kept"
  184. X$ inquire sys$score
  185. X$ msg "The following line will abort the procedure if directory does not exi
  186. Vst"
  187. X$ dir 'sys$score'*.da
  188. X$ open/write file scorebase.bas
  189. X$ write file "scorebase$ = ""''sys$score'"""
  190. X$ close file
  191. X$ set ver
  192. X$ bas minesweeper
  193. X$ bas msw_score_files
  194. X$ del scorebase.bas;*
  195. X$! all reference to the wherabouts of the scoring files has now disappeared.
  196. X$ bas help_mate
  197. X$ lin minesweeper,help_mate
  198. X$ set nover
  199. X$ msg "The executable and help will now be copied to a publically readable a
  200. Vrea"
  201. X$ inquire destn "Please input the public area for minesweeper.exe"
  202. X$ define where_to 'destn'`20
  203. X$ copy minesweeper.exe where_to/log
  204. X$ copy minesweeper.hlp where_to/log
  205. X$ msg "Their protection will now be set to w:e and w:r respectively"
  206. X$ set prot=w:e where_to:minesweeper.exe/log
  207. X$ set prot=w:r where_to:minesweeper.hlp/log
  208. X$ set ver
  209. X$ lin msw_score_files
  210. X$ run msw_score_files
  211. X$ set nover
  212. X$ msg "Their protection will now be set to w:rw"
  213. X$ set prot=w:rw 'sys$score'mine*score.da/log
  214. X$! let's try to get the message ok for logical names w/o colons
  215. X$ last_char = f$extract(f$length(destn)-1,1,destn)
  216. X$ if last_char .eqs. ":" .or. last_char .eqs. "`5D" then goto ok
  217. X$ destn = "''destn':"
  218. X$ok:
  219. X$ msg "Include the lines "
  220. X$ msg "$ define mine_help ''destn'"
  221. X$ msg "$ minesweeper :== run ''destn'minesweeper"
  222. X$ msg "in the sylogin.com for those who should be allowed to play"
  223. X$ msg ""
  224. X$ if savevf then $ exit  f$verify(1) + 1
  225. X$ exit 1
  226. $ CALL UNPACK BUILD.COM;41 72849256
  227. $ create 'f'
  228. X      ! ====================================================================
  229. V=
  230. X      !  GET_CHAR             Character input routines - no timeout, no echo
  231. X      !  gosub DO_GET return a character in INBUF
  232. X      !  from GET.BAS   MV circa sept 1986
  233. X      ! Mods                                            PB Oct 1987
  234. X      ! io$m_nofilter and virgin_got_flag added.
  235. X      ! no initial call to setup_get required`20
  236. X      ! control chars passed, except cC cO cQ cS cT cY.  CX changes to cU
  237. X      !=====================================================================
  238. V=
  239. X
  240. X      goto END_GET
  241. X      setup_get:
  242. X      external integer function`09sys$assign,`09&
  243. X`09`09`09`09sys$trnlog,`09&
  244. X`09`09`09`09sys$qiow
  245. X      external integer constant`09io$_readvblk,`09&
  246. X`09`09`09`09io$m_noecho,`09&
  247. X`09`09`09`09io$m_nofiltr,`09&
  248. X`09`09`09`09ss$_normal,`09&
  249. X`09`09`09`09ss$_notran
  250. X      common string inbuf  = 1 \ !  needs to be near start of program
  251. X      map (eqnam) string rsn_buf = 80
  252. X      map (iosb)  word io_sb(3)
  253. X      map (mask)  long tmask(1)
  254. X      tmask(0) = 0 \ tmask(1) = 0
  255. X      declare long sys_status, word chan, rsn_len, string dev_nam
  256. X      translate_routine:
  257. X      sys_status = sys$trnlog("sys$output", rsn_len, rsn_buf,,,,)
  258. X      select sys_status
  259. X`09  case ss$_normal
  260. X`09  case ss$_notran
  261. X`09  case else
  262. X`09`09print "error from"
  263. X`09`09print "sys$trnlog, error is";sys_status
  264. X     end select
  265. X      dev_nam = seg$(rsn_buf,1,rsn_len)
  266. X      assign_routine:
  267. X      sys_status = sys$assign(dev_nam, chan,,,)
  268. X      if (sys_status and 1%) <> 1
  269. X     then
  270. X       `09  print "error from sys$assign"
  271. X`09  print "error number is ";sys_status
  272. X     end if
  273. X      virgin_got_flag = 1
  274. X      return
  275. X      ! =========================================================
  276. X      !               Execute get command
  277. X      ! =========================================================
  278. X      do_get:
  279. X      if virgin_got_flag <> 1 then gosub setup_get end if
  280. X      sys_status = sys$qiow(, chan by value,`09`09&
  281. X`09`09`09      io$_readvblk+io$m_nofiltr+io$m_noecho by value, &
  282. X`09`09`09      io_sb() by ref,,,`09`09&
  283. X`09`09`09      inbuf by ref,`09`09&
  284. X`09`09`09      1% by value,,             &
  285. X`09`09`09      tmask() by ref,,)
  286. X      if (sys_status and 1%) = 0%
  287. X      then
  288. X`09  print "error from sys$qiow"
  289. X`09  print "error number is ";sys_status
  290. X      end if
  291. X      return
  292. X      END_GET:
  293. $ CALL UNPACK GET_CHAR.BAS;9 259875104
  294. $ create 'f'
  295. X100  sub helpmate (helpfile$,defselect)
  296. X      ! This was developed from help in multcomp,              PB july 87
  297. X      ! General  externally linkable subroutine to provide help screens for
  298. X      !   any program.
  299. X      ! Help text is in serial file whose name is passed to the routine.
  300. X      ! File is divided up into screens  line length max 75,`20
  301. X      !   of up to 16 lines (+title)each - lines 7 to 22 used for text,`20
  302. X      !   4,5,6 for title , lines 3 and 23 for boxing and line 24 for prompt
  303. V.
  304. X      !   Page number is printed on line 2 from char position 65
  305. X      ! single hash (#) on line denotes end of screen
  306. X      ! double hash (##) denotes end of file
  307. X      ! First line of each screen is used as topic title (max length 66),
  308. X      !   but if first line after # is blank, screen is regarded as continua
  309. Vtion
  310. X      !   of previous. Extra blank line automatically inserted after title.
  311. X      ! For defselect = 0 (the `60normal' mode) the standard menu program pr
  312. Vovides
  313. X      !   selection via menu.
  314. X      ! For defselect > 1 or if only one topic, get immediate display of the
  315. V`20
  316. X      !   topic pointed to by defselect
  317. X      ! For defselect < 1 default topic in menu is pointed to by -defselect
  318. X      ! Index of topic/screen provides entry to right place and screens/topi
  319. Vc
  320. X      ! NB all variables are local and unsaved
  321. X
  322. X      ! cater for  50 screens, 18 lines(16+title+#), 15 topics(16th is exit)
  323. X      dim h$(50,18), item$(16), length(50), topic (16)
  324. X      %include "pub:get_char"
  325. X      %include "pub:vid_attrib.bas"
  326. X      %include "pub:menu"
  327. X     `20
  328. X`09!==============================================================
  329. X`09!                 Read the help screens from file             !
  330. X`09!==============================================================
  331. X`09SETUP_HELP:
  332. X      !
  333. X    when error in
  334. X      open helpfile$ for input as #1, access read
  335. X       scrn = 0
  336. X       ntopics = 0
  337. X       lin = 1
  338. X      while 1 <> 2
  339. X        linput #1,a$
  340. X        a$ = trm$(a$)
  341. X        if a$ = "##" then       ! this is eof marker to exit loop
  342. X          h$(scrn,lin) = "#"
  343. X          length (scrn) = lin-1
  344. X          items = ntopics + 1
  345. X          item$(items) = "Exit help"
  346. X          topic(items) = scrn + 1
  347. X          goto finish1
  348. X        end if
  349. X        if a$ = "#" then
  350. X          length (scrn) = lin-1
  351. X          scrn = scrn + 1 \ lin = 1
  352. X        else
  353. X          if lin = 1 then`20
  354. X            if a$ <> "" then
  355. X              ntopics = ntopics + 1
  356. X              item$(ntopics) = a$`20
  357. X              topic(ntopics) = scrn
  358. X              lin = 2
  359. X            else
  360. X              !continuation screen
  361. X              lin = 2
  362. X            end if
  363. X          else
  364. X            h$(scrn,lin) = a$
  365. X            ! print ntopics;scrn;lin;h$(scrn,lin)`20
  366. X            lin = lin + 1
  367. X          end if
  368. X        end if
  369. X      next     `20
  370. X    use
  371. X      print "Error in reading in help file"
  372. X             print "Topic no. ";ntopics
  373. X            print "Screen no. ";scrn;
  374. X            print "Line no.";lin `20
  375. X            print a$
  376. X            if scrn > 50  then print "Too many screens" end if
  377. X            if lin > 17 then print "Too many lines on this screen" end if
  378. X      exit handler
  379. X    end when
  380. X
  381. X    finish1:
  382. X      close #1
  383. X
  384. X`09!==============================================================
  385. X`09!                  Program Help
  386. X`09!==============================================================
  387. X    HELP:
  388. X      if virgin_flag = 0 then`20
  389. X         gosub setup_get
  390. X         virgin_flag = 1
  391. X      end if
  392. X      top = 6
  393. X      if defselect < 0 then selected = -defselect else selected = 1 end if
  394. X      if defselect > 0 then`20
  395. X        selected = defselect`20
  396. X        scrn = topic(selected)
  397. X        goto menushow
  398. X      else`20
  399. X        if items = 2 then      !1 item plus exit
  400. X          goto menushow
  401. X        end if
  402. X      end if
  403. X  menuask:
  404. X      print rev;bold; posnt(68,2);"Help Menu   ";normal
  405. X      print posnt(1,4);cleos;      !should include in menu ?
  406. X        gosub menu
  407. X      if selected = items then goto finish end if
  408. X      scrn = topic(selected)
  409. X  menushow:
  410. X      ! Adjust header box
  411. X      print rev;bold; posnt(73,2);"Page ";
  412. X      print using "##";scrn+1;
  413. X      ! Print title line
  414. X      print posnt(1,5);cleos;normal;"   ";item$(selected);
  415. X      if scrn > topic(selected) then print "  (contd)"  end if
  416. X      ! Print the screen
  417. X      for lyne = 2 to length(scrn)
  418. X`09print posnt(4,lyne+5); h$(scrn,lyne);
  419. X      next lyne
  420. X      ! Pretty enclosure
  421. X      print rev;box(1,1,80,23);normal
  422. X      print posnt(25,24); "press `5Breturn`5D to continue";
  423. X      gosub do_get
  424. X      gosub CLEAR_PAGE
  425. X      scrn = scrn + 1
  426. X      if scrn < topic(selected+1) then`20
  427. X        go to menushow`20
  428. X      else`20
  429. X        if defselect > 0 then
  430. X          goto finish
  431. X        else
  432. X          selected = selected + 1
  433. X          goto menuask`20
  434. X        end if
  435. X      end if     `20
  436. X
  437. X`09CLEAR_PAGE:
  438. X`09`09print posnt(1,4);cleos;
  439. X`09return
  440. X
  441. X      finish:
  442. X      end sub
  443. $ CALL UNPACK HELP_MATE.BAS;2 2067421875
  444. $ create 'f'
  445. X ! MENU selection routine                                    PB & MV  Aug 19
  446. V86
  447. X ! MODS Oct 1987    1. TO ALLOW scrolling if wont fit on one screen
  448. X !                  2. Label and goto included`20
  449. X !
  450. X ! Assumes get_char is included in the main program (before menu)
  451. X !   also uses pub:vid_attrib`20
  452. X ! Data required:
  453. X !   ITEM$      array of text up to 66 characters from which selection is ma
  454. Vde
  455. X !   items      the number of items in the array
  456. X !   top        the line on the screen on which the first item will appear
  457. X !                minimum 3 if title and box required
  458. X ! Value returned:
  459. X !   selected   points to the item that has been selected
  460. X !
  461. X ! Options
  462. X !   if SELECTED <> 0, this will be the default position for selection
  463. X !   if TITLE$ is non-null string, it will be printed above the selections`2
  464. V0
  465. X !                                                      (double width)
  466. X !   menu_no_box non zero will suppress box draw
  467. X !   menu_no_instr non zero will suppress instruction line
  468. X !   menu_no_centre non zero will suppress centering on screen
  469. X !`20
  470. X ! Practical limit - more than 99 items cant be selected directly by 2 digit
  471. Vs
  472. X !
  473. X      goto menu_end
  474. X    menu:
  475. X      menu_longest = 0
  476. X      for menu_j = 1 to items
  477. X            if len(item$(menu_j)) > menu_longest then
  478. X                  menu_longest = len(item$(menu_j))
  479. X            end if
  480. X      next menu_j
  481. X ! calculate positions for box
  482. X      menu_longest = menu_longest + 9
  483. X      if menu_no_centre <> 0 then`20
  484. X        menu_lft = 3`20
  485. X        menu_rgt = menu_lft + menu_longest
  486. X        menu_title_posn = 1
  487. X      else
  488. X        menu_lft = int((80-menu_longest)/2)
  489. X        if menu_lft < 3 then menu_lft = 3 end if
  490. X        menu_rgt = 80 - menu_lft
  491. X        menu_title_posn = int(21-len(title$)/2)
  492. X      end if
  493. X      if title$ <> "" then`20
  494. X        print posnt(1,top-2);cleos;posnt(menu_title_posn,top-2); dbw;title$`
  495. V20
  496. X      end if
  497. X
  498. X      if selected <= 0 then selected = 1 end if
  499. X      if selected >= items then selected = items end if
  500. X      menu_no_of_lines = (23-top)
  501. X      if items > menu_no_of_lines then
  502. X        menu_bottom = 22
  503. X        multi_screen = 1
  504. X      else
  505. X        menu_bottom = top + items - 1
  506. X        multi_screen = 0
  507. X        menu_no_of_lines = items
  508. X      end if
  509. X
  510. X    menu_restart:
  511. X      gosub menu_screen_draw
  512. X      menu_2_digit_flag = 0
  513. X    menu_recurse:
  514. X      gosub DO_GET
  515. X      select inbuf
  516. X        case  "0" to "9"`20
  517. X          if menu_2_digit_flag = 0 then
  518. X            menu_2_digit_flag = 1
  519. X            numsofar = val(inbuf)
  520. X          else`20
  521. X            menu_2_digit_flag = 0
  522. X            numsofar = numsofar*10 + val(inbuf)
  523. X          end if
  524. X
  525. X          if numsofar >= menu_first and numsofar <= menu_last then
  526. X            print posnt(menu_lft,screen_line);"   ";
  527. X            selected = numsofar`20
  528. X            screen_line = top+selected-menu_first
  529. X            if multi_screen > 1 then screen_line = screen_line + 1 end if
  530. X            print posnt(menu_lft,screen_line);rev;"-->";normal;
  531. X          else
  532. X            if menu_2_digit_flag = 0 then
  533. X              if numsofar >= 1 then
  534. X                if numsofar > items then
  535. X                  print bel;
  536. X                  numsofar = items
  537. X                end if
  538. X                selected = numsofar`20
  539. X                gosub menu_screen_draw
  540. X              else
  541. X                menu_2_digit_flag = 0
  542. X                print bel;
  543. X              end if
  544. X            end if
  545. X          end if
  546. X        case ESC`20
  547. X          menu_2_digit_flag = 0
  548. X          gosub DO_GET
  549. X          gosub DO_GET
  550. X          if inbuf = "A" then                        ! up
  551. X            if screen_line > top then
  552. X              print posnt(menu_lft,screen_line);"   ";
  553. X              screen_line  = screen_line  - 1
  554. X              selected = selected - 1
  555. X              print posnt(menu_lft,screen_line );rev;"-->";normal;
  556. X              if screen_line = top and multi_screen > 1 then`20
  557. X                gosub menu_screen_draw
  558. X              end if
  559. X            else
  560. X              print chr$(7);
  561. X            end if
  562. X          else
  563. X            if inbuf = "B" then                   !down
  564. X              if screen_line  < menu_bottom then
  565. X                print posnt(menu_lft,screen_line);"   ";
  566. X                selected = selected + 1
  567. X                screen_line  = screen_line  + 1
  568. X                print posnt(menu_lft,screen_line );rev;"-->";normal;
  569. X                if screen_line  = menu_bottom and &
  570. X                      (multi_screen = 2 or multi_screen = 1) then`20
  571. X                  gosub menu_screen_draw
  572. X                end if
  573. X              else
  574. X                print chr$(7);
  575. X              end if
  576. X            end if
  577. X          end if
  578. X        case cr
  579. X          if menu_2_digit_flag = 1 and selected <> numsofar then
  580. X            print bel;
  581. X            selected = numsofar`20
  582. X            goto menu_restart
  583. X          else
  584. X            print posnt(1,menu_bottom+2);cleos;
  585. X            return
  586. X          end if
  587. X        case else
  588. X          print chr$(7);
  589. X          menu_2_digit_flag = 0
  590. X      end select
  591. X      goto menu_recurse
  592. X
  593. X    menu_screen_draw:
  594. X
  595. X      if menu_no_box = 0 then
  596. X     print posnt(1,top-1);cleos;box(menu_lft-2,top-1,menu_rgt+2,menu_bottom+
  597. V1);
  598. X      else
  599. X        print posnt(1,top);cleos;
  600. X      end if
  601. X
  602. X      if multi_screen = 0 then
  603. X        menu_first = 1
  604. X        menu_last = items
  605. X        for menu_j = menu_first to menu_last
  606. X          print posnt(menu_lft+4,top+menu_j-1);
  607. X          print using "##",menu_j;
  608. X          print ".  ";item$(menu_j);
  609. X        next menu_j
  610. X      else
  611. X        select selected
  612. X          case < menu_no_of_lines`20
  613. X            multi_screen = 1
  614. X            menu_first = 1
  615. X            menu_last = menu_no_of_lines - 1
  616. X            for menu_j = menu_first to menu_last
  617. X              print posnt(menu_lft+4,top+menu_j-1);
  618. X              print using "##",menu_j;
  619. X              print ".  ";item$(menu_j);
  620. X            next menu_j
  621. X            print posnt(menu_lft+4,menu_bottom);
  622. X            print "     More...";
  623. X          case > items - menu_no_of_lines + 1
  624. X            multi_screen = 3
  625. X            menu_first = items - menu_no_of_lines + 2
  626. X            menu_last = items
  627. X            print posnt(menu_lft+4,top);
  628. X            print "     Back...";
  629. X            for menu_j = menu_first to menu_last
  630. X              print posnt(menu_lft+4,top+menu_j+1-menu_first);
  631. X              print using "##",menu_j;
  632. X              print ".  ";item$(menu_j);
  633. X            next menu_j
  634. X          case else
  635. X            multi_screen = 2
  636. X            menu_first = 2
  637. X            while (selected - menu_first) >= menu_no_of_lines -2
  638. X              menu_first = menu_first + menu_no_of_lines - 2
  639. X            next
  640. X            menu_last = menu_no_of_lines + menu_first - 3
  641. X            print posnt(menu_lft+4,top);
  642. X            print "     Back...";
  643. X            for menu_j = menu_first to menu_last
  644. X              print posnt(menu_lft+4,top+menu_j+1-menu_first);
  645. X              print using "##",menu_j;
  646. X              print ".  ";item$(menu_j);
  647. X            next menu_j
  648. X            print posnt(menu_lft+4,menu_bottom);
  649. X            print "     More...";
  650. X        end select !
  651. X      end if
  652. X      if menu_no_instr = 0  then
  653. X        print posnt(1,24);"   Use arrow keys or type number to make selectio
  654. Vn,";
  655. X        print "  then press return";
  656. X      end if
  657. X !
  658. X      screen_line = top+selected-menu_first
  659. X      if multi_screen > 1 then screen_line = screen_line + 1 end if
  660. X      print posnt(menu_lft,screen_line );rev;"-->";normal;
  661. X      return
  662. X    menu_end:
  663. $ CALL UNPACK MENU.BAS;25 68299084
  664. $ create 'f'
  665. X! Minesweeper for vt100                        Peter Bury,  April 1992
  666. X!   Victorian College of Pharmacy (Monash University), Melbourne, Australia
  667. X! Instructions in Minesweeper.hlp
  668. X! link the program with pub:helpmate for the help file to be available.
  669. X! NB The logical pub: points to a public area on our VAX where these files
  670. X!    normally reside. The BUILD.COM procedure will take care of this.
  671. X%include "pub:vid_attrib"
  672. X%include "pub:get_char"
  673. X%include "scorebase"
  674. Xmap (user_id) string user_name = 12
  675. Xmap (score) integer scorehigh, string nm=35, who=12, dated = 9
  676. Xdim nm$(21), hscore(21), user_name$(21), when$(21)
  677. Xexternal integer function lib$getjpi
  678. Xexternal integer constant jpi$_username
  679. Xexternal integer function lib$get_symbol
  680. Xyes = 1
  681. Xno = 0
  682. Xmaxscores = 45      ! random erasing when reaches this
  683. X! Find out who this is for scoring system
  684. Xcall lib$getjpi(jpi$_username,,,,user_name,)
  685. Xflag$ = " " + bold + "X" + normal
  686. Xunknown$ = " ."
  687. Xstar$ = " *"
  688. Xrandom
  689. Xlevel = 1
  690. Xagain:
  691. Xprint cls
  692. Xprint cls;rev;box(1,1,80,3); bold;posnt(2,2);`20
  693. Xprint "VCP VAX                  ** Minesweeper **                       ";
  694. Xprint "      Mar 92 ";   normal;lf
  695. Xprint`20
  696. Xprint
  697. Xprint "1. Beginner"
  698. Xprint "2. Intermediate"
  699. Xprint "3. Expert"
  700. Xprint "4. Custom"
  701. Xprint "5. Instructions"
  702. Xprint "6. High Scores"
  703. Xprint "7. Quit"
  704. Xprint
  705. Xprint "Please select option or desired level  `5B"; str$(level);"`5D";
  706. Xinput a$
  707. Xwhen error in
  708. X  newlevel = val(a$)
  709. Xuse
  710. X  if ERR = 50 then continue fmterr else exit handler end if
  711. Xend when
  712. Xgoto setupp
  713. X
  714. Xfmterr:
  715. Xprint bel
  716. Xgoto again
  717. X
  718. Xsetupp:
  719. Xif newlevel > 0 then level = newlevel end if
  720. Xselect level
  721. X  case 1
  722. X    nny = 10
  723. X    nnx = 10
  724. X    nmine = 10
  725. X    scorefile$ = scorebase$ + "mine1score.da"
  726. X  case 2
  727. X    nny = 16
  728. X    nnx = 16
  729. X    nmine = 40
  730. X    scorefile$ = scorebase$ + "mine2score.da"
  731. X  case 3
  732. X    nny = 16
  733. X    nnx = 30
  734. X    nmine = 99
  735. X    scorefile$ = scorebase$ + "mine3score.da"
  736. X  case 4
  737. Ximposs:
  738. X    input "Height (3 - 18)";nny`20
  739. X    if nny < 3 or nny > 18 then
  740. X      print bel; "Out of range, try again"
  741. X      goto imposs
  742. X    end if
  743. X    input "Width  (3 - 36)";nnx
  744. X    if nnx < 3 or nnx > 36 then
  745. X      print bel; "Out of range, try again"
  746. X      goto imposs
  747. X    end if
  748. X    input "Number of mines"; nmine`20
  749. X    if nmine < 0 or nmine > nnx*nny-1 then
  750. X      print bel; "Out of range, try again"
  751. X      goto imposs
  752. X    end if
  753. X    scorefile$ = ""
  754. X  case 5
  755. X    call helpmate("mine_help:minesweeper.hlp",0)
  756. X    level = 1
  757. X    goto again
  758. X  case 6
  759. X    print " Select Level for score display";lf
  760. X    print "1. Beginner"
  761. X    print "2. Intermediate"
  762. X    print "3. Expert"
  763. X    print`20
  764. X    input newlevel
  765. X    newlevel = int(newlevel)
  766. X    if newlevel >=1 and newlevel <= 3 then
  767. X      level = newlevel`20
  768. X      scorefile$ = scorebase$ + "mine" + str$(level) + "score.da"
  769. X      gosub score_read
  770. X    end if
  771. X    goto again
  772. X  case 7
  773. X    goto fini
  774. X  case else
  775. X    goto again
  776. Xend select
  777. Xnn1 = nnx*nny
  778. Xdim arr$ (nnx,nny), mine(nnx,nny), cleared(nnx,nny)
  779. Xdim x1(nn1),y1(nn1)
  780. X! Positions x & y from bottom left
  781. X! Array mine(x,y) set to -1 for mine or the digit representing no.`20
  782. X!  neighbours
  783. X! Array arr$(x,y) 2 characters wide is what shows on the screen
  784. X! Array cleared(x,y) keeps a record of what has been cleared to date.
  785. Xntofind = nn1-nmine
  786. Xupset = 2            ! distance above bottom of screen
  787. X
  788. X!      Lay the minefield
  789. Xinit:
  790. Xarr$(x,y) = unknown$            for x = 1 to nnx      for y = 1 to nny
  791. Xunfound = 0
  792. Xuntil unfound = nmine
  793. X  y = int(nny*rnd + 1)
  794. X  x = int(nnx*rnd + 1)
  795. X  if y = int((nny+1)/2) and x = int((nnx+1)/2) then
  796. X    ! keep centre square free to start
  797. X  else
  798. X    if mine(x,y) = 0 then
  799. X      mine(x,y) = -1
  800. X      unfound = unfound + 1
  801. X    end if
  802. X  end if
  803. Xnext
  804. X
  805. X! Count how many are adjacent to each square and store in array mine(x,y)
  806. Xfor y = 1 to nny
  807. X  for x = 1 to nnx
  808. X    if mine(x,y) >= 0 then
  809. X      n = 0
  810. X      for j = x-1 to x+1
  811. X        for k = y-1 to y+1
  812. X          if j >=1 and j <= nnx and k >=1 and k <= nny then
  813. X            if mine(j,k) < 0 then
  814. X              n = n + 1
  815. X            end if
  816. X          end if
  817. X        next k
  818. X      next j
  819. X      mine(x,y) = n
  820. X    end if
  821. X  next x
  822. Xnext y`20
  823. X
  824. Xy = int((nny+1)/2)
  825. Xx = int((nnx+1)/2)
  826. Xgosub redraw
  827. Xstarted = no
  828. X
  829. X!            Returns here after each keystroke is processed
  830. Xwhile ntofind > 0`20
  831. Xprint posnb(2*x,y +upset);arr$(x,y);cb;
  832. Xgosub DO_GET
  833. Xif started = no then
  834. X  started = yes
  835. X  start_time = time(0)
  836. Xend if
  837. Xprint posnt(1,2); "Time taken:   ";time(0) - start_time; "      ";
  838. Xselect inbuf
  839. X  case "Q","q"
  840. X    print bel;posnt (1,1);cleol;bold;
  841. X    input "Are you sure you want to quit  `5BN`5D";an$
  842. X    print normal;
  843. X    if edit$(left$(an$,1),32) = "Y" then
  844. X      level = 7
  845. X      goto again
  846. X    else
  847. X      gosub redraw
  848. X    end if
  849. X  case " "
  850. X    x1 = x
  851. X    y1 = y
  852. X    gosub clear_it
  853. X  case chr$(23),chr$(18)
  854. X    gosub redraw
  855. X  case "p", "P"
  856. X    pstart = time(0)
  857. X    print cls
  858. X    print posnb(1,2); "Press P to resume";
  859. X    inbuf = ""
  860. X    until inbuf = "P" or inbuf = "p"
  861. X      gosub do_get
  862. X    next
  863. X    start_time = start_time + time(0) - pstart
  864. X    gosub redraw
  865. X  case "F","f","M","m","X","x"
  866. X    if arr$(x,y) = flag$  then
  867. X      arr$(x,y) = unknown$
  868. X      cleared(x,y) = no
  869. X      unfound = unfound + 1
  870. X    else
  871. X      if arr$(x,y) = unknown$ then
  872. X        arr$(x,y) = flag$`20
  873. X        cleared(x,y) = yes
  874. X        unfound = unfound - 1
  875. X      end if
  876. X    end if
  877. X    print posnt(1,1); "Mines to find:";unfound;"  "
  878. X    print posnb (2*x,y+upset); rev; arr$(x,y);normal;
  879. X  case "C","c"
  880. X    if arr$(x,y) <> flag$  and arr$(x,y) <> unknown$ then
  881. X      known = 0                              ! must be a number
  882. X      for x1 = x-1 to x+1
  883. X        for y1 = y-1 to y+1
  884. X          if x1 >=1 and x1 <= nnx and y1 >=1 and y1 <= nny then
  885. X            if arr$(x1,y1) = flag$ then
  886. X              known = known + 1
  887. X            end if
  888. X          end if
  889. X        next y1
  890. X      next x1
  891. X      if known = mine(x,y) then`20
  892. X        gosub safe_round
  893. X      else
  894. X        gosub warn_round
  895. X       print bel;
  896. X    else
  897. X      ! not a suitable spot
  898. X    end if
  899. X  case ESC`20
  900. X    gosub DO_GET
  901. X    gosub DO_GET
  902. X    a$ = inbuf
  903. X!          if arr$(x,y) = unknown$ then
  904. X!            print posnb (2*x,y+upset);rev;arr$(x,y);normal
  905. X!          else
  906. X      print posnb (2*x,y+upset);arr$(x,y);
  907. X!          end if
  908. X    select a$
  909. X      case "A"                         ! up
  910. X        if y < nny then
  911. X          y  = y  + 1
  912. X        else
  913. X          print chr$(7);
  914. X        end if
  915. X      case "B"                        !down
  916. X        if y > 1 then
  917. X          y  = y - 1
  918. X        else
  919. X          print chr$(7);
  920. X        end if
  921. X      case "C"                         ! right
  922. X        if x < nnx then
  923. X          x  = x  + 1
  924. X        else
  925. X          print chr$(7);
  926. X        end if
  927. X      case "D"                    !left
  928. X        if x > 1 then
  929. X          x  = x - 1
  930. X        else
  931. X          print chr$(7);
  932. X        end if
  933. X!              print posnb(2*x,y +upset);arr$(x,y);cb;
  934. X      end select
  935. X  case else
  936. X!          print posnb (1,22);" -- ";inbuf," ";
  937. Xend select
  938. Xnext
  939. Xprint posnb(1,2)
  940. XPrint bold;blink;"Congratulations";normal;"  --  all mines cleared in";
  941. Xtaken = time(0) - start_time
  942. Xprint bold;blink; taken; normal;"seconds"
  943. Xif scorefile$ <> "" then
  944. X  gosub scoring
  945. X  goto again
  946. Xelse
  947. X  input "Play again  `5By`5D";a$
  948. X  a$ = edit$(left$(a$,1),32)`20
  949. X  if a$ = "N" then
  950. X    goto fini
  951. X  else
  952. X    goto again
  953. X  end if
  954. Xend if
  955. X
  956. X
  957. Xscoring:
  958. X! from temple - march 92            PB
  959. X! map (score) integer scorehigh, string nm=35, who=12, dated = 9
  960. X  print "                                           ";
  961. X  print "...................................";cu;cr;
  962. X  input "Please type in your Minesweeping identity"; nm
  963. X  scorehigh = taken
  964. X  who = edit$(user_name,4)
  965. X!  if who = "PB" then scorehigh = 0.8 * taken end if for cheating/testing
  966. X  dated = date$(0)
  967. Xlock_loop1:
  968. X  when error in
  969. X    open scorefile$ for input as file #1         &
  970. X`09,organization indexed fixed`09`09&
  971. X`09,access modify      `09`09`09&
  972. X`09,primary key scorehigh duplicates`09&
  973. X`09,map score
  974. X  use
  975. X    if err = 138 then
  976. X      print "High-scores file in use, please wait..."
  977. X      sleep 3
  978. X      continue lock_loop1
  979. X    else
  980. X      PrinT "Unable to open scoring file, please see system manager"
  981. X      sleep 3
  982. X      exit handler
  983. X    end if
  984. X  end when
  985. X  when error in
  986. X    put #1
  987. X  use
  988. X    PrinT "Error";err;"in scoring system, please see system manager"
  989. X    sleep 3
  990. X  end when
  991. X  close #1
  992. X  input "Do you want to see how this ranks in the high scores ";an$
  993. X  if EDIT$(LEFT$(an$,1),32) <> "N" then`20
  994. X    gosub score_read
  995. X  end if
  996. X  return
  997. X
  998. Xscore_read:
  999. X!high scores print
  1000. X  cycle = 0
  1001. X  scoremark% = 0
  1002. Xscore_loop:
  1003. X  when error in
  1004. X  open scorefile$ for input as file #1         &
  1005. X    ,organization indexed fixed`09`09&
  1006. X    ,access read      `09`09`09&
  1007. X    ,primary key scorehigh duplicates`09&
  1008. X    ,map score
  1009. X  use
  1010. X    if err = 138 then
  1011. X      print "High-scores file in use, please wait..."
  1012. X      sleep 2
  1013. X      continue score_loop
  1014. X    else
  1015. X      Print "Unable to open scoring file, please see system manager"
  1016. X      sleep 3
  1017. X      exit handler
  1018. X    end if
  1019. X  end when
  1020. X  for j = 1 to 16
  1021. X    when error in
  1022. X      if j = 1 then
  1023. X        get #1, key #0% ge scoremark%
  1024. X      else
  1025. X        get #1
  1026. X      end if
  1027. X    use
  1028. X      if err = 11 or err = 155 then
  1029. X        hscore(j) = 0
  1030. X        j = 17
  1031. X        close #1
  1032. X        continue printit
  1033. X      else
  1034. X        Print "Error ";ert$(err);" in scoring system, please see system mana
  1035. Vger"
  1036. X        sleep 3
  1037. X      end if
  1038. X    end when
  1039. X    nm$(j) = trm$(nm)
  1040. X    hscore(j) = scorehigh`20
  1041. X    user_name$(j) = trm$(who)
  1042. X    when$(j) = dated`20
  1043. X  next j
  1044. X  close #1
  1045. X! Read fast, then get out while we print it and he looks at it
  1046. X  scoremark% = scorehigh
  1047. Xprintit:
  1048. X! map (score) integer scorehigh, string nm=35, who=12, dated = 9
  1049. X  print cls;
  1050. X  print "          VAX high scores:  ";
  1051. X  if level = 1 then print " Beginner level" end if
  1052. X  if level = 2 then print " Intermediate level" end if
  1053. X  if level = 3 then print " Expert level" end if
  1054. X  print "Ranking";tab(14);"Name", tab(50);"Score";tab(65);"Date"
  1055. X  print "-------";tab(14);"----", tab(50);"-----";tab(65);"----"
  1056. X  print
  1057. X  for j = 1 to 16
  1058. X    if hscore(j) = 0 then`20
  1059. X      goto eolist
  1060. X    else
  1061. X      if user_name$(j) = user_name then`20
  1062. X        ! if user name matches then lets make it glow
  1063. X        print bold; else print normal;`20
  1064. X      end if
  1065. X      print j+15*cycle; tab(14);nm$(j); tab(50);
  1066. X      print using "#####"; hscore(j);
  1067. X      print tab(65);when$(j);normal
  1068. X    end if
  1069. X  next j `20
  1070. X  print posnt (1,25);cleol;
  1071. X  input "Press return to continue listing scores, or F to finish";an$
  1072. X  if EDIT$(LEFT$(an$,1),32) = "F" then return end if
  1073. X  cycle = cycle+1
  1074. X  goto score_loop
  1075. X
  1076. Xeolist:
  1077. X  print posnt (1,25);cleol;
  1078. X  if j+15*cycle > maxscores then
  1079. X! delete a few quietly     (the top score should stay)
  1080. X    ndel = j+15*cycle - maxscores
  1081. X    del_int = maxscores/ndel
  1082. X    when error in
  1083. X      open scorefile$ for input as file #1         &
  1084. X`09,organization indexed fixed`09`09&
  1085. X`09,access modify      `09`09`09&
  1086. X`09,primary key scorehigh duplicates`09&
  1087. X`09,map score
  1088. X    use
  1089. X      ! forget it for now
  1090. X      continue lock_loop2
  1091. X    end when
  1092. X    when error in
  1093. X      get #1            ! the top one
  1094. Xtill_err:   `20
  1095. X      for j = 1 to del_int * rnd * 2   !   ( NB only approx the right number
  1096. V)
  1097. X        get #1
  1098. X      next j            ! avoid any done in current month
  1099. X      if mid$(dated,4,6) <> mid$(date$(0),4,6) then`20
  1100. X        delete #1
  1101. X      end if
  1102. X      goto till_err
  1103. X    use
  1104. X      continue lock_loop2
  1105. X    end when
  1106. Xlock_loop2:`20
  1107. X    close #1
  1108. X  end if
  1109. X  input "Press return to continue"; an$
  1110. Xreturn
  1111. X`20
  1112. Xredraw:
  1113. X  print cls
  1114. X  print posnt(30,1);"Spacebar  to clear"
  1115. X  print posnt(30,2);"F or M    to flag"
  1116. X  print posnt(30,3);"Arrows    to move"
  1117. X  print posnt(30,4);"Q         to quit"
  1118. X  print posnt(60,1);"C      clear round"
  1119. X  print posnt(60,2);"ctrl/W  to refresh"
  1120. X  print posnt(60,3);"P       to pause"
  1121. X  for y1 = nny to 1 step -1
  1122. X    l$ = ""
  1123. X    for x1 = 1 to nnx
  1124. X      l$ = l$ + arr$(x1,y1)
  1125. X    next x1
  1126. X    print posnb(2,y1+upset);l$
  1127. X  next y1
  1128. X  print normal; box(1,25-(nny+upset+1),2*nnx+2,25-upset)
  1129. X  print posnt(1,1); "Mines to find:";unfound;"   "
  1130. X  print posnt(1,2); "Time taken:   ";
  1131. X  if started = yes then
  1132. X    print time(0) - start_time;"   "
  1133. X  end if
  1134. X  print posnt(1,3); "Spaces to clear";ntofind; "   "
  1135. Xreturn
  1136. X
  1137. Xclear_round:
  1138. X! no mines adjacent to square, so all can be cleared
  1139. X! additional clear locations found are saved on stack
  1140. X  for j = x1(bstack)-1 to x1(bstack)+1
  1141. X    for k = y1(bstack)-1 to y1(bstack)+1
  1142. X      if j >=1 and j <= nnx and k >=1 and k <= nny then
  1143. X        if arr$(j,k) = unknown$ then
  1144. X          cleared(j,k) = yes
  1145. X          ntofind = ntofind - 1
  1146. X          if mine(j,k) = 0 then
  1147. X            arr$(j,k) = "  "
  1148. X            print posnb(2*j,k +upset);arr$(j,k);
  1149. X            tstack = tstack + 1
  1150. X            x1(tstack) = j
  1151. X            y1(tstack) = k
  1152. X          else
  1153. X            arr$(j,k) = format$(mine(j,k),"##")
  1154. X            print posnb(2*j,k +upset);arr$(j,k);
  1155. X          end if
  1156. X        end if
  1157. X      end if
  1158. X    next k
  1159. X  next j
  1160. Xreturn
  1161. X
  1162. Xclear_it:
  1163. X! called by spacebar press or "C" of adjacent square
  1164. X  if cleared(x1,y1) = no then
  1165. X  if mine(x1,y1) < 0 then
  1166. X! Disaster
  1167. X    for k = nny to 1 step -1
  1168. X      for j = 1 to nnx
  1169. X        if mine(j,k) < 0 then
  1170. X          if arr$(j,k) <> flag$ then
  1171. X            print posnb(2*j,k+upset);" M";
  1172. X          end if
  1173. X        else
  1174. X          if arr$(j,k) = flag$ and mine(j,k) >=0 then
  1175. X            print posnb(2*j,k+upset);blink;" F";normal;
  1176. X          end if
  1177. X        end if
  1178. X      next j
  1179. X    next k
  1180. X    print posnb(2*x1,y1 +upset);blink;" M";normal;
  1181. X    print bel;posnb(80,3)
  1182. X    print "Sorry, you blew it      ";
  1183. X    input "Try again  `5By`5D";a$
  1184. X    a$ = edit$(left$(a$,1),32)`20
  1185. X    if a$ = "N" then
  1186. X      goto fini
  1187. X    else
  1188. X      goto again
  1189. X    end if
  1190. X  else
  1191. X! Safe
  1192. X    if mine(x1,y1) = 0 then
  1193. X      tstack = 1
  1194. X      bstack = 1
  1195. X      x1(1) = x1
  1196. X      y1(1) = y1
  1197. X      while bstack <= tstack
  1198. X        gosub clear_round
  1199. X        bstack = bstack + 1
  1200. X      next
  1201. X      print posnt(1,3); "Spaces to clear";ntofind;"  "
  1202. X    else
  1203. X      if arr$(x1,y1) = unknown$ then
  1204. X        ntofind = ntofind - 1
  1205. X        cleared(x1,y1) = yes
  1206. X        print posnt(1,3); "Spaces to clear";ntofind;"  "
  1207. X        arr$(x1,y1) = format$(mine(x1,y1),"##")
  1208. X        print posnb(2*x1,y1+upset);arr$(x1,y1);
  1209. X      else
  1210. X        print chr$(7);
  1211. X      end if
  1212. X    end if
  1213. X  end if
  1214. X  end if
  1215. Xreturn
  1216. X
  1217. Xsafe_round:
  1218. X  for x1 = x-1 to x+1
  1219. X    for y1 = y-1 to y+1
  1220. X      if x1 >=1 and x1 <= nnx and y1 >=1 and y1 <= nny then
  1221. X        gosub clear_it
  1222. X      end if
  1223. X    next y1
  1224. X  next x1
  1225. Xreturn
  1226. X
  1227. Xwarn_round:
  1228. X  for x1 = x-1 to x+1
  1229. X    for y1 = y-1 to y+1
  1230. X      if x1 >=1 and x1 <= nnx and y1 >=1 and y1 <= nny then
  1231. X        if arr$(x1,y1) = unknown$ then
  1232. X          arr$(x1,y1) = star$
  1233. X          print posnb(2*x1,y1+upset);arr$(x1,y1) ;
  1234. X        end if
  1235. X      end if
  1236. X    next y1
  1237. X  next x1
  1238. X  sleep (1)
  1239. X  for x1 = x-1 to x+1
  1240. X    for y1 = y-1 to y+1
  1241. X      if x1 >=1 and x1 <= nnx and y1 >=1 and y1 <= nny then
  1242. X        if arr$(x1,y1) = star$ then
  1243. X          arr$(x1,y1) = unknown$
  1244. X          print posnb(2*x1,y1+upset);arr$(x1,y1) ;
  1245. X        end if
  1246. X      end if
  1247. X    next y1
  1248. X  next x1
  1249. Xreturn
  1250. X
  1251. Xfini:
  1252. X  print posnb(1,1)
  1253. $ CALL UNPACK MINESWEEPER.BAS;22 941250866
  1254. $ create 'f'
  1255. XMinesweeper
  1256. X
  1257. X
  1258. XThis is a reverse-engineered version of the Minesweeper for Windows program.
  1259. XIt runs on VT100 compatible terminals under VMS.
  1260. X
  1261. XYou are given a grid with a random array of mines.
  1262. XThe aim is to identify the location of the mines and to clear all other`20
  1263. Xcells. When a cell is cleared, you are told the number of adjacent squares`2
  1264. V0
  1265. Xthat contain mines. Adjacency is vertical, horizontal and diagonal.
  1266. XIf you attempt to clear a cell that is occupied by a mine then it will`20
  1267. Xexplode and the game ends. The exploded mine and any falsely flagged mines`2
  1268. V0
  1269. Xare shown flashing.
  1270. X
  1271. XConversion for VAX BASIC by Peter Bury, April 1992
  1272. XPB@vcp.monash.edu.au
  1273. X#
  1274. XKeys
  1275. X
  1276. XYour current position is indicated by the cursor.
  1277. XUse the group of four Arrow keys to move`20
  1278. X
  1279. XF or f or M or m or X or x   to flag the presence of a mine. Will also`20
  1280. Xunflag the mine if you change your mind.
  1281. X                              (equiv to right mouse button in original)
  1282. X
  1283. XSpacebar   to clear a square
  1284. X                              (equiv to left  mouse button in original)
  1285. X
  1286. XC or c     to clear around a number that is fully accounted for. Will`20
  1287. Xbriefly show neighbours if not fully accounted for.
  1288. X                              (equiv to both mouse buttons in original)
  1289. X
  1290. X
  1291. XNB all cells adjacent to a score of zero are automatically cleared
  1292. X#
  1293. XThe board
  1294. X
  1295. XUnknown locations are shown as dots.
  1296. X
  1297. XCleared locations are numbers representing the number of adjacent squares`20
  1298. Xthat contain mines. Adjacency is vertical, horizontal and diagonal.`20
  1299. XSquares not adjacent to any mines are shown clear rather than as zeroes.
  1300. X
  1301. XFlagged squares contain `1B`5B1mX`1B`5B0m in bold
  1302. X
  1303. X
  1304. X#
  1305. XStrategy
  1306. X
  1307. XYou have to guess a couple to try to get a start.
  1308. XThen think!
  1309. X
  1310. XYou will get to recognise some patterns eg in straight-line edges
  1311. X
  1312. X`7C 1 1 x x x x 1 2 1 x x x x 2 1 x x x`20
  1313. X`7C . . . . . . . . . . . . . . . . . .
  1314. X  ? ? `5E     `5E * `5E * `5E     * ? ? `5E
  1315. X
  1316. Xwhere `7C is a wall and x is don't care, the places above the stars must be`
  1317. V20
  1318. Xmines, the hats must be clear. The question marks are undetermined.
  1319. X##
  1320. $ CALL UNPACK MINESWEEPER.HLP;3 1829056626
  1321. $ create 'f'
  1322. X! Create score files for Minesweeper`20
  1323. X!  3 files - one for each level
  1324. Xmap (score) integer scorehigh, string nm=35, who=12, dated = 9
  1325. X      %include "scorebase.bas"
  1326. X      print "Score files in directory  "; scorebase$`20
  1327. X      if mid$(scorebase$,len(scorebase$),1) <> "`5D" and       &
  1328. X         mid$(scorebase$,len(scorebase$),1) <> ":" then`20
  1329. X            print bel; "Warning - check form of directory name"
  1330. X      end if
  1331. X
  1332. X      for j = 1 to 3
  1333. X        scorefile$ = scorebase$ + "mine" + str$(j) + "score.da"
  1334. X        when error in
  1335. X          open scorefile$ for output as file #1      &
  1336. X            ,organization indexed fixed               &
  1337. X            ,primary key scorehigh duplicates         &
  1338. X            ,map score
  1339. X          print scorefile$; " created "`20
  1340. X          close #1
  1341. X        use
  1342. X          print bel; "Can't create "; scorefile$
  1343. X          print "Error ";err, ert$(err)
  1344. X        end when
  1345. X      next j   `20
  1346. $ CALL UNPACK MSW_SCORE_FILES.BAS;11 1208039327
  1347. $ create 'f'
  1348. X  !     BASIC calls to set vt100 video attributes
  1349. X  !  Mod  sept 24 1986   dbl1 & dbl2 AFTER line are top & bottom of 2x heigh
  1350. Vt
  1351. X      Declare string function box(real,real,real,real)      !x1,y1,x2,y2
  1352. X      Declare string function posnt(real,real)      !position from top
  1353. X      Declare string function cleos                 !clear to eos
  1354. X      Declare string function cleol                 !clear to eol
  1355. X      Declare string function posnb(real,real)      !position from bottom
  1356. X      Declare string function cls
  1357. X      Declare string function bold
  1358. X      Declare string function uline
  1359. X      Declare string function blink
  1360. X      Declare string function rev
  1361. X      Declare string function normal
  1362. X      Declare string function nobold
  1363. X      Declare string function norev
  1364. X      Declare string function noblink
  1365. X      Declare string function nouline
  1366. X      Declare string function cu              !Cursor up or reverse index
  1367. X      Declare string function cd              !       down
  1368. X      Declare string function cb              !       back
  1369. X      Declare string function cf              !       forward
  1370. X      Declare string function col80
  1371. X      Declare string function col132
  1372. X      Declare string function ginit           !init ascii to g0 & dec to g1
  1373. X      Declare string function gon
  1374. X      Declare string function goff
  1375. X      Declare string function dbw            !double width
  1376. X      Declare string function dbl1
  1377. X      Declare string function dbl2
  1378. X    !
  1379. X      def box(va_x1,va_y1,va_x2,va_y2)
  1380. X      bx$ = posnt(va_x1,va_y1) + ginit + gon + "l"`20
  1381. X      bx$ = bx$ + "q" for vid_attrib_v1 = va_x1+1 to va_x2-1`20
  1382. X      bx$ = bx$ + "k"
  1383. X      bx$ = bx$ +  posnt(va_x1,vid_attrib_v1) + "x" + posnt(va_x2,vid_attrib
  1384. V_v1) &
  1385. X        + "x" for vid_attrib_v1 = va_y1+1 to va_y2-1
  1386. X      bx$ = bx$ +  posnt(va_x1,va_y2) + gon + "m"
  1387. X      bx$ = bx$ +  "q" for vid_attrib_v1 = va_x1+1 to va_x2-1`20
  1388. X      box = bx$ +  "j" +  goff
  1389. X      end def
  1390. X    !
  1391. X      def dbl1
  1392. X      dbl1 = esc + "#3"
  1393. X      end def
  1394. X    !
  1395. X      def dbl2
  1396. X      dbl2 = esc + "#4"
  1397. X      end def
  1398. X    !
  1399. X      def dbw
  1400. X      dbw = esc + "#6"
  1401. X      end def
  1402. X    !
  1403. X      def bold
  1404. X      bold = esc + "`5B1m"
  1405. X      end def
  1406. X    !
  1407. X      def uline
  1408. X      uline = esc + "`5B4m"
  1409. X      end def
  1410. X    !
  1411. X      def blink
  1412. X      blink = esc + "`5B5m"
  1413. X      end def
  1414. X    !
  1415. X      def rev
  1416. X      rev = esc + "`5B7m"
  1417. X      end def
  1418. X    !
  1419. X      def normal
  1420. X      normal = esc + "`5B0m"
  1421. X      end def
  1422. X    !
  1423. X      def nobold
  1424. X      nobold = esc + "`5B22m"
  1425. X      end def
  1426. X    !
  1427. X      def nouline
  1428. X      nouline = esc + "`5B24m"
  1429. X      end def
  1430. X    !
  1431. X      def noblink
  1432. X      noblink = esc + "`5B25m"
  1433. X      end def
  1434. X    !
  1435. X      def norev
  1436. X      norev = esc + "`5B27m"
  1437. X      end def
  1438. X    !
  1439. X      def cu
  1440. X      cu = esc + "M"
  1441. X      end def
  1442. X    !
  1443. X      def cd
  1444. X      cd = esc + "D"
  1445. X      end def
  1446. X    !
  1447. X      def cf
  1448. X      cf = esc + "`5B1C"
  1449. X      end def
  1450. X    !
  1451. X      def cb
  1452. X      cb = esc + "`5B1D"
  1453. X      end def
  1454. X    !
  1455. X      def col80
  1456. X      col80 = esc + "`5B?3l"
  1457. X      end def
  1458. X    !
  1459. X      def col132
  1460. X      col132 = esc + "`5B?3h"
  1461. X      end def
  1462. X    !
  1463. X      def gon
  1464. X      gon = chr$(14)
  1465. X      end def
  1466. X    !
  1467. X      def goff
  1468. X      goff = chr$(15)
  1469. X      end def
  1470. X    !
  1471. X    ! 'ginit' loads normal ASCII char set to G0, DEC special graphics to G1
  1472. X    ! This is normal terminal setup, and 'gon' may be used to select graphic
  1473. Vs
  1474. X    !  mode, and 'goff' to turn it off again
  1475. X    !
  1476. X      def ginit                       `20
  1477. X      ginit = esc + ")0" + esc + "(B"
  1478. X      end def
  1479. X    !
  1480. X      def cls                              ! clear screen and home
  1481. X      vid_attrib_h1=0 \ vid_attrib_v1=0`20
  1482. X      cls=posnt(vid_attrib_h1,vid_attrib_v1) + cleos
  1483. X      end def
  1484. X    !
  1485. X      def cleos
  1486. X      cleos = esc + "`5B0J"                  ! clear to EOS
  1487. X      end def
  1488. X    !
  1489. X      def cleol
  1490. X      cleol = esc + "`5B0K"                ! clear to EOL
  1491. X      end def
  1492. X    !
  1493. X    ! Position cursor from top left (x,y)
  1494. X      def posnt(vid_attrib_h1,vid_attrib_v1)
  1495. X      posnt = chr$(27)+"`5B"+str$(vid_attrib_v1)+";"+str$(vid_attrib_h1)+"H"
  1496. X      end def                                        `20
  1497. X    !
  1498. X    ! Position cursor from bottom left (x,y)
  1499. X      def posnb(vid_attrib_h1,vid_attrib_v1)
  1500. X      posnb = chr$(27)+"`5B"+str$(25-vid_attrib_v1)+";"+str$(vid_attrib_h1)+
  1501. V"H"`20
  1502. X      end def
  1503. X    !
  1504. X      print ginit;goff;
  1505. $ CALL UNPACK VID_ATTRIB.BAS;19 1379062756
  1506. $ v=f$verify(v)
  1507. $ EXIT
  1508.