OSDN Git Service

la der de der
[fast-forth/master.git] / MSP430-FORTH / FF_SPECS.f
1 \ -*- coding: utf-8 -*-
2 \
3 \ displays all FastForth specifications
4 \ 3 kb free mandatory.
5 \
6 \ FastForth kernel compilation minimal options:
7 \ TERMINAL3WIRES, TERMINAL4WIRES
8 \ MSP430ASSEMBLER, CONDCOMP
9
10 \ TARGET ( = the name of \INC\target.pat file without extension):
11 \ MSP_EXP430FR5739  MSP_EXP430FR5969    MSP_EXP430FR5994    MSP_EXP430FR6989
12 \ MSP_EXP430FR4133  CHIPSTICK_FR2433    MSP_EXP430FR2433    MSP_EXP430FR2355
13 \ LP_MSP430FR2476
14 \ MY_MSP430FR5738_2
15 \ JMJ_BOX_2018_10_29    JMJ_BOX_2022_07_28
16 \
17 \ from scite editor : copy your TARGET selection in (shift+F8) parameter 1:
18 \                     copy COMPLEMENT if used in (shift+F8) parameter 2:
19 \
20 \ OR
21 \
22 \ from file explorer :  drag and drop this file onto SendSourceFileToTarget.bat
23 \                       then select your TARGET + COMPLEMENT when asked.
24 \
25 ; ---------------------------------
26 ; FF_SPECS.f
27 ; ---------------------------------
28
29 \ first, we do some tests allowing the download
30     CODE ABORT_FF_SPECS
31     SUB #2,PSP
32     MOV TOS,0(PSP)
33     MOV &VERSION,TOS        \ ARG
34     SUB #401,TOS            \ FastForth V4.1
35     COLON
36     'CR' EMIT               \ return to column 1, no 'LF'
37     ABORT" FastForth V4.1 please!"
38     RST_RET                 \ remove ABORT_FF_SPECS definition before resuming
39     ;
40
41     ABORT_FF_SPECS          \ run tests
42
43 ; ------------------------------------------------------------------
44 ; first we download the set of definitions we need, from CORE_ANS
45 ; ------------------------------------------------------------------
46
47     [UNDEFINED] DUP [IF]    \ define DUP and DUP?
48 \ https://forth-standard.org/standard/core/DUP
49 \ DUP      x -- x x      duplicate top of stack
50     CODE DUP
51 BW1 SUB #2,PSP      \ 2  push old TOS..
52     MOV TOS,0(PSP)  \ 3  ..onto stack
53     MOV @IP+,PC     \ 4
54     ENDCODE
55
56 \ https://forth-standard.org/standard/core/qDUP
57 \ ?DUP     x -- 0 | x x    DUP if nonzero
58     CODE ?DUP
59     CMP #0,TOS      \ 2  test for TOS nonzero
60     0<> ?GOTO BW1   \ 2
61     MOV @IP+,PC     \ 4
62     ENDCODE
63     [THEN]
64
65     [UNDEFINED] OVER [IF]
66 \ https://forth-standard.org/standard/core/OVER
67 \ OVER    x1 x2 -- x1 x2 x1
68     CODE OVER
69     MOV TOS,-2(PSP)     \ 3 -- x1 (x2) x2
70     MOV @PSP,TOS        \ 2 -- x1 (x2) x1
71     SUB #2,PSP          \ 1 -- x1 x2 x1
72     MOV @IP+,PC
73     ENDCODE
74     [THEN]
75
76     [UNDEFINED] DROP [IF]
77 \ https://forth-standard.org/standard/core/DROP
78 \ DROP     x --          drop top of stack
79     CODE DROP
80     MOV @PSP+,TOS   \ 2
81     MOV @IP+,PC     \ 4
82     ENDCODE
83     [THEN]
84
85     [UNDEFINED] SWAP [IF]
86 \ https://forth-standard.org/standard/core/SWAP
87 \ SWAP     x1 x2 -- x2 x1    swap top two items
88     CODE SWAP
89     MOV @PSP,W      \ 2
90     MOV TOS,0(PSP)  \ 3
91     MOV W,TOS       \ 1
92     MOV @IP+,PC     \ 4
93     ENDCODE
94     [THEN]
95
96     [UNDEFINED] ROT [IF]
97 \ https://forth-standard.org/standard/core/ROT
98 \ ROT    x1 x2 x3 -- x2 x3 x1
99     CODE ROT
100     MOV @PSP,W          \ 2 fetch x2
101     MOV TOS,0(PSP)      \ 3 store x3
102     MOV 2(PSP),TOS      \ 3 fetch x1
103     MOV W,2(PSP)        \ 3 store x2
104     MOV @IP+,PC
105     ENDCODE
106     [THEN]
107
108     [UNDEFINED] >R [IF]
109 \ https://forth-standard.org/standard/core/toR
110 \ >R    x --   R: -- x   push to return stack
111     CODE >R
112     PUSH TOS
113     MOV @PSP+,TOS
114     MOV @IP+,PC
115     ENDCODE
116     [THEN]
117
118     [UNDEFINED] R> [IF]
119 \ https://forth-standard.org/standard/core/Rfrom
120 \ R>    -- x    R: x --   pop from return stack ; CALL #RFROM performs DOVAR
121     CODE R>
122     SUB #2,PSP      \ 1
123     MOV TOS,0(PSP)  \ 3
124     MOV @RSP+,TOS   \ 2
125     MOV @IP+,PC     \ 4
126     ENDCODE
127     [THEN]
128
129     [UNDEFINED] 0< [IF]
130 \ https://forth-standard.org/standard/core/Zeroless
131 \ 0<     n -- flag      true if TOS negative
132     CODE 0<
133     ADD TOS,TOS     \ 1 set carry if TOS negative
134     SUBC TOS,TOS    \ 1 TOS=-1 if carry was clear
135     XOR #-1,TOS     \ 1 TOS=-1 if carry was set
136     MOV @IP+,PC     \
137     ENDCODE
138     [THEN]
139
140     [UNDEFINED] = [IF]
141 \ https://forth-standard.org/standard/core/Equal
142 \ =      x1 x2 -- flag         test x1=x2
143     CODE =
144     SUB @PSP+,TOS   \ 2
145     0<> IF          \ 2
146         AND #0,TOS  \ 1 flag Z = 1
147         MOV @IP+,PC \ 4
148     THEN
149     XOR #-1,TOS     \ 1
150     MOV @IP+,PC     \ 4
151     ENDCODE
152     [THEN]
153
154     [UNDEFINED] U< [IF] \ define U> and U>
155 \ https://forth-standard.org/standard/core/Uless
156 \ U<    u1 u2 -- flag       test u1<u2, unsigned
157     CODE U<
158     SUB @PSP+,TOS   \ 2 u2-u1
159     U< ?GOTO FW1
160     0<> IF
161 BW1 MOV #-1,TOS     \ 1
162     THEN
163     MOV @IP+,PC     \ 4
164     ENDCODE
165
166 \ https://forth-standard.org/standard/core/Umore
167 \ U>     n1 n2 -- flag
168     CODE U>
169     SUB @PSP+,TOS   \ 2
170     U< ?GOTO BW1    \ 2 flag = true, Z = 0
171 FW1 AND #0,TOS      \ 1 Z = 1
172     MOV @IP+,PC     \ 4
173     ENDCODE
174     [THEN]
175
176     [UNDEFINED] IF [IF]     \ define IF and THEN
177 \ https://forth-standard.org/standard/core/IF
178 \ IF       -- IFadr    initialize conditional forward branch
179     CODE IF
180     SUB #2,PSP              \
181     MOV TOS,0(PSP)          \
182     MOV &DP,TOS             \ -- HERE
183     ADD #4,&DP              \           compile one word, reserve one word
184     MOV #QFBRAN,0(TOS)      \ -- HERE   compile QFBRAN
185     ADD #2,TOS              \ -- HERE+2=IFadr
186     MOV @IP+,PC
187     ENDCODE IMMEDIATE
188
189 \ https://forth-standard.org/standard/core/THEN
190 \ THEN     IFadr --                resolve forward branch
191     CODE THEN
192     MOV &DP,0(TOS)          \ -- IFadr
193     MOV @PSP+,TOS           \ --
194     MOV @IP+,PC
195     ENDCODE IMMEDIATE
196     [THEN]
197
198     [UNDEFINED] ELSE [IF]
199 \ https://forth-standard.org/standard/core/ELSE
200 \ ELSE     IFadr -- ELSEadr        resolve forward IF branch, leave ELSEadr on stack
201     CODE ELSE
202     ADD #4,&DP              \ make room to compile two words
203     MOV &DP,W               \ W=HERE+4
204     MOV #BRAN,-4(W)
205     MOV W,0(TOS)            \ HERE+4 ==> [IFadr]
206     SUB #2,W                \ HERE+2
207     MOV W,TOS               \ -- ELSEadr
208     MOV @IP+,PC
209     ENDCODE IMMEDIATE
210     [THEN]
211
212     [UNDEFINED] BEGIN [IF]  \ define BEGIN UNTIL AGAIN WHILE REPEAT
213
214 \ https://forth-standard.org/standard/core/BEGIN
215 \ BEGIN    -- BEGINadr             initialize backward branch
216     CODE BEGIN
217     MOV #BEGIN,PC
218     ENDCODE IMMEDIATE
219
220 \ https://forth-standard.org/standard/core/UNTIL
221 \ UNTIL    BEGINadr --             resolve conditional backward branch
222     CODE UNTIL              \ immediate
223     MOV #QFBRAN,X
224 BW1 ADD #4,&DP          \ compile two words
225     MOV &DP,W           \ W = HERE
226     MOV X,-4(W)         \ compile Bran or QFBRAN at HERE
227     MOV TOS,-2(W)       \ compile bakcward adr at HERE+2
228     MOV @PSP+,TOS
229     MOV @IP+,PC
230     ENDCODE IMMEDIATE
231
232 \ https://forth-standard.org/standard/core/AGAIN
233 \ AGAIN    BEGINadr --             resolve uncondionnal backward branch
234     CODE AGAIN
235     MOV #BRAN,X
236     GOTO BW1
237     ENDCODE IMMEDIATE
238
239 \ https://forth-standard.org/standard/core/WHILE
240 \ WHILE    BEGINadr -- WHILEadr BEGINadr
241     : WHILE
242     POSTPONE IF SWAP
243     ; IMMEDIATE
244
245 \ https://forth-standard.org/standard/core/REPEAT
246 \ REPEAT   WHILEadr BEGINadr --     resolve WHILE loop
247     : REPEAT
248     POSTPONE AGAIN POSTPONE THEN
249     ; IMMEDIATE
250     [THEN]
251
252     [UNDEFINED] DO [IF] \ define DO LOOP +LOOP
253
254     HDNCODE XDO         \ DO run time
255     MOV #$8000,X        \ 2 compute 8000h-limit = "fudge factor"
256     SUB @PSP+,X         \ 2
257     MOV TOS,Y           \ 1 loop ctr = index+fudge
258     ADD X,Y             \ 1 Y = INDEX
259     PUSHM #Z,X          \ 4 PUSHM X,Y, i.e. PUSHM LIMIT, INDEX
260     MOV @PSP+,TOS       \ 2
261     MOV @IP+,PC         \ 4
262     ENDCODE
263
264 \ https://forth-standard.org/standard/core/DO
265 \ DO       -- DOadr   L: -- 0
266     CODE DO
267     SUB #2,PSP              \
268     MOV TOS,0(PSP)          \
269     ADD #2,&DP              \   make room to compile xdo
270     MOV &DP,TOS             \ -- HERE+2
271     MOV #XDO,-2(TOS)        \   compile xdo
272     ADD #2,&LEAVEPTR        \ -- HERE+2     LEAVEPTR+2
273     MOV &LEAVEPTR,W         \
274     MOV #0,0(W)             \ -- HERE+2     L-- 0
275     MOV @IP+,PC
276     ENDCODE IMMEDIATE
277
278     HDNCODE XLOOP       \   LOOP run time
279     ADD #1,0(RSP)       \ 4 increment INDEX
280 BW1 BIT #$100,SR        \ 2 is overflow bit set?
281     0= IF               \   branch if no overflow
282         MOV @IP,IP
283         MOV @IP+,PC
284     THEN
285     ADD #4,RSP          \ 1 empties RSP
286     ADD #2,IP           \ 1 overflow = loop done, skip branch ofs
287     MOV @IP+,PC         \ 4 14~ taken or not taken xloop/loop
288     ENDCODE             \
289
290 \ https://forth-standard.org/standard/core/LOOP
291 \ LOOP    DOadr --         L-- an an-1 .. a1 0
292     CODE LOOP
293     MOV #XLOOP,X
294 BW2 ADD #4,&DP              \ make room to compile two words
295     MOV &DP,W
296     MOV X,-4(W)             \ xloop --> HERE
297     MOV TOS,-2(W)           \ DOadr --> HERE+2
298     BEGIN                   \ resolve all "leave" adr
299         MOV &LEAVEPTR,TOS   \ -- Adr of top LeaveStack cell
300         SUB #2,&LEAVEPTR    \ --
301         MOV @TOS,TOS        \ -- first LeaveStack value
302         CMP #0,TOS          \ -- = value left by DO ?
303     0<> WHILE
304         MOV W,0(TOS)        \ move adr after loop as UNLOOP adr
305     REPEAT
306     MOV @PSP+,TOS
307     MOV @IP+,PC
308     ENDCODE IMMEDIATE
309
310     HDNCODE XPLOO   \   +LOOP run time
311     ADD TOS,0(RSP)  \ 4 increment INDEX by TOS value
312     MOV @PSP+,TOS   \ 2 get new TOS, doesn't change flags
313     GOTO BW1        \ 2
314     ENDCODE         \
315
316 \ https://forth-standard.org/standard/core/PlusLOOP
317 \ +LOOP   adrs --   L-- an an-1 .. a1 0
318     CODE +LOOP
319     MOV #XPLOO,X
320     GOTO BW2
321     ENDCODE IMMEDIATE
322     [THEN]
323
324     [UNDEFINED] I [IF]
325 \ https://forth-standard.org/standard/core/I
326 \ I        -- n   R: sys1 sys2 -- sys1 sys2
327 \                  get the innermost loop index
328     CODE I
329     SUB #2,PSP              \ 1 make room in TOS
330     MOV TOS,0(PSP)          \ 3
331     MOV @RSP,TOS            \ 2 index = loopctr - fudge
332     SUB 2(RSP),TOS          \ 3
333     MOV @IP+,PC             \ 4 13~
334     ENDCODE
335     [THEN]
336
337     [UNDEFINED] HERE [IF]
338     CODE HERE
339     MOV #BEGIN,PC
340     ENDCODE
341     [THEN]
342
343     [UNDEFINED] C@ [IF]
344 \ https://forth-standard.org/standard/core/CFetch
345 \ C@     c-addr -- char   fetch char from memory
346     CODE C@
347     MOV.B @TOS,TOS
348     MOV @IP+,PC
349     ENDCODE
350     [THEN]
351
352     [UNDEFINED] SPACES [IF]
353 \ https://forth-standard.org/standard/core/SPACES
354 \ SPACES   n --            output n spaces
355     CODE SPACES
356     CMP #0,TOS
357     0<> IF
358         PUSH IP
359         BEGIN
360             LO2HI
361             'SP' EMIT
362             HI2LO
363             SUB #1,TOS
364         0= UNTIL
365         MOV @RSP+,IP
366     THEN
367     MOV @PSP+,TOS           \ --         drop n
368     MOV @IP+,PC
369     ENDCODE
370     [THEN]
371
372     [UNDEFINED] 1+ [IF]
373 \ https://forth-standard.org/standard/core/OnePlus
374 \ 1+      n1/u1 -- n2/u2       add 1 to TOS
375     CODE 1+
376     ADD #1,TOS
377     MOV @IP+,PC
378     ENDCODE
379     [THEN]
380
381     [UNDEFINED] + [IF]
382 \ https://forth-standard.org/standard/core/Plus
383 \ +       n1/u1 n2/u2 -- n3/u3     add n1+n2
384     CODE +
385     ADD @PSP+,TOS
386     MOV @IP+,PC
387     ENDCODE
388     [THEN]
389
390     [UNDEFINED] - [IF]
391 \ https://forth-standard.org/standard/core/Minus
392 \ -      n1/u1 n2/u2 -- n3/u3     n3 = n1-n2
393     CODE -
394     SUB @PSP+,TOS   \ 2  -- n2-n1 ( = -n3)
395     XOR #-1,TOS     \ 1
396     ADD #1,TOS      \ 1  -- n3 = -(n2-n1) = n1-n2
397     MOV @IP+,PC
398     ENDCODE
399     [THEN]
400
401     [UNDEFINED] 2* [IF]
402 \ https://forth-standard.org/standard/core/TwoTimes
403 \ 2*      x1 -- x2         arithmetic left shift
404     CODE 2*
405     ADD TOS,TOS
406     MOV @IP+,PC
407     ENDCODE
408     [THEN]
409
410     [UNDEFINED] 2/ [IF]
411 \ https://forth-standard.org/standard/core/TwoDiv
412 \ 2/      x1 -- x2        arithmetic right shift
413     CODE 2/
414     RRA TOS
415     MOV @IP+,PC
416     ENDCODE
417     [THEN]
418
419     [UNDEFINED] UM/MOD [IF]
420 \ https://forth-standard.org/standard/core/UMDivMOD
421 \ UM/MOD   udlo|udhi u1 -- r q   unsigned 32/16->r16 q16
422     CODE UM/MOD
423     PUSH #DROP      \
424     MOV #MUSMOD,PC  \ execute MUSMOD then return to DROP
425     ENDCODE
426     [THEN]
427
428     [UNDEFINED] MOVE [IF]
429 \ https://forth-standard.org/standard/core/MOVE
430 \ MOVE    addr1 addr2 u --     smart move
431 \             VERSION FOR 1 ADDRESS UNIT = 1 CHAR
432     CODE MOVE
433     MOV TOS,W           \ W = cnt
434     MOV @PSP+,Y         \ Y = addr2 = dst
435     MOV @PSP+,X         \ X = addr1 = src
436     MOV @PSP+,TOS       \ pop new TOS
437     CMP #0,W            \ count = 0 ?
438     0<> IF              \ if 0, already done !
439         CMP X,Y         \ Y-X \ dst - src
440         0<> IF          \ if dst = src, already done !
441             U< IF       \ U< if src > dst
442                 BEGIN   \ copy W bytes
443                     MOV.B @X+,0(Y)
444                     ADD #1,Y
445                     SUB #1,W
446                 0= UNTIL
447                 MOV @IP+,PC
448             THEN        \ U>= if dst > src
449             ADD W,Y     \ copy W bytes beginning with the end
450             ADD W,X
451             BEGIN
452                 SUB #1,X
453                 SUB #1,Y
454                 MOV.B @X,0(Y)
455                 SUB #1,W
456             0= UNTIL
457         THEN
458     THEN
459     MOV @IP+,PC
460     ENDCODE
461     [THEN]
462
463     [UNDEFINED] CR [IF]
464 \ https://forth-standard.org/standard/core/CR
465 \ CR      --               send CR+LF to the output device
466
467 \ create a primary defered word, i.e. with its default runtime beginning at the >BODY of the definition
468     CODE CR     \ part I : DEFERed definition of CR
469     MOV #NEXT_ADR,PC                \ [PFA] = NEXT_ADR
470     ENDCODE
471
472     :NONAME     \ part II : :NONAME part as default runtime of CR
473     'CR' EMIT 'LF' EMIT
474     ; IS CR                         \ set [PFA] of CR = >BODY addr of CR = CFA of :NONAME part
475
476     [THEN]
477
478     [UNDEFINED] CASE [IF]   \ define CASE OF ENDOF ENDCASE
479
480 \ https://forth-standard.org/standard/core/CASE
481     : CASE
482     0
483     ; IMMEDIATE \ -- #of-1
484
485 \ https://forth-standard.org/standard/core/OF
486     : OF \ #of-1 -- orgOF #of
487     1+                      \ count OFs
488     >R                      \ move off the stack in case the control-flow stack is the data stack.
489     POSTPONE OVER
490     POSTPONE =              \ copy and test case value
491     POSTPONE IF             \ add orig to control flow stack
492     POSTPONE DROP               \ discards case value if =
493     R>                      \ we can bring count back now
494     ; IMMEDIATE
495
496 \ https://forth-standard.org/standard/core/ENDOF
497     : ENDOF \ orgOF #of -- orgENDOF #of
498     >R                      \ move off the stack in case the control-flow stack is the data stack.
499     POSTPONE ELSE
500     R>                      \ we can bring count back now
501     ; IMMEDIATE
502
503 \ https://forth-standard.org/standard/core/ENDCASE
504     : ENDCASE \ orgENDOF1..orgENDOFn #of --
505     POSTPONE DROP
506     0 DO
507         POSTPONE THEN
508     LOOP
509     ; IMMEDIATE
510     [THEN]
511
512 ; --------------------------
513 ; end of definitions we need
514 ; --------------------------
515
516     CODE 2*DUP
517     SUB #2,PSP
518     ADD TOS,TOS
519     MOV TOS,0(PSP)
520     MOV @IP+,PC
521     ENDCODE
522
523     [UNDEFINED] S? [IF] \
524     CODE S?             \  sep ---          to compile: sep S? <string>sep
525     MOV #S"+$0A,PC      \                   (S" + 10) --> PC
526     ENDCODE IMMEDIATE
527     [THEN]
528
529     [UNDEFINED] ESC [IF]
530     CODE ESC            \ we can't use \e which is trapped by TERMINAL !
531     CMP #0,&STATEADR
532     0= IF MOV @IP+,PC   \ interpret time usage disallowed
533     THEN
534     COLON
535     'ESC'               \ -- char escape
536     POSTPONE LITERAL    \ compile-time code : lit 'ESC'
537     POSTPONE EMIT       \ compile-time code : EMIT
538     'SP'                \ char SPACE as separator for end of string
539     POSTPONE S?         \ compile-time code : S?
540     POSTPONE TYPE       \ compile-time code : TYPE
541     ; IMMEDIATE
542     [THEN]
543
544     [DEFINED] FORTH [IF]    \ word-set addon ?
545 \ NFA address is always even
546 \ [NFA] = count_of_string + Immediate_flag
547 \ NFA + count_of_string_odd = CFA
548 \ NFA + count_of_string_even + 1 = CFA
549     CODE BODY>SQNFA     \ BODY -- NFA(addr cnt)             BODY > SQuoteNFA
550     SUB #2,PSP          \ -- x BODY
551     SUB #4,TOS          \ -- x CFA
552     MOV TOS,Y           \               Y = CFA
553     MOV Y,X             \               X = CFA
554     BEGIN
555         SUB #2,X        \ --            X = CFA-2i = NFA ?
556         MOV X,0(PSP)    \ -- CFA-2i x
557         MOV.B @X+,TOS   \ -- CFA-2i cnt_test+Imm
558         RRA TOS         \ -- CFA-2I cnt_test
559         MOV TOS,W       \
560         ADD #1,TOS
561         BIT #1,W        \                   cnt_test even ?
562         0= IF
563             ADD #1,W    \                   if yes add #1 to cnt_test
564         THEN
565         ADD X,W         \                   CFA-2i + aligned_cnt_test
566         CMP W,Y         \                   CFA-2i + aligned_cnt_test = CFA ?
567     0<> WHILE           \                   out of loop if yes
568         MOV @PSP,X      \                   loop back to test with CFA-2(i+1)
569     REPEAT
570     MOV @IP+,PC         \ -- addr cnt
571     ENDCODE
572     [THEN]
573
574     : SPECS             \ to see all FastForth specifications
575 \
576     RST_RET             \ before computing free bytes, remove all FF_SPECS previous definitions
577     ECHO
578     ESC [8;42;80t       \ set 42L * 80C terminal display
579 \
580 \   title in reverse video
581     CR
582     ESC [7m             \ Turn reverse video on
583     CR ." FastForth V"
584     VERSION @
585     0 <# # 'BS' HOLD # '.' HOLD #S #> TYPE
586     ."  for MSP430FR"
587     HERE                \ HERE - MAIN_ORG = bytes code
588     DEVICEID @          \ value kept in TLV area
589     CASE
590 \
591 \ device_ID OF  ." xxxx," $MAIN_ORG ENDOF \ <-- add here your device
592     $8102   OF  ." 5738,"   $C200   ENDOF
593     $8103   OF  ." 5739,"   $C200   ENDOF
594     $810D   OF  ." 5986,"   $4400   ENDOF
595     $8160   OF  ." 5948,"   $4400   ENDOF
596     $8169   OF  ." 5969,"   $4400   ENDOF
597     $81A8   OF  ." 6989,"   $4400   ENDOF
598     $81F0   OF  ." 4133,"   $C400   ENDOF
599     $8240   OF  ." 2433,"   $C400   ENDOF
600     $825D   OF  ." 5972,"   $4400   ENDOF
601     $82A1   OF  ." 5994,"   $4000   ENDOF
602     $830C   OF  ." 2355,"   $8000   ENDOF
603     $830D   OF  ." 2353,"   $C000   ENDOF
604     $831E   OF  ." 2155,"   $8000   ENDOF
605     $831D   OF  ." 2153,"   $C000   ENDOF
606     $832A   OF  ." 2476,"   $8000   ENDOF
607     $832B   OF  ." 2475,"   $8000   ENDOF
608     $833C   OF  ." 2633,"   $C400   ENDOF
609     $833D   OF  ." 2533,"   $C400   ENDOF
610     ABORT" xxxx <-- unrecognized device!"
611     ENDCASE                             \ -- HERE MAIN_ORG
612     ."  DTC"
613     ['] ['] DUP @ $1284 =               \ DOCOL = CALL rDOCOL opcode
614     IF ." =1," DROP                     \ [CFA] = CALL rDOCOL
615     ELSE 2 + @ $1284 =                  \
616         IF ." =2,"                      \ [CFA] = PUSH IP, [CFA+2] = CALL rDOCOL
617         ELSE ." =3,"                    \ [CFA] = PUSH IP, [CFA+2] = MOV PC,IP
618         THEN
619     THEN
620     'SP' EMIT
621     THREADS @ U. 'BS' EMIT
622     ." -Entry word set, "               \ number of Entry word set,
623     FREQ_KHZ @ 0 1000 UM/MOD U.         \ frequency
624     ?DUP IF 'BS' EMIT ',' EMIT U.       \ if remainder
625     THEN ." MHz, "                      \ MCLK
626     - U. ." bytes"                      \ HERE - MAIN_ORG = number of bytes code,
627     ESC [0m                             \ Turn off character attributes
628     CR
629
630 \
631 \   FORTH specs
632     ." /COUNTED-STRING   = 255" CR
633     ." /HOLD             = 34" CR
634     ." /PAD              = 84" CR
635     ." ADDRESS-UNIT-BITS = 16" CR
636     ." FLOORED DIVISION  = "
637     [DEFINED] SM/REM [IF] ." false" [THEN]
638     [DEFINED] FM/MOD [IF] ." true" [THEN]
639     CR
640     ." MAX-CHAR          = 255" CR
641     ." MAX-N             = 32767" CR
642     ." MAX-U             = 65535" CR
643     ." MAX-D             = 2147483647" CR
644     ." MAX-UD            = 4294967295" CR
645     ." STACK-CELLS       = 48" CR
646     ." RETURN-STACK-CELLS= 48" CR
647     ." Definitions are forced UPPERCASE" CR
648 \    ." BACKGROUND, COLD, WARM, ABORT customizable" CR
649 \    ." automatic garbage collector" CR
650
651 \   kernel specs
652     CR ESC [7m ." KERNEL add-ons" ESC [0m CR  \ subtitle in reverse video
653     KERNEL_ADDON @
654     2*DUP   0< IF ." 32.768kHz LF XTAL" CR THEN         \ BIT14
655     2*DUP   0< IF ." /CTS " THEN                        \ BIT13
656     2*DUP   0< IF ." /RTS " THEN                        \ BIT12
657     2*DUP   0< IF ." XON/XOFF "  THEN                   \ BIT11
658     2*DUP   0< IF ." Half-Duplex "  THEN                \ BIT10
659     2*DUP   0< IF ." I2C_Master TERMINAL"               \ BIT9
660             ELSE  ." UART TERMINAL"                     \ /BIT9
661             THEN CR
662     2*DUP   0< IF 2*DUP
663                 0< IF ." DOUBLE and "                   \  BIT8 + BIT7
664                 THEN  ." Q15.16 numbers handling" CR
665             ELSE  2*DUP
666                 0< IF ." DOUBLE numbers handling" CR    \ /BIT8 + BIT7
667                 THEN
668             THEN
669     2*DUP   0< IF       ." MSP430 16/20bits"            \ BIT6   BIT5
670             ELSE  2*DUP ." MSP430 16bits"               \ /BIT6
671                 0< IF   ."  (20bits addr)"              \        BIT5
672                 THEN
673             THEN    ."  assembler, with TI's syntax" CR
674     DROP
675     [DEFINED] FORTH [IF] ." word-set management" CR 
676     [THEN]
677     [DEFINED] LOAD" [IF] ." SD_CARD Load + Bootloader" CR
678     [THEN]
679     [DEFINED] READ" [IF] ." SD_CARD Read/Write/Del/CopyTERM2SD" CR
680     [THEN]
681
682 \   extensions
683     CR ESC [7m ." EXTENSIONS" ESC [0m   \ subtitle in reverse video
684     [DEFINED] {CORE_ANS} [IF] CR ." CORE ANS94 'CORETEST passed'"
685     [THEN]
686     [DEFINED] {DOUBLE}   [IF] CR ." DOUBLE numbers set"
687     [THEN]
688     [DEFINED] {UTILITY}  [IF] CR ." UTILITY"
689     [THEN]
690     [DEFINED] {FIXPOINT} [IF] CR ." Q15.16 ADD SUB MUL DIV"
691     [THEN]
692     [DEFINED] {CORDIC}   [IF] CR ." CORDIC engine"
693     [THEN]
694     [DEFINED] {SD_TOOLS} [IF] CR ." SD_TOOLS"
695     [THEN]
696     [DEFINED] {RTC}      [IF] CR ." RTC utility"
697     [THEN]
698     [DEFINED] {UARTI2CS} [IF] CR ." UART to I2C_FastForth bridge"
699     [THEN]
700     CR
701
702 \   display word-sets
703 \   ------------------------------------\
704     LASTVOC                             \ -- VOCLINK addr.
705     BEGIN
706         @ ?DUP                          \ -- VOCLINK            word-set here ?
707     WHILE                               \ -- VLK
708 \       --------------------------------\
709         ESC [7m                         \                       word-set TITLE in reverse video
710         DUP THREADS @ 2* -              \ -- VLK WORDSET_BODY
711         [DEFINED] FORTH                 \                       word-set addon ?
712         [IF]    DUP BODY>SQNFA          \ -- VLK WRDST_BODY addr cnt
713         [ELSE]  OVER @                  \ -- VLK WRDST_BODY NEXT_VLINK
714                 IF S" hidden"           \                       if next_vlink <>0
715                 ELSE S" FORTH"          \                       if next_vlink = 0
716                 THEN                    \ -- VLK WRDST_BODY addr cnt
717         [THEN]  TYPE                    \                       type word-set name
718         ."  word-set"                   \ -- VLK WRDST_BODY
719         ESC [0m CR
720 \       --------------------------------\
721 \       : WORDS                         \ --
722 \       --------------------------------\
723 \       CR                              \
724 \       CONTEXT @                       \ -- VOC_BODY
725         PAD_ORG                         \ -- VOC_BODY PAD                  MOVE all threads from VOC_BODY to PAD_ORG
726         THREADS @ 2*                    \ -- VOC_BODY PAD THREADS*2
727         MOVE                            \ -- vocabulary entries are copied in PAD_ORG
728         BEGIN                           \ --
729             0 DUP                       \ -- ptr=0 MAX=0
730             THREADS @ 2* 0              \ -- ptr=0 MAX=0 THREADS*2 0
731                 DO                      \ -- ptr MAX            I =  PAD_ptr = thread*2
732                 DUP I PAD_ORG + @       \ -- ptr MAX MAX NFAx
733                     U< IF               \ -- ptr MAX            if MAX U< NFAx
734                         DROP DROP I     \ --                    drop ptr and MAX
735                         DUP PAD_ORG + @ \ -- new_ptr new_MAX
736                     THEN                \
737                 2 +LOOP                 \ -- ptr MAX
738             ?DUP                        \ -- ptr MAX MAX | -- ptr 0 (all threads in PAD = 0)
739         WHILE                           \ -- ptr MAX                    replace it by its LFA
740             DUP                         \ -- ptr MAX MAX
741             2 - @                       \ -- ptr MAX [LFA]
742             ROT                         \ -- MAX [LFA] ptr
743             PAD_ORG +                   \ -- MAX [LFA] thread
744             !                           \ -- MAX                MAX=highest_NFA [LFA]=new_NFA updates PAD_ORG+ptr
745             COUNT 2/                    \ -- addr name_count    2/ to hide Immediate flag
746             DUP >R TYPE                 \ --      R-- count
747             $10 R> - SPACES             \ --      R--           complete with spaces modulo 16 chars
748         REPEAT                          \ --
749         DROP                            \ ptr --
750 \       ;                               \ all threads in PAD are filled with 0
751 \       --------------------------------\
752         CR                              \ -- VLINK              definitions display
753     REPEAT
754 \   ------------------------------------\ --
755     SYS                                 \ [0] SYS = WARM
756     ;
757
758 SPECS \ performs RST_RET and displays FastForth specs