OSDN Git Service

la der de der
[fast-forth/master.git] / MSP430-FORTH / SD_TEST.f
1 \ -*- coding: utf-8 -*-
2 \
3 \ to see kernel options, download FastForthSpecs.f
4 \ FastForth kernel options: MSP430ASSEMBLER, CONDCOMP, SD_CARD_READ_WRITE
5 \
6 \ TARGET SELECTION ( = the name of \INC\target.pat file without the extension)
7 \ MSP_EXP430FR5739  MSP_EXP430FR5969    MSP_EXP430FR5994    MSP_EXP430FR6989
8 \ MSP_EXP430FR4133  MSP_EXP430FR2433    MSP_EXP430FR2355    CHIPSTICK_FR2433
9 \ LP_MSP430FR2476
10 \
11 \ from scite editor : copy your target selection in (shift+F8) parameter 1:
12 \
13 \ OR
14 \
15 \ drag and drop this file onto SendSourceFileToTarget.bat
16 \ then select your TARGET when asked.
17 \
18 \
19 \
20 \
21 \ how to test SD_CARD driver on your launchpad:
22 \
23 \
24 \ remove the jumpers RX, TX of programming port (don't remove GND, TST, RST and VCC)
25 \ wire PL2303TA/HXD: GND <-> GND, RX <-- TX, TX --> RX
26 \ connect it to your PC on a free USB port
27 \ connect the PL2303TA/HXD cable to your PC on another free USB port
28 \ configure TERATERM as indicated in forthMSP430FR.asm
29 \
30 \
31 \ if you have a MSP-EXP430FR5994 launchpad, program it with MSP_EXP430FR5994_xbauds_SD_CARD.txt
32 \ to do, drag and drop this file onto prog.bat
33 \ nothing else to do!
34 \
35 \
36 \ else edit forthMSP430FR.asm with scite editor
37 \   uncomment your target, copy it
38 \   paste it into (SHIFT+F8) param1
39 \   set DTC .equ 1
40 \       FREQUENCY   .equ 16
41 \       THREADS     .equ 16
42 \       TERMINALBAUDRATE    .equ what_you_want
43 \
44 \   uncomment:  CONDCOMP
45 \               MSP430ASSEMBLER
46 \               SD_CARD_LOADER
47 \               SD_CARD_READ_WRITE
48 \
49 \   compile for your target (CTRL+0)
50 \
51 \   program your target via TI interface (CTRL+1)
52 \
53 \   then wire your SD_Card module as described in your MSP430-FORTH\target.pat file
54 \
55 \
56 \
57 \ format FAT16 or FAT32 a SD_CARD memory (max 64GB) with "FRxxxx" in the disk name
58 \ drag and drop \MSP430_COND\MISC folder on the root of this SD_CARD memory (FastForth doesn't do yet)
59 \ put it in your target SD slot
60 \ if no reset, type COLD from the console input (teraterm) to reset FAST FORTH
61 \
62 \ with MSP430FR5xxx or MSP430FR6xxx targets, you can first set RTC:
63 \ by downloading RTC.f with SendSourceFileToTarget.bat
64 \ then terminal input asks you to type (with spaces) (DMY), then (HMS),
65 \ So, subsequent copied files will be dated:
66 \
67 \ with CopySourceFileToTarget_SD_Card.bat (or better, from scite editor, menu tools):
68 \
69 \   copy TESTASM.4TH        to \MISC\TESTASM.4TH    (add path \MISC in the window opened by TERATERM)
70 \   copy TSTWORDS.4TH       to \TSTWORDS.4TH
71 \   copy CORETEST.4TH       to \CORETEST.4TH
72 \   copy SD_TOOLS.f         to \SD_TOOLS.4TH
73 \   copy SD_TEST.f          to \SD_TEST.4TH
74 \   copy PROG100k.f         to \PROG100k.4TH
75 \   copy RTC.f              to \RTC.4TH             ( doesn't work with if FR2xxx or FR4xxx)
76
77 ; --------------------------------
78 ; SD_TEST.f
79 ; --------------------------------
80
81 \ first, we do some tests allowing the download
82     CODE ABORT_SD_TEST
83     SUB #4,PSP
84     MOV TOS,2(PSP)
85     [UNDEFINED] WRITE  
86     [IF]
87         MOV #-1,0(PSP)
88     [ELSE]
89         MOV #0,0(PSP)
90     [THEN]
91     MOV &VERSION,TOS
92     SUB #401,TOS        \ FastForth V4.1
93     COLON
94     'CR' EMIT           \ return to column 1 without 'LF'
95     ABORT" FastForth V4.1 please!"
96     ABORT" build FastForth with SD_CARD_READ_WRITE addon!"
97     RST_RET             \ remove ABORT_SD_TEST definition before resuming
98     ;
99
100     ABORT_SD_TEST
101
102 ; ------------------------------------------------------------------
103 ; first we download the set of definitions we need (from CORE_ANS.f)
104 ; ------------------------------------------------------------------
105
106 \ https://forth-standard.org/standard/core/EXIT
107 \ EXIT     --      exit a colon definition; CALL #EXIT performs ASMtoFORTH (10 cycles)
108 \                                           JMP #EXIT performs EXIT
109     [UNDEFINED] EXIT
110     [IF]
111     CODE EXIT
112     MOV @RSP+,IP    \ 2 pop previous IP (or next PC) from return stack
113     MOV @IP+,PC     \ 4 = NEXT
114     ENDCODE         \ 6 (ITC-2)
115     [THEN]
116
117 \ https://forth-standard.org/standard/core/SWAP
118 \ SWAP     x1 x2 -- x2 x1    swap top two items
119     [UNDEFINED] SWAP
120     [IF]
121     CODE SWAP
122     MOV @PSP,W      \ 2
123     MOV TOS,0(PSP)  \ 3
124     MOV W,TOS       \ 1
125     MOV @IP+,PC     \ 4
126     ENDCODE
127     [THEN]
128
129 \ https://forth-standard.org/standard/core/toBODY
130 \ >BODY     -- addr      leave BODY of a CREATEd word\ also leave default ACTION-OF primary DEFERred word
131     [UNDEFINED] >BODY
132     [IF]
133     CODE >BODY
134     ADD #4,TOS
135     MOV @IP+,PC
136     ENDCODE
137     [THEN]
138
139 \ https://forth-standard.org/standard/core/ZeroEqual
140 \ 0=     n/u -- flag    return true if TOS=0
141     [UNDEFINED] 0=
142     [IF]
143     CODE 0=
144     SUB #1,TOS      \ borrow (clear cy) if TOS was 0
145     SUBC TOS,TOS    \ TOS=-1 if borrow was set
146     MOV @IP+,PC
147     ENDCODE
148     [THEN]
149
150 \ https://forth-standard.org/standard/core/IF
151 \ IF       -- IFadr    initialize conditional forward branch
152     [UNDEFINED] IF
153     [IF]     \ define IF and THEN
154     CODE IF       \ immediate
155     SUB #2,PSP              \
156     MOV TOS,0(PSP)          \
157     MOV &DP,TOS             \ -- HERE
158     ADD #4,&DP            \           compile one word, reserve one word
159     MOV #QFBRAN,0(TOS)      \ -- HERE   compile QFBRAN
160     ADD #2,TOS              \ -- HERE+2=IFadr
161     MOV @IP+,PC
162     ENDCODE IMMEDIATE
163
164 \ https://forth-standard.org/standard/core/THEN
165 \ THEN     IFadr --                resolve forward branch
166     CODE THEN               \ immediate
167     MOV &DP,0(TOS)          \ -- IFadr
168     MOV @PSP+,TOS           \ --
169     MOV @IP+,PC
170     ENDCODE IMMEDIATE
171     [THEN]
172
173 \ https://forth-standard.org/standard/core/ELSE
174 \ ELSE     IFadr -- ELSEadr        resolve forward IF branch, leave ELSEadr on stack
175     [UNDEFINED] ELSE
176     [IF]
177     CODE ELSE     \ immediate
178     ADD #4,&DP              \ make room to compile two words
179     MOV &DP,W               \ W=HERE+4
180     MOV #BRAN,-4(W)
181     MOV W,0(TOS)            \ HERE+4 ==> [IFadr]
182     SUB #2,W                \ HERE+2
183     MOV W,TOS               \ -- ELSEadr
184     MOV @IP+,PC
185     ENDCODE IMMEDIATE
186     [THEN]
187
188 \ https://forth-standard.org/standard/core/BEGIN
189 \ BEGIN    -- BEGINadr             initialize backward branch
190     [UNDEFINED] BEGIN
191     [IF]  \ define BEGIN UNTIL AGAIN WHILE REPEAT
192     CODE BEGIN
193     MOV #BEGIN,PC
194     ENDCODE IMMEDIATE
195
196 \ https://forth-standard.org/standard/core/UNTIL
197 \ UNTIL    BEGINadr --             resolve conditional backward branch
198     CODE UNTIL              \ immediate
199     MOV #QFBRAN,X
200 BW1 ADD #4,&DP          \ compile two words
201     MOV &DP,W           \ W = HERE
202     MOV X,-4(W)         \ compile Bran or QFBRAN at HERE
203     MOV TOS,-2(W)       \ compile bakcward adr at HERE+2
204     MOV @PSP+,TOS
205     MOV @IP+,PC
206     ENDCODE IMMEDIATE
207
208 \ https://forth-standard.org/standard/core/AGAIN
209 \ AGAIN    BEGINadr --             resolve uncondionnal backward branch
210     CODE AGAIN     \ immediate
211     MOV #BRAN,X
212     GOTO BW1
213     ENDCODE IMMEDIATE
214
215 \ https://forth-standard.org/standard/core/WHILE
216 \ WHILE    BEGINadr -- WHILEadr BEGINadr
217     : WHILE     \ immediate
218     POSTPONE IF SWAP
219     ; IMMEDIATE
220
221 \ https://forth-standard.org/standard/core/REPEAT
222 \ REPEAT   WHILEadr BEGINadr --     resolve WHILE loop
223     : REPEAT
224     POSTPONE AGAIN POSTPONE THEN
225     ; IMMEDIATE
226     [THEN]
227
228 \ https://forth-standard.org/standard/core/DO
229 \ DO       -- DOadr   L: -- 0
230     [UNDEFINED] DO
231     [IF]                \ define DO LOOP +LOOP
232     HDNCODE XDO         \ DO run time
233     MOV #$8000,X        \ 2 compute 8000h-limit = "fudge factor"
234     SUB @PSP+,X         \ 2
235     MOV TOS,Y           \ 1 loop ctr = index+fudge
236     ADD X,Y             \ 1 Y = INDEX
237     PUSHM #2,X          \ 4 PUSHM X,Y, i.e. PUSHM LIMIT, INDEX
238     MOV @PSP+,TOS       \ 2
239     MOV @IP+,PC         \ 4
240     ENDCODE
241
242     CODE DO
243     SUB #2,PSP              \
244     MOV TOS,0(PSP)          \
245     ADD #2,&DP              \   make room to compile xdo
246     MOV &DP,TOS             \ -- HERE+2
247     MOV #XDO,-2(TOS)        \   compile xdo
248     ADD #2,&LEAVEPTR        \ -- HERE+2     LEAVEPTR+2
249     MOV &LEAVEPTR,W         \
250     MOV #0,0(W)             \ -- HERE+2     L-- 0
251     MOV @IP+,PC
252     ENDCODE IMMEDIATE
253
254 \ https://forth-standard.org/standard/core/LOOP
255 \ LOOP    DOadr --         L-- an an-1 .. a1 0
256     HDNCODE XLOOP       \   LOOP run time
257     ADD #1,0(RSP)       \ 4 increment INDEX
258 BW1 BIT #$100,SR        \ 2 is overflow bit set?
259     0= IF               \   branch if no overflow
260         MOV @IP,IP
261         MOV @IP+,PC
262     THEN
263     ADD #4,RSP          \ 1 empties RSP
264     ADD #2,IP           \ 1 overflow = loop done, skip branch ofs
265     MOV @IP+,PC         \ 4 14~ taken or not taken xloop/loop
266     ENDCODE             \
267
268     CODE LOOP
269     MOV #XLOOP,X
270 BW2 ADD #4,&DP              \ make room to compile two words
271     MOV &DP,W
272     MOV X,-4(W)             \ xloop --> HERE
273     MOV TOS,-2(W)           \ DOadr --> HERE+2
274     BEGIN                   \ resolve all "leave" adr
275         MOV &LEAVEPTR,TOS   \ -- Adr of top LeaveStack cell
276         SUB #2,&LEAVEPTR    \ --
277         MOV @TOS,TOS        \ -- first LeaveStack value
278         CMP #0,TOS          \ -- = value left by DO ?
279     0<> WHILE
280         MOV W,0(TOS)        \ move adr after loop as UNLOOP adr
281     REPEAT
282     MOV @PSP+,TOS
283     MOV @IP+,PC
284     ENDCODE IMMEDIATE
285
286 \ https://forth-standard.org/standard/core/PlusLOOP
287 \ +LOOP   adrs --   L-- an an-1 .. a1 0
288     HDNCODE XPLOO   \   +LOOP run time
289     ADD TOS,0(RSP)  \ 4 increment INDEX by TOS value
290     MOV @PSP+,TOS   \ 2 get new TOS, doesn't change flags
291     GOTO BW1        \ 2
292     ENDCODE         \
293
294     CODE +LOOP
295     MOV #XPLOO,X
296     GOTO BW2        \ goto BW1 LOOP
297     ENDCODE IMMEDIATE
298     [THEN]
299
300 \ https://forth-standard.org/standard/core/I
301 \ I        -- n   R: sys1 sys2 -- sys1 sys2
302 \                  get the innermost loop index
303     [UNDEFINED] I
304     [IF]
305     CODE I
306     SUB #2,PSP              \ 1 make room in TOS
307     MOV TOS,0(PSP)          \ 3
308     MOV @RSP,TOS            \ 2 index = loopctr - fudge
309     SUB 2(RSP),TOS          \ 3
310     MOV @IP+,PC             \ 4 13~
311     ENDCODE
312     [THEN]
313
314 \ https://forth-standard.org/standard/core/Plus
315 \ +       n1/u1 n2/u2 -- n3/u3     add n1+n2
316     [UNDEFINED] +
317     [IF]
318     CODE +
319     ADD @PSP+,TOS
320     MOV @IP+,PC
321     ENDCODE
322     [THEN]
323
324 \ https://forth-standard.org/standard/core/Minus
325 \ -      n1/u1 n2/u2 -- n3/u3     n3 = n1-n2
326     [UNDEFINED] -
327     [IF]
328     CODE -
329     SUB @PSP+,TOS   \ 2  -- n2-n1 ( = -n3)
330     XOR #-1,TOS     \ 1
331     ADD #1,TOS      \ 1  -- n3 = -(n2-n1) = n1-n2
332     MOV @IP+,PC
333     ENDCODE
334     [THEN]
335
336     [UNDEFINED] MAX
337     [IF]   \ define MAX and MIN
338     CODE MAX    \    n1 n2 -- n3       signed maximum
339     CMP @PSP,TOS    \ n2-n1
340     S< ?GOTO FW1    \ n2<n1
341 BW1 ADD #2,PSP
342     MOV @IP+,PC
343     ENDCODE
344
345     CODE MIN    \    n1 n2 -- n3       signed minimum
346     CMP @PSP,TOS    \ n2-n1
347     S< ?GOTO BW1    \ n2<n1
348 FW1 MOV @PSP+,TOS
349     MOV @IP+,PC
350     ENDCODE
351     [THEN]
352
353 \ https://forth-standard.org/standard/core/CFetch
354 \ C@     c-addr -- char   fetch char from memory
355     [UNDEFINED] C@
356     [IF]
357     CODE C@
358     MOV.B @TOS,TOS
359     MOV @IP+,PC
360     ENDCODE
361     [THEN]
362
363 \ https://forth-standard.org/standard/core/SPACE
364 \ SPACE   --               output a space
365     [UNDEFINED] SPACE
366     [IF]
367     : SPACE
368     $20 EMIT ;
369     [THEN]
370
371 \ https://forth-standard.org/standard/core/SPACES
372 \ SPACES   n --            output n spaces
373     [UNDEFINED] SPACES
374     [IF]
375     CODE SPACES
376     CMP #0,TOS
377     0<> IF
378         PUSH IP
379         BEGIN
380             LO2HI
381             $20 EMIT
382             HI2LO
383             SUB #2,IP
384             SUB #1,TOS
385         0= UNTIL
386         MOV @RSP+,IP
387     THEN
388     MOV @PSP+,TOS           \ --         drop n
389     NEXT
390     ENDCODE
391     [THEN]
392
393 \ https://forth-standard.org/standard/core/DUP
394 \ DUP      x -- x x      duplicate top of stack
395     [UNDEFINED] DUP
396     [IF]    \ define DUP and DUP?
397     CODE DUP
398 BW1 SUB #2,PSP      \ 2  push old TOS..
399     MOV TOS,0(PSP)  \ 3  ..onto stack
400     MOV @IP+,PC     \ 4
401     ENDCODE
402
403 \ https://forth-standard.org/standard/core/qDUP
404 \ ?DUP     x -- 0 | x x    DUP if nonzero
405     CODE ?DUP
406     CMP #0,TOS      \ 2  test for TOS nonzero
407     0<> ?GOTO BW1    \ 2
408     MOV @IP+,PC     \ 4
409     ENDCODE
410     [THEN]
411
412 \ https://forth-standard.org/standard/core/OVER
413 \ OVER    x1 x2 -- x1 x2 x1
414     [UNDEFINED] OVER
415     [IF]
416     CODE OVER
417     MOV TOS,-2(PSP)     \ 3 -- x1 (x2) x2
418     MOV @PSP,TOS        \ 2 -- x1 (x2) x1
419     SUB #2,PSP          \ 1 -- x1 x2 x1
420     MOV @IP+,PC
421     ENDCODE
422     [THEN]
423
424 \ https://forth-standard.org/standard/core/toR
425 \ >R    x --   R: -- x   push to return stack
426     [UNDEFINED] >R
427     [IF]
428     CODE >R
429     PUSH TOS
430     MOV @PSP+,TOS
431     MOV @IP+,PC
432     ENDCODE
433     [THEN]
434
435 \ https://forth-standard.org/standard/core/Rfrom
436 \ R>    -- x    R: x --   pop from return stack ; CALL #RFROM performs DOVAR
437     [UNDEFINED] R>
438     [IF]
439     CODE R>
440     SUB #2,PSP      \ 1
441     MOV TOS,0(PSP)  \ 3
442     MOV @RSP+,TOS   \ 2
443     MOV @IP+,PC     \ 4
444     ENDCODE
445     [THEN]
446
447 \ https://forth-standard.org/standard/core/CONSTANT
448 \ CONSTANT <name>     n --                      define a Forth CONSTANT
449     [UNDEFINED] CONSTANT
450     [IF]
451     : CONSTANT
452     CREATE
453     HI2LO
454     MOV TOS,-2(W)           \   PFA = n
455     MOV @PSP+,TOS
456     MOV @RSP+,IP
457     MOV @IP+,PC
458     ENDCODE
459     [THEN]
460
461 \ https://forth-standard.org/standard/core/STATE
462 \ STATE   -- a-addr       holds compiler state
463     [UNDEFINED] STATE
464     [IF]
465     STATEADR CONSTANT STATE
466     [THEN]
467
468 \ https://forth-standard.org/standard/core/CR
469 \ CR      --               send CR+LF to the output device
470     [UNDEFINED] CR
471     [IF]
472
473 \    DEFER CR    \ DEFERed definition, by default executes that of :NONAME
474 \ create a primary defered word, i.e. with its default runtime beginning at the >BODY of the definition
475     CODE CR     \ part I : DEFERed definition of CR
476     MOV #NEXT_ADR,PC                \ [PFA] = NEXT_ADR
477     ENDCODE
478
479     :NONAME
480     'CR' EMIT 'LF' EMIT
481     ; IS CR
482     [THEN]
483
484 \ https://forth-standard.org/standard/core/BASE
485 \ BASE    -- a-addr       holds conversion radix
486     [UNDEFINED] BASE
487     [IF]
488     BASEADR  CONSTANT BASE
489     [THEN]
490
491     [UNDEFINED] HERE
492     [IF]
493     CODE HERE
494     MOV #BEGIN,PC
495     ENDCODE
496     [THEN]
497
498 \ https://forth-standard.org/standard/core/DROP
499 \ DROP     x --          drop top of stack
500     [UNDEFINED] DROP
501     [IF]
502     CODE DROP
503     MOV @PSP+,TOS   \ 2
504     MOV @IP+,PC     \ 4
505     ENDCODE
506     [THEN]
507
508 \ https://forth-standard.org/standard/core/OnePlus
509 \ 1+      n1/u1 -- n2/u2       add 1 to TOS
510     [UNDEFINED] 1+
511     [IF]
512     CODE 1+
513     ADD #1,TOS
514     MOV @IP+,PC
515     ENDCODE
516     [THEN]
517
518 \ https://forth-standard.org/standard/core/Equal
519 \ =      x1 x2 -- flag         test x1=x2
520     [UNDEFINED] =
521     [IF]
522     CODE =
523     SUB @PSP+,TOS   \ 2
524     0<> IF          \ 2
525         AND #0,TOS  \ 1
526         MOV @IP+,PC \ 4
527     THEN
528     XOR #-1,TOS     \ 1 flag Z = 1
529     MOV @IP+,PC     \ 4
530     ENDCODE
531     [THEN]
532
533 \ https://forth-standard.org/standard/core/CASE
534     [UNDEFINED] CASE
535     [IF]
536     : CASE
537     0
538     ; IMMEDIATE \ -- #of-1
539
540 \ https://forth-standard.org/standard/core/OF
541     : OF \ #of-1 -- orgOF #of
542     1+                      \ count OFs
543     >R                      \ move off the stack in case the control-flow stack is the data stack.
544     POSTPONE OVER
545     POSTPONE =              \ copy and test case value
546     POSTPONE IF             \ add orig to control flow stack
547     POSTPONE DROP               \ discards case value if =
548     R>                      \ we can bring count back now
549     ; IMMEDIATE
550
551 \ https://forth-standard.org/standard/core/ENDOF
552     : ENDOF \ orgOF #of -- orgENDOF #of
553     >R                      \ move off the stack in case the control-flow stack is the data stack.
554     POSTPONE ELSE
555     R>                      \ we can bring count back now
556     ; IMMEDIATE
557
558 \ https://forth-standard.org/standard/core/ENDCASE
559     : ENDCASE \ orgENDOF1..orgENDOFn #of --
560     POSTPONE DROP
561     0 DO
562         POSTPONE THEN
563     LOOP
564     ; IMMEDIATE
565     [THEN]
566
567 ; ------------------------------------------------------------------
568 ; then we download the set of definitions we need (from UTILITY.f)
569 ; ------------------------------------------------------------------
570
571     [UNDEFINED] U.R
572     [IF]        \ defined in {UTILITY}
573     : U.R                       \ u n --           display u unsigned in n width (n >= 2)
574     >R  <# 0 # #S #>
575     R> OVER - 0 MAX SPACES TYPE
576     ;
577     [THEN]
578
579 ; --------------------------
580 ; end of definitions we need
581 ; --------------------------
582
583 \ https://forth-standard.org/standard/tools/DUMP
584     CODE DUMP               \ adr n  --   dump memory
585     PUSH IP
586     PUSH &BASE              \ save current base
587     MOV #$10,&BASE          \ HEX base
588     ADD @PSP,TOS            \ -- ORG END
589     LO2HI
590     SWAP                    \ -- END ORG
591     DO                      \ generate line
592         I 4 U.R SPACE       \ generate address
593         I 8 + I
594         DO I C@ 3 U.R LOOP
595         SPACE
596         I $10 + I 8 +
597         DO I C@ 3 U.R LOOP
598         SPACE SPACE
599         I $10 + I           \ display 16 chars
600         DO I C@ $7E MIN $20 MAX EMIT LOOP
601         CR
602     $10 +LOOP
603     R> BASE !               \ restore current base
604     ;
605
606  \ SD_EMIT  c --    output char c to a SD_CARD file opened as write
607     CODE SD_EMIT
608     MOV &BufferPtr,Y            \ 3
609     MOV.B TOS,SD_BUF(Y)         \ 3
610     MOV @PSP+,TOS               \ 2
611     ADD #1,Y                    \ 1
612     MOV Y,&BufferPtr            \ 3
613     CMP #$200,Y                 \ 2 512 bytes by sector
614     U>= IF                      \ 2 if buffer is full
615         CALL #Write_File        \   write it; BufferPtr = 0
616     THEN
617     MOV @IP+,PC                 \ 4
618     ENDCODE                     \ 20~
619
620     : WRITEDUMP        
621     ['] SD_EMIT IS EMIT         \ redirect output to SD_EMIT
622     MAIN_ORG HERE OVER - DUMP   \ dump MAIN memory up to HERE address
623     ['] EMIT >BODY IS EMIT      \ redirect output to default EMIT
624     CLOSE                       \ close YOURFILE.TXT
625     ;
626
627     CODE START_TIMER
628     MOV #%01_0010_0100,&TB0CTL  \ start  TB0, ACLK (32768 Hz), continuous mode
629     MOV @IP+,PC
630     ENDCODE
631
632     CODE DISPLAY_TIME
633     SUB #6,PSP
634     MOV TOS,4(PSP)              \ save TOS
635     MOV &TB0R,2(PSP)            \ DVDlo=TB0R
636     MOV #0,&TB0CTL              \ stop timer
637     MOV #0,0(PSP)               \ DVDhi=0
638     MOV #33,TOS                 \ DVR=33  --> 0.7% error, 1985ms max
639     CALL #MUSMOD                \ DVDlo DVDhi DVR -- REM QUOTlo QUOThi
640     MOV @PSP+,TOS               \ -- REM QUOTlo
641     ADD #2,PSP                  \ -- QUOlo
642     COLON
643     ECHO ." , done in " U. ." ms"
644     ;
645
646     : SD_TEST
647     ECHO
648     'CR' EMIT
649     CR
650     ." ----------" CR
651     ." SD_TESTS  " CR
652     ." ----------" CR
653     ." ? Fast Forth Specs" CR
654     ." 0 Set date and time (MSP430FR5xxx)" CR
655     ." 1 Load {UTILITY} words" CR
656     ." 2 Load {SD_TOOLS} words" CR
657     ." 3 Load {CORE_ANS} words" CR
658     ." 4 Execute ANS core tests" CR
659     ." 5 Load a source file to compile 10k program" CR
660     ." 6 Read it only (51k)" CR
661     ." 7 write FORTH dump in YOURFILE.TXT" CR
662     ." 8 append FORTH dump to YOURFILE.TXT" CR
663     ." 9 delete YOURFILE.TXT" CR
664     ." your choice: "
665     KEY DUP 'CR' = 
666                 IF KEY DROP ." 'CR'"    \ skip LF...
667                 ELSE DUP EMIT
668                 THEN
669     RST_RET                             \ remove all definitions
670     NOECHO
671     CASE
672     '?' OF  CR LOAD" FF_SPECS.4TH"  ENDOF   \ LOAD" command is always executed after the SD_TEST exit,
673     '0' OF  CR LOAD" RTC.4TH"       ENDOF   \ so, no risk of crashing this program, regardless of RST_RET use...
674     '1' OF  CR LOAD" UTILITY.4TH"   ENDOF
675     '2' OF  CR LOAD" SD_TOOLS.4TH"  ENDOF
676     '3' OF  CR LOAD" CORE_ANS.4TH"  ENDOF
677     '4' OF  CR LOAD" CORETEST.4TH"  ENDOF
678     '5' OF  CR LOAD" PROG10K.4TH"   ENDOF
679                                         \ ...instead of READ" WRITE" APPEND" DEL" which are executed immediately
680     '6' OF  START_TIMER
681             READ" PROG10K.4TH"          \ open file as read
682             BEGIN READ UNTIL            \ sequentially read 512 bytes, then the file is closed
683             DISPLAY_TIME            ENDOF
684     '7' OF  START_TIMER
685             WRITE" YOURFILE.TXT"        \ create new file or overwrite existing file
686             WRITEDUMP DISPLAY_TIME  ENDOF
687     '8' OF  START_TIMER
688             APPEND" YOURFILE.TXT"       \ append to existing file or create new file
689             WRITEDUMP DISPLAY_TIME  ENDOF
690     '9' OF  START_TIMER
691             DEL" YOURFILE.TXT"          \ no message
692             DISPLAY_TIME            ENDOF
693     ENDCASE
694     ;
695
696 SD_TEST