Source-Changes-HG archive

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index][Old Index]

[src/trunk]: src/sys/arch/arm26/stand It seems that all versions of BBC BASIC...



details:   https://anonhg.NetBSD.org/src/rev/44701bb3528d
branches:  trunk
changeset: 499640:44701bb3528d
user:      bjh21 <bjh21%NetBSD.org@localhost>
date:      Sat Nov 25 13:32:51 2000 +0000

description:
It seems that all versions of BBC BASIC V can load a text file specified on
the command line, so we don't need to tokenize it first.

This makes it less than clear what file type BBBB should have, so let's not
make an issue of it.

diffstat:

 sys/arch/arm26/stand/BBBB/BBBB       |  461 +++++++++++++++++++++++++++++++++++
 sys/arch/arm26/stand/BBBB/BBBB,fd1   |  461 -----------------------------------
 sys/arch/arm26/stand/BBBB/Makefile   |   26 +-
 sys/arch/arm26/stand/Makefile        |    4 +-
 sys/arch/arm26/stand/bastok/Makefile |   11 -
 sys/arch/arm26/stand/bastok/bastok.1 |   24 -
 sys/arch/arm26/stand/bastok/bastok.l |  308 -----------------------
 7 files changed, 466 insertions(+), 829 deletions(-)

diffs (truncated from 1329 to 300 lines):

