home *** CD-ROM | disk | FTP | other *** search
/ Programmer 7500 / MAX_PROGRAMMERS.iso / PROGRAMS / UTILS / LASER / FPC35_5.ZIP / FPCSRC.ZIP / KERNEL4.SEQ < prev    next >
Encoding:
Text File  |  1989-09-21  |  20.7 KB  |  560 lines

  1. \ KERNEL4.SEQ   Last part of the kernel file, finishes up the compile.
  2.  
  3. \ Link this file into the FILELIST chain.
  4.  
  5. FILES DEFINITIONS
  6.  
  7. VARIABLE KERNEL4.SEQ
  8.  
  9. FORTH DEFINITIONS   META IN-META
  10.  
  11. VARIABLE #USER
  12. \ A variable that holds the count of how many user variables are allocated.
  13.  
  14. VOCABULARY USER   USER DEFINITIONS
  15. \ Vocabulary that holds task versions of defining words.
  16.  
  17. : ALLOT         ( n -- )
  18. \ Allocate space in the user area for a multi-tasking word.
  19.                 #USER +!   ;
  20.  
  21. ' CREATE        \ avoid recursion: leave address for ,-X in CREATE
  22.  
  23. : CREATE        ( -- )
  24. \ Define a word that returns the address of the next available user
  25. \ memory location.
  26.                 [ ,-X ]         \ compile addr of CREATE
  27.                 #USER @ ,
  28.                 ;USES  DOUSER-VARIABLE ,-X
  29.  
  30. : VARIABLE      ( -- )
  31. \ Define a task type variable. Similar to the old FIG version word USER.
  32.                 CREATE   2 ALLOT   ;
  33.  
  34. : DEFER         ( -- )
  35. \ Defines an execution vector that is local to a task.
  36.                 VARIABLE   ;USES   DOUSER-DEFER  ,-X
  37.  
  38. FORTH DEFINITIONS   META IN-META
  39.  
  40. : >IS           ( cfa -- data-address )
  41. \ smart word converts from CFA to data field. Knows about user variables.
  42.                 DUP 1+ @ OVER >BODY +
  43.                 DUP [  [ASSEMBLER] DOUSER-VARIABLE META ] LITERAL = SWAP
  44.                 DUP [  [ASSEMBLER] DOUSER-DEFER    META ] LITERAL = SWAP
  45.                 DROP   OR IF   >BODY @ UP @ +   ELSE    >BODY   THEN   ;
  46.  
  47. : (IS)          ( cfa --- )
  48. \ This word is compiled by IS. Sets the following DEFERred word to the
  49. \ address on the parameter stack.
  50.                 2R@ @L >IS !   R> 2+ >R   ;
  51.  
  52. : IS            ( cfa --- )
  53. \ Depending on STATE, either sets the following DEFERred word immediatly
  54. \ or compiles (IS) to set it later.
  55.                 STATE @
  56.                 IF      COMPILE (IS)
  57.                 ELSE    ' >IS !
  58.                 THEN    ;       IMMEDIATE
  59.  
  60. : SELECT        ( N1 --- )
  61. \ Select drive n1 as the current disk drive. 0=A, 1=B etc.
  62.                 14 bdos drop
  63.                 seqhandle >hndle @ -2 =
  64.                 if      -1 seqhandle >hndle !
  65.                 then    ;
  66.  
  67. : A:            ( --- )         0 SELECT ;
  68. : B:            ( --- )         1 SELECT ;
  69. : C:            ( --- )         2 SELECT ;
  70. : D:            ( --- )         3 SELECT ;
  71. : E:            ( --- )         4 SELECT ;
  72. : F:            ( --- )         5 SELECT ;
  73. \ Select drive A:, B:, C:, D:, E: or F: as the default drive.
  74.  
  75. : QUIT          ( -- )
  76. \ The main loop in Forth. Gets input from the terminal and Interprets it.
  77. \ Responds with OK if healthy and repeats the process.
  78.                 SP0 @ 'TIB !    [COMPILE] [
  79.                 BEGIN   BEGIN RP0 @ RP! STATUS QUERY  RUN
  80.                               STATE @ NOT UNTIL ."  ok" AGAIN  ;
  81.  
  82. DEFER BOOT
  83. \ A defered word that performs initialization before executing QUIT.
  84.  
  85. DEFER INITSTUFF   ' SEQINIT IS INITSTUFF
  86. \ A defered word chain that performs various initialization operations
  87. \ at Forth initial cold start time.
  88.  
  89. DEFER SEGSET      ' SETYSEG IS SEGSET
  90. \ A DEFERed word that contain the current function used to set up the
  91. \ segment registers at cold start time. Typically contains SETYSEG.
  92.  
  93. : WARMSTRT      ( --- )
  94. \ The default function to be performed on a WARM start.
  95.                 FORTH
  96.                 TRUE ABORT" Warm Start" ;
  97.  
  98. DEFER WARMFUNC  ' WARMSTRT IS WARMFUNC
  99. \ A DEFERed word that is invoked when a warm start occurs.
  100. \ This function is also called whenever the CONTROL BREAK key is pressed.
  101.  
  102. TRUE VALUE 1STCOLD
  103. \ A flag to tell if COLD has been called yet.
  104.  
  105. : WARM          ( -- )
  106. \ The WARM entry point for Forth, just calles the DEFERed word WARMFUNC.
  107. \ A WARM start is invoked whenever the CONTROL BREAK key is pressed.
  108.                 [ LABEL WARMBODY ]
  109.                 WARMFUNC ;
  110.  
  111. : COLD          ( -- )
  112. \ The high level cold start code. For ordinary forth, BOOT should
  113. \ initialize and pass control to QUIT.
  114.                 [ LABEL COLDBODY ]
  115.                 1STCOLD                 \ Only do this stuff once each load
  116.                 IF      SEGSET VMODE.SET INITSTUFF
  117.                 THEN    %OFF> 1STCOLD
  118.                 BOOT QUIT   ;
  119.  
  120. : START         ( -- )
  121. \ Minimal default initialization. This word is stuffed into BOOT
  122. \ when compiling the KERNEL.COM file.
  123.                 SP0 @ 'TIB !
  124.                 >IN OFF
  125.                 SPAN OFF
  126.                 #TIB OFF
  127.                 LOADING OFF
  128.                 DEFAULT INTERPRET ;
  129.  
  130. VARIABLE BIOSBKSAVE     0 ,-T
  131. \ A double variable that holds the BIOS Control Break vector so it
  132. \ can be restored on exit.
  133.  
  134. VARIABLE DIV0SAVE       0 ,-T
  135. \ A double variable that holds the divide by zero interupt vector
  136. \ so it can be restored on exit from Forth.
  137.  
  138. VARIABLE CTRLBKSAVE
  139. \ A variable that holds the state of the low memory Control Break
  140. \ flag so it can be restored on exit from Forth.
  141.  
  142. CODE RESTORE_VECTORS    ( --- )
  143. \ Restores the saved vectors to their saved values.  This word is called
  144. \ just prior to returning to DOS.
  145.                 MOV AX, CS              MOV DS, AX
  146.                 MOV DX, CS: BIOSBKSAVE
  147.                 MOV DS, CS: BIOSBKSAVE 2+
  148.                 MOV AX, # $251B
  149.                 INT $21
  150.                 MOV AX, CS              MOV DS, AX
  151.                 MOV DX, CS: DIV0SAVE
  152.                 MOV DS, CS: DIV0SAVE 2+
  153.                 MOV AX, # $2500
  154.                 INT $21
  155.                 MOV AX, CS              MOV DS, AX
  156.                 MOV DX, CTRLBKSAVE
  157.                 MOV AX, # $3301         \ Control BREAK flag status
  158.                 INT $21
  159.                 NEXT                    END-CODE
  160.  
  161. : DIV0STRT      ( --- )
  162. \ The default function to perform when a DIVIDE by 0 trap occurs.
  163.                 TRUE ABORT" Divide OVERFLOW error" ;
  164.  
  165. DEFER DIV0FUNC  ' DIV0STRT IS DIV0FUNC
  166. \ F-PC traps divide by 0 errors, and calls this defered word when
  167. \ such an error is detected.
  168.  
  169. DEFER BYEFUNC   ' NOOP IS BYEFUNC
  170. \ A defered word which normally contains NOOP, provided so you
  171. \ can specify a function to be performed before leaving back to DOS.
  172.  
  173. : BYE           ( -- )
  174. \ Returns control to DOS. Performs the defered word BYEFUNC before
  175. \ actually leaving.
  176.                 RESTORE_VECTORS
  177.                 BYEFUNC
  178.                 ."  Leaving.." 0 0 BDOS  ;
  179.  
  180. : DIVIDE0       ( STATUS_reg, CS, IP, AX, BX, CX, DX, SI, BP --- )
  181. \ The actual entry point from the divide by 0 trap, this word just
  182. \ calls the deferd word DIV0FUNC.
  183.                 [ LABEL DIV0BODY ]
  184.                 DIV0FUNC BYE ;
  185.  
  186. LABEL DIV0BK
  187. \ Handle the Divide by 0 interupt processing. You cannot reliably return
  188. \ from a divide by zero interupt.
  189.                 STI
  190.                 PUSH AX
  191.                 PUSH BX
  192.                 PUSH CX
  193.                 PUSH DX
  194.                 PUSH SI
  195.                 PUSH DI
  196.                 PUSH BP
  197.                 MOV AX, # DIV0BODY 5 -
  198.                 JMP AX
  199.                 END-CODE
  200.  
  201. TRUE VALUE RESTNEXT
  202. \ A flag to determine if we want the next code restored.
  203.  
  204. LABEL SETBRK
  205. \ A subroutine not accessible directly from Forth that sets the
  206. \ various interupt vectors used by Forth.
  207.                 PUSH ES
  208.                 MOV AX, CS
  209.                 MOV DS, AX
  210.                 CMP ' RESTNEXT >BODY # 0 WORD   \ If RESTNEXT is NOT = 0
  211.             0<> IF      MOV AX, # $AD26      \ Value to restore in >NEXT
  212.                         MOV >NEXT AX         \ Restore it
  213.                         MOV AX, # $E0FF      \ Value to restore in >NEXT + 2
  214.                         MOV >NEXT 2+ AX      \ Restore it
  215.                 THEN
  216.                 MOV DX, # BIOSBK
  217.                 MOV AX, # $251B         \ BIOS Break
  218.                 INT $21
  219.                 MOV DX, # DOSBK
  220.                 MOV AX, # $2523         \ DOS Break
  221.                 INT $21
  222.                 MOV DX, # 0
  223.                 MOV AX, # $3301         \ DISABLE DOS Break
  224.                 INT $21
  225.                 MOV DX, # DIV0BK
  226.                 MOV AX, # $2500         \ BIOS Break
  227.                 INT $21
  228.                 POP ES
  229.                 RET             END-CODE
  230.  
  231. LABEL SAVEVECTORS ( --- )
  232. \ A subroutine not accessible directly from Forth that saves
  233. \ the Divide by 0 & Cntrl Brk interrupt vectors.
  234.                 PUSH ES
  235.                 MOV AX, # $351B          \ Get the interupt vector for
  236.                 INT $21                  \ BIOS control break vector
  237.                 MOV BIOSBKSAVE BX
  238.                 MOV BIOSBKSAVE 2+ ES    \ Save old vector
  239.                 MOV AX, # $3500          \ Get the interupt vector for
  240.                 INT $21                  \ DIVIDE by 0
  241.                 MOV DIV0SAVE BX
  242.                 MOV DIV0SAVE 2+ ES      \ Save old vector
  243.                 POP ES
  244.                 MOV AX, # $3300         \ Control BREAK flag status
  245.                 INT $21
  246.                 SUB DH, DH
  247.                 MOV CTRLBKSAVE DX       \ Save it away for later restoral
  248.                 RET             END-CODE
  249.  
  250. CODE SET_VECTORS ( --- )
  251. \ Set the CONTROL BREAK and DIVIDE by 0 traps to point to the
  252. \ Forth provided functions, so we can handle them smoothly.
  253.                 CALL SETBRK
  254.                 NEXT            END-CODE
  255.  
  256. CODE @REL>ABS   ( a1 --- a2 )
  257. \ Convert JMP address in a1+1 to an absolute memory address
  258.                 POP BX
  259.                 ADD BX, 1 [BX]
  260.                 ADD BX, # 3
  261.                 PUSH BX
  262.                 NEXT            END-CODE
  263.  
  264. [FORTH] ASSEMBLER
  265.  
  266. LABEL WORIG
  267. \ An inaccessible routine. You get here from the WARM entry at offset
  268. \ ORIGIN + 4, and get sent to the WARM colon definition.
  269. HERE ORIGIN 6 + - ORIGIN 4 + !-T  ( WARM ENTRY )
  270.         MOV AX, # WARMBODY 5 -
  271.         JMP AX
  272.         END-CODE
  273.  
  274. LABEL CORIG
  275. \ An inaccessible routine. You get here from the COLD entry at offset
  276. \ ORIGIN + 0, and get sent to the COLD colon definition.
  277. \ This routine expands out the compressed Forth system to its various
  278. \ segments.
  279. HERE ORIGIN 3 + - ORIGIN 1+ !-T  ( COLD ENTRY )
  280.         MOV AX, CS                      \ move CS to AX
  281.         MOV DS, AX
  282.         MOV SS, AX
  283.         MOV BX, YSTART                  \ Read YSTART
  284.         OR BX, BX 0<>                   \ If not reset, then move stuff
  285.      IF
  286.         ADD AX, ' #CODESEGS >BODY       \ Add CODE segments and LIST
  287.         ADD AX, ' #LISTSEGS >BODY       \ segments to get to head space.
  288.         MOV ES, AX                      \ move head seg to ES
  289.         MOV CX, YDP
  290.         MOV DI, # 0                     \ Clear DI
  291.         MOV SI, YSTART                  \ MOV YSTART to AX
  292.         OR CX, CX 0<>                   \ if YDP was not zero (0)
  293.         IF      CLD
  294.                 REPZ
  295.                 MOVSB                   \ move HEADS to head space
  296.                 CLD
  297.         THEN
  298.         MOV YSEG ES                     \ set YSEG to ES
  299.      THEN
  300.         MOV BX, XMOVED                  \ Has LIST been moved?
  301.         OR BX, BX 0=                    \ If not reset, then move stuff
  302.      IF
  303.         MOV AX, DS                      \ move DS to AX
  304.         ADD AX, ' #CODESEGS >BODY       \ Add 64k to get to heads
  305.         MOV ES, AX                      \ move head seg to ES
  306.         MOV CX, XSEGLEN
  307.         SHL CX, # 1                     \ MULTIPLY BY 16 DECIMAL
  308.         SHL CX, # 1
  309.         SHL CX, # 1
  310.         SHL CX, # 1
  311.         MOV DI, # 0                     \ Clear DI
  312.         MOV SI, DPSTART                 \ MOV source offset to SI
  313.         OR CX, CX 0<>                   \ if DPSTART was not zero (0)
  314.         IF      CLD             \ Forward move, NOT backwards this time.
  315.                 REPZ
  316.                 MOVSB                   \ move LISTS to LIST space
  317.                 CLD
  318.         THEN
  319.         MOV XSEG ES                     \ set XSEG to ES
  320.      THEN
  321.  
  322. \ The following few instructions patch two ADD instructions in KERNEL1, so
  323. \ we can do an ADD IMMEDIATE rather than an ADD MEMORY in NEST and DODOES.
  324.         MOV ES, XSEG                    \ Initialize ES in case we haven't??
  325.         MOV NESTPATCH 1+ ES             \ Patch NEST   ADD instruction
  326.         MOV DOESPATCH 1+ ES             \ Patch DODOES ADD instruction
  327.  
  328.         CALL SAVEVECTORS                \ Save existing vectors
  329.         MOV ' RESTNEXT >BODY # TRUE WORD \ We want NEXT restored
  330.         CALL SETBRK                     \ Install Break vectors &
  331.                                         \ restore NEXT
  332.         MOV AX, ' #CODESEGS >BODY
  333.         SUB AX, # 1                     \ One less than max
  334.         SHL AX, # 1
  335.         SHL AX, # 1
  336.         SHL AX, # 1
  337.         SHL AX, # 1
  338.  
  339.         MOV ' LIMIT 3 + AX              \ LIMIT
  340.         SUB AX, # 10
  341.         MOV ' FIRST 3 + AX              \ FIRST = LIMIT - 10h
  342.         SUB AX, # 10
  343.         MOV RP, AX                      \ RP = FIRST - 10h
  344.         MOV BX, # RP0
  345.         ADD BX, UP
  346.         MOV 0 [BX], RP                  \ RP0 = RP
  347.         SUB AX, # 250
  348.         MOV 'TIB AX                     \ TIB = RP - 250 DECIMAL
  349.         MOV BX, # SP0
  350.         ADD BX, UP
  351.         MOV 0 [BX], AX                  \ SP0 = TIB
  352.         MOV SP, AX                      \ SP = TIB
  353.         MOV ' 1STCOLD >BODY # TRUE WORD \ Make COLD to its initialization
  354.         MOV AX, COLDBODY 2-
  355.         ADD AX, XSEG
  356.         MOV ES, AX
  357.         MOV IP, # 0
  358.         NEXT
  359.         END-CODE
  360.   IN-META
  361.  
  362. \ Here we initialize the USER table with its default values.
  363. HERE UP !-T     ( SET UP USER AREA )
  364.        0 ,      ( TOS )
  365.        0 ,      ( ENTRY )
  366.        0 ,      ( LINK )
  367.        0 ,      ( ES0 )
  368. INIT-R0 256 - , ( SP0 )
  369.  INIT-R0 ,      ( RP0 )
  370.        0 ,      ( DP )          ( Must be patched later )
  371.        0 ,      ( OFFSET )
  372.       10 ,      ( BASE )
  373.        0 ,      ( HLD )
  374.    FALSE ,      ( PRINTING )
  375. ' (EMIT) ,      ( EMIT )
  376. ' (KEY?) ,      ( KEY? )
  377. ' (KEY)  ,      ( KEY  )
  378. ' (TYPE) ,      ( TYPE )
  379. ' (TYPEL) ,     ( TYPEL )
  380.  
  381. 0 , 0 , 0 , 0 , 0 ,             \ room for 10 additional USER variables
  382. 0 , 0 , 0 , 0 , 0 ,
  383.  
  384. : DEPTH         ( -- n )
  385. \ Returns the number of items on the parameter stack.
  386.                 SP@ SP0 @ SWAP - 2/   ;
  387.  
  388. VARIABLE MAX.S
  389. \ A variable that holds the maximum depth to be displayed of the
  390. \ data stack with .S following.
  391.  
  392. : .S            ( -- )
  393. \ Displays the contents of the parameter stack non destructively.
  394. \ Very useful when debugging.
  395.                 DEPTH 0< ABORT" Stack UNDERFLOW !! "
  396.                 DEPTH ?DUP MAX.S @ 1 < IF 4 MAX.S ! THEN
  397.                 IF      DUP ."  [" 1 .R ." ]" 0 SWAP 1- MAX.S @ 1- MIN
  398.                         DO I PICK 7 U.R SPACE -1 +LOOP
  399.                 ELSE    ."  Stack Empty. "  THEN ;
  400.  
  401. : %.ID          ( nfa -- )
  402. \ Display the variable length name whose name field address is on the
  403. \ stack. If it is shorter than its count, it is padded with underscores.
  404. \ Only valid Ascii is typed.
  405.                 DUP 1+ DUP YC@ ROT YC@ 31 AND 0
  406.                ?DO      DUP 127 AND FEMIT 128 AND
  407.                         IF   ASCII _ 128 OR   ELSE  1+ DUP YC@  THEN
  408.                 LOOP    2DROP SPACE ;
  409.  
  410. DEFER .ID       ' %.ID IS .ID   \ defer to allow for COLORIZER
  411. \ A defered word. Display the variable length name whose name field
  412. \ address is on the stack. If it is shorter than its count, it is
  413. \ padded with underscores. Only valid Ascii is typed.
  414.  
  415. : DUMP          ( addr len -- )
  416. \ A primitive little dump routine to help you debug after you have
  417. \ changed the system source and nothing works any more.
  418.               0 DO   CR DUP 6 .R SPACE  16 0 DO   DUP C@ 3 .R 1+   LOOP
  419.             16 +LOOP   DROP   ;
  420.  
  421. : RECURSE       ( -- )
  422. \ Makes the definition this word is used in call itself at the
  423. \ point where it is used. ie. "RECUSION"
  424.                 LAST @ NAME> X,  ;  IMMEDIATE
  425.  
  426. : H.            ( N1 --- )
  427. \ Display the unsigned number in hex, with trailing blank. Does not
  428. \ change the number base.
  429.                 BASE @ >R HEX U. R> BASE ! ;
  430.  
  431. VARIABLE LMARGIN    0 LMARGIN !-T
  432. \ The left margin setting used by ?LINE, ?CR.
  433.  
  434. VARIABLE RMARGIN   70 RMARGIN !-T
  435. \ Controls the right margin, used by ?LINE, ?CR.
  436.  
  437. VARIABLE TABSIZE    8 TABSIZE !-T
  438. \ Controls the TAB increment for TAB. Default is 8.
  439.  
  440. : ?LINE         ( n -- )
  441. \ Break the line at the cursor if there are less than n1 characters
  442. \ till RMARGIN is encountered.
  443.                 #OUT @ +  RMARGIN @ > IF CR LMARGIN @ SPACES THEN ;
  444.  
  445. : ?CR           ( -- )
  446. \ Break the line at the cursor, if we have reached the right margin
  447. \ as specified by RMARGIN.
  448.                 0 ?LINE  ;
  449.  
  450. : TAB           ( --- )
  451. \ Print spaces to get to the next TAB increment as specified by
  452. \ TABSIZE.
  453.                 #OUT @ TABSIZE @ MOD TABSIZE @ SWAP - SPACES ;
  454.  
  455. : \             ( --- )
  456. \ Comment till the end of this line.
  457.                 #TIB @ >IN ! ; IMMEDIATE
  458.  
  459. CODE SET-CURSOR ( n1 --- )
  460. \ Set the cursor shape to value n1
  461.                 POP CX
  462.                 MOV AH, # 1
  463.                 PUSH SI         PUSH BP
  464.                 INT $10
  465.                 POP BP          POP SI
  466.                 NEXT C;
  467.  
  468. : GET-CURSOR    ( --- n1 )      \ return n1 the shape of the cursor.
  469.                 0 $460 @L ;
  470.  
  471. \ : SS            ( | <name> )
  472. \                 ' >BODY @ +XSEG 0 ;
  473.  
  474. \ : NN            ( SEG OFF --- SEG OFF+2 )
  475. \                 2DUP @L DUP H. >NAME .ID 2+ ;
  476.  
  477. \ The :RESOLVES word resolves forward references in LIST space, while
  478. \ the  RESOLVES word resolves forward reverences in CODE space.
  479. \ It does not matter whether the word you are resolving is a CODE word
  480. \ or a COLON definitions, what matters is where it is being resolved which
  481. \ is typically in LIST space not CODE space.  All this to say you should
  482. \ normally use :RESOLVES rather than RESOLVES to resolve forward reverences.
  483.  
  484. \ Resolve some forward references.
  485.  
  486. ' (.")                            :RESOLVES <(.")>
  487. ' (")                             :RESOLVES <(")>
  488. ' (;CODE)                         :RESOLVES <(;CODE)>
  489. ' (;USES)                         :RESOLVES <(;USES)>
  490. ' (IS)                            :RESOLVES <(IS)>
  491. ' (ABORT")                        :RESOLVES <(ABORT")>
  492.  [ASSEMBLER] >NEXT    META         RESOLVES <VARIABLE>
  493.  [ASSEMBLER] DOUSER-DEFER META     RESOLVES <USER-DEFER>
  494.  [ASSEMBLER] DOUSER-VARIABLE META  RESOLVES <USER-VARIABLE>
  495.  
  496. ' DEFINITIONS                     :RESOLVES DEFINITIONS
  497. ' [                               :RESOLVES [
  498. ' ?MISSING                        :RESOLVES ?MISSING
  499. ' QUIT                            :RESOLVES QUIT
  500. ' .ID                             :RESOLVES .ID
  501. ' @REL>ABS                        :RESOLVES @REL>ABS
  502. ' >IS                             :RESOLVES >IS
  503.  
  504. \ Fill in some deferred words.
  505. ' CRLF          IS CR
  506. ' CR            IS STATUS
  507. ' START         IS BOOT
  508. ' (PRINT)       IS PEMIT
  509. ' (CONSOLE)     IS CONSOLE
  510.  
  511. \ Set CONTEXT and CURRENT to FORTH.
  512. ' FORTH >BODY-T CURRENT !-T
  513. ' FORTH >BODY-T CONTEXT !-T
  514.  
  515. HERE-T  DP UP @-T + !-T               \ INIT USER DP
  516. #USER-T @ #USER !-T                   \ INIT USER VAR COUNT
  517. TRUE  CAPS !-T                        \ SET TO IGNORE CASE
  518. TRUE WARNING !-T                      \ SET TO ISSUE WARNINGS
  519. 31 WIDTH !-T                          \ 31 CHARACTER NAMES
  520. VOC-LINK-T @ VOC-LINK !-T             \ INIT VOC-LINK
  521.  
  522. \ Now display the statistics for this compile.
  523.  
  524. CR
  525. CR .( Unresolved references: )          CR   .UNRESOLVED ?NEWPAGE
  526. CR .(     Statistics: )
  527. CR .( Last  Host Address:        )      [FORTH] HERE U.
  528. CR .( First Target Code Address: )      META 256 THERE U.
  529. CR .( Last  Target Code Address: )      META HERE-T THERE U.
  530.                                         META 256 THERE          \ start addr
  531.                                         SVXSEG     DPSTART !-T
  532.                                         HERE-X DROP 1+
  533.                                         0 XS: DROP - XSEGLEN !-T
  534. CR .( CODE space used:           )      HERE-T U.
  535. CR .( LIST space used:           )      HERE-X SWAP 0 XS: DROP - 16 * + U.
  536. CR .( HEAD space used:           )      HERE-Y U.
  537.                                         HERE-X DROP 1+ 0 XS: DROP -
  538.                                         DUP 16 * ALLOT-T DROP
  539.                                         0 XDP !-T
  540.                                       SVYSEG DUP
  541.                                         YSTART !-T
  542.                                         0 XMOVED !-T
  543.                                       HERE-Y +
  544.                                         HERE-Y YDP !-T
  545.                                         THERE ONLY FORTH ALSO META ALSO
  546.                                       CODESEGS 16 * OVER -
  547. CR .( Free Target Program room:  )      U.
  548.                                         SP@ HERE -
  549. CR .( Free Symbol Table bytes:   )      U.
  550.  
  551. .COMPSTAT
  552.  
  553. ( A1 N1 --- )   ZSAVE KERNEL.COM        \ Save the KERNEL.COM file.
  554.  
  555. ONLY FORTH ALSO DEFINITIONS
  556.  
  557. CR .( Now type EXTEND <enter> at the DOS prompt.)
  558. CR
  559.  
  560.