diff -r cacd9db7daa7 -r 44701bb3528d sys/arch/arm26/stand/BBBB/BBBB
--- /dev/null   Thu Jan 01 00:00:00 1970 +0000
+++ b/sys/arch/arm26/stand/BBBB/BBBB    Sat Nov 25 13:32:51 2000 +0000
@@ -0,0 +1,461 @@
+REM>BBBB
+REM $NetBSD: BBBB,v 1.1 2000/11/25 13:32:52 bjh21 Exp $
+REM
+REM Copyright (c) 1998, 1999, 2000 Ben Harris
+REM All rights reserved.
+REM
+REM Redistribution and use in source and binary forms, with or without
+REM modification, are permitted provided that the following conditions
+REM are met:
+REM 1. Redistributions of source code must retain the above copyright
+REM    notice, this list of conditions and the following disclaimer.
+REM 2. Redistributions in binary form must reproduce the above copyright
+REM    notice, this list of conditions and the following disclaimer in the
+REM    documentation and/or other materials provided with the distribution.
+REM 3. The name of the author may not be used to endorse or promote products
+REM    derived from this software without specific prior written permission.
+REM
+REM THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
+REM IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
+REM OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
+REM IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
+REM INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
+REM NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
+REM DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
+REM THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
+REM (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
+REM THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
+REM
+REM This file is part of NetBSD/arm26 -- a port of NetBSD to ARM2/3 machines.
+REM
+REM Ben's BASIC BSD Booter (allegedly)
+debug% = 1
+PRINT ">> BBBB, Revision 0.32"
+SYS "OS_ReadMemMapInfo" TO nbpp%, npages%
+IF debug% THEN
+  PRINT "Machine has ";npages%;" pages of ";nbpp% DIV 1024;"K each.  ";
+  PRINT "Total RAM: ";npages% * nbpp% DIV 1024 DIV 1024;"Mb"
+  PRINT "Lowering HIMEM: &";~HIMEM;
+ENDIF
+HIMEM = &10000
+IF debug% THEN PRINT " -> &";~HIMEM
+
+twirl% = 0
+
+DIM vaddr%(npages%-1), access%(npages%-1), pgok%(npages%-1)
+pgok%() = FALSE
+
+PROCget_mem_map
+SYS "OS_GetEnv" TO A$
+IF debug% THEN PRINT A$
+WHILE LEFT$(A$, 1) <> " " AND LEN(A$) > 0 A$ = MID$(A$, 2) : ENDWHILE
+WHILE LEFT$(A$, 1) = " " A$ = MID$(A$, 2) : ENDWHILE
+WHILE RIGHT$(A$,1) = " " A$ = LEFT$(A$) : ENDWHILE
+IF FNtolower(LEFT$(A$, 5)) = "-quit" THEN
+  A$ = MID$(A$, 7)
+  WHILE LEFT$(A$, 1) <> " " AND LEN(A$) > 0 A$ = MID$(A$, 2) : ENDWHILE
+  WHILE LEFT$(A$, 1) = " " A$ = MID$(A$, 2) : ENDWHILE
+ENDIF
+file$ = ""
+howto% = 0
+WHILE LEN(A$) > 0
+  CASE LEFT$(A$, 1) OF
+    WHEN "-"
+      done% = FALSE
+      REPEAT
+        A$ = MID$(A$, 2)
+        CASE FNtolower(LEFT$(A$, 1)) OF
+          WHEN "a" : howto% = howto% OR &01 : REM RB_ASKNAME
+          WHEN "s" : howto% = howto% OR &02 : REM RB_SINGLE
+          WHEN "d" : howto% = howto% OR &40 : REM RB_KDB
+          WHEN "q" : howto% = howto% OR &10000 : REM AB_QUIET
+          WHEN "v" : howto% = howto% OR &20000 : REM AB_VERBOSE
+          WHEN " ", "" : done% = TRUE
+          OTHERWISE : ERROR EXT 0, "Bad option: " + LEFT$(A$, 1)
+        ENDCASE
+      UNTIL done%
+    WHEN " "
+      A$ = MID$(A$, 2)
+    OTHERWISE
+      IF file$ <> "" THEN ERROR EXT 0, "Too many files!"
+      WHILE LEFT$(A$, 1) <> " " AND LEN(A$) > 0
+        file$ += LEFT$(A$,1)
+        A$ = MID$(A$, 2)
+      ENDWHILE
+  ENDCASE
+ENDWHILE
+IF file$ = "" AND (howto% AND &01) THEN
+  INPUT "boot: "file$
+ELSE
+  IF file$ = "" THEN file$ = "netbsd"
+ENDIF
+PRINT "Booting "; file$; " (howto = 0x"; ~howto%; ")"
+PROCload_kernel(file$)
+DIM P% 1023
+REM
+[ OPT 2
+ .config%
+  EQUD &942B7DFE             ; magic
+  EQUD 0                     ; version
+  EQUD howto%                ; boothowto
+  EQUD 0                     ; bootdev
+  EQUD ssym%                 ; ssym
+  EQUD esym%                 ; esym
+  EQUD nbpp%                 ; nbpp
+  EQUD npages%               ; npages
+  EQUD txtbase%              ; txtbase
+  EQUD txtsize%              ; txtsize
+  EQUD database%             ; database
+  EQUD datasize%             ; datasize
+  EQUD bssbase%              ; bssbase
+  EQUD bsssize%              ; bsssize
+  EQUD freebase%             ; freebase
+  EQUD FNvdu_var(11) + 1     ; xpixels
+  EQUD FNvdu_var(12) + 1     ; ypixels
+  EQUD 1 << FNvdu_var(9)     ; bpp
+  EQUD FNvdu_var(149) + FNvdu_var(150) - &02000000 ; screenbase (XXX?)
+  EQUD FNvdu_var(150)        ; screensize
+]
+SYS "OS_Byte", 165 TO ,,crow%
+[ OPT 2
+  EQUD crow% * FNvdu_var(170) ; cpixelrow
+]
+
+IF FNvdu_var(9) <> 3 THEN
+  PRINT "WARNING: Current screen mode has fewer than eight bits per pixel."
+  PRINT "         Console display may not work correctly (or at all)."
+ENDIF
+
+REM Try to ensure that we leave the page registers for podule ROMs pointing
+REM at the page with the ECID in it, so that NetBSD has a hope of finding it.
+FOR pod% = 0 TO 3
+  SYS "XPodule_ReadID",,,,pod%
+NEXT
+PROCstart_kernel(config%, 0, 0, 0, entry%)
+END
+
+DEF PROCget_mem_map
+  LOCAL block%
+  DIM block% (npages%+1)*12
+  FOR page%=0 TO npages%-1
+    block%!(page%*12) = page%
+  NEXT
+  block%!(npages%*12) = -1
+  SYS "OS_ReadMemMapEntries", block%
+  FOR page% = 0 TO npages%-1
+    vaddr%(page%) = block%!(page%*12+4)
+    access%(page%) = block%!(page%*12+8)
+  NEXT
+  IF debug% THEN PRINT "--------/-------/-------/-------"
+  FOR page%=0 TO npages%-1
+    IF access%(page%) = 3 THEN
+      IF debug% THEN PRINT ".";
+    ELSE
+      CASE TRUE OF
+        WHEN vaddr%(page%) < &0008000: IF debug% THEN PRINT "0";
+        WHEN vaddr%(page%) < &0010000: IF debug% THEN PRINT "+";
+        WHEN vaddr%(page%) < &1000000:
+          IF access%(page%) = 0 THEN
+            IF debug% THEN PRINT "*";
+            pgok%(page%) = TRUE
+           ELSE
+             IF debug% THEN PRINT "a";
+           ENDIF
+        WHEN vaddr%(page%) < &1400000: IF debug% THEN PRINT "d";
+        WHEN vaddr%(page%) < &1800000: IF debug% THEN PRINT "s";
+        WHEN vaddr%(page%) < &1C00000: IF debug% THEN PRINT "m";
+        WHEN vaddr%(page%) < &1E00000: IF debug% THEN PRINT "h";
+        WHEN vaddr%(page%) < &1F00000: IF debug% THEN PRINT "f";
+        WHEN vaddr%(page%) < &2000000: IF debug% THEN PRINT "S";
+      ENDCASE
+    ENDIF
+    IF page% MOD 32 = 31 AND debug% THEN PRINT
+  NEXT
+ENDPROC
+
+DEF PROCload_kernel(file$)
+  LOCAL file%, magic%
+  file% = OPENIN(file$)
+  IF file% = 0 THEN ERROR 1, "Can't open kernel"
+  DIM magic% 3
+  SYS "OS_GBPB", 3, file%, magic%, 4, 0
+  IF magic%?0 = 127 AND magic%?1 = ASC("E") AND magic%?2 = ASC("L") AND magic%?3 = ASC("F") THEN
+    PROCload_kernel_elf(file%)
+  ELSE
+    PROCload_kernel_aout(file%)
+  ENDIF
+  CLOSE#file%
+ENDPROC
+
+DEF PROCload_kernel_elf(file%)
+  LOCAL hdr%, phoff%, phentsize%, phnum%, phdrs%, ph%
+  LOCAL offset%, vaddr%, filesz%, memsz%, flags%, first%
+  LOCAL shoff%, shentsize%, shnum%, shdrs%, sh%, havesyms%, mshdrs%
+  DIM hdr% 51
+  SYS "OS_GBPB", 3, file%, hdr%, 52, 0
+  IF hdr%?4 <> 1 THEN ERROR 1, "Not a 32-bit ELF file"
+  IF hdr%?5 <> 1 THEN ERROR 1, "Not an LSB ELF file"
+  IF hdr%?6 <> 1 THEN ERROR 1, "Not a version-1 ELF file"
+  REM hdr%?7 is EI_OSABI.  Should it be 255 (ELFOSABI_STANDALONE)?
+  IF (hdr%!16 AND &FFFF) <> 2 THEN ERROR 1, "Not an executable ELF file"
+  IF (hdr%!18 AND &FFFF) <> 40 THEN ERROR 1, "Not an ARM ELF file"
+  entry% = hdr%!24
+  phoff% = hdr%!28
+  shoff% = hdr%!32
+  phentsize% = hdr%!42 AND &FFFF
+  phnum% = hdr%!44 AND &FFFF
+  shentsize% = hdr%!46 AND &FFFF
+  shnum% = hdr%!48 AND &FFFF
+  DIM phdrs% phnum% * phentsize% - 1
+  SYS "OS_GBPB", 3, file%, phdrs%, phnum% * phentsize%, phoff%
+  IF phnum% = 0 THEN ERROR 1, "No program headers"
+  first% = TRUE
+  FOR ph% = phdrs% TO phdrs% + (phnum% - 1) * phentsize% STEP phentsize%
+    IF ph%!0 <> 1 THEN NEXT : REM We only do PT_LOAD
+    IF NOT first% THEN PRINT "+";
+    first% = FALSE
+    offset% = ph%!4
+    vaddr% = ph%!8
+    filesz% = ph%!16
+    memsz% = ph%!20
+    flags% = ph%!24
+    PROCload_chunk(file%, offset%, vaddr%, filesz%, memsz%)
+    freebase% = vaddr% - &02000000 + memsz% : REM XXX
+  NEXT
+  txtbase% = 0
+  txtsize% = 0
+  database% = 0
+  datasize% = 0
+  bssbase% = 0
+  bsssize% = 0
+  ssym% = 0
+  esym% = 0
+  DIM shdrs% shnum% * shentsize% - 1
+  SYS "OS_GBPB", 3, file%, shdrs%, shnum% * shentsize%, shoff%
+  IF shnum% <> 0 THEN
+    havesyms% = FALSE
+    FOR sh% = shdrs% TO shdrs% + (shnum% - 1) * shentsize% STEP shentsize%
+      IF sh%!4 = 2 THEN havesyms% = TRUE
+    NEXT
+    IF havesyms% THEN
+      ssym% = freebase%
+      REM First, we have the munged ELF header
+      PRINT "+[";
+      PROCload_chunk(file%, 0, &02000000 + ssym%, 52, 52)
+      PROCwrite_word(ssym%+32, 52)
+      freebase% += 52
+      REM then, the munged section headers
+      mshdrs% = freebase%
+      PRINT "+";
+      PROCload_chunk(file%, shoff%, &02000000 + mshdrs%, shnum% * shentsize%, shnum% * shentsize%)
+      freebase% += shnum% * shentsize%
+      FOR sh% = shdrs% TO shdrs% + (shnum% - 1) * shentsize% STEP shentsize%
+        IF sh%!4 = 2 OR sh%!4 = 3 THEN
+          PRINT "+";
+          PROCload_chunk(file%, sh%!16, &02000000 + freebase%, sh%!20, sh%!20)
+          PROCwrite_word(mshdrs% + sh% - shdrs% + 16, freebase% - ssym%)
+          freebase% += FNroundup(sh%!20, 4)
+        ENDIF
+      NEXT
+      esym% = freebase%
+      PRINT "]";
+    ENDIF
+  ENDIF
+  PRINT " "
+  REM XXX
+ENDPROC
+
+DEF PROCload_chunk(file%, offset%, vaddr%, filesz%, memsz%)
+  LOCAL paddr%, ppn%, fragaddr%, fragsz%
+  PRINT ;filesz%;
+  WHILE filesz% > 0
+    paddr% = vaddr% - &02000000
+    ppn% = paddr% DIV nbpp%
+    IF NOT pgok%(ppn%) THEN ERROR 1, "Page " + STR$(ppn$) + " not free"
+    fragaddr% = vaddr%(ppn%) + paddr% MOD nbpp%
+    fragsz% = nbpp% - (paddr% MOD nbpp%)
+    IF fragsz% > filesz% THEN fragsz% = filesz%
+    SYS "OS_GBPB", 3, file%, fragaddr%, fragsz%, offset%
+    PROCtwirl
+    offset% += fragsz%
+    vaddr% += fragsz%
+    filesz% -= fragsz%
+    memsz% -= fragsz%
+  ENDWHILE
+  IF memsz% > 0 PRINT "+";memsz%;
+  WHILE memsz% > 0
+    paddr% = vaddr% - &02000000
+    ppn% = paddr% DIV nbpp%
+    IF NOT pgok%(ppn%) THEN ERROR 1, "Page " + STR$(ppn%) + " not free"
+    fragaddr% = vaddr%(ppn%) + paddr% MOD nbpp%
+    fragsz = nbpp% - (paddr% MOD nbpp%)
+    IF fragsz% > memsz% THEN fragsz% = memsz%
+    PROCbzero(fragaddr%, fragsz%)
+    PROCtwirl
+    offset% += fragsz%
+    vaddr% += fragsz%



Home | Main Index | Thread Index | Old Index