OSDN Git Service

fe2f5e2b3d79b770b188cfb47ab37b25f7223eab
[fast-forth/master.git] / MSP430-FORTH / SD_TOOLS.f
1 \ -*- coding: utf-8 -*-
2
3 \ to see kernel options, download FastForthSpecs.f
4 \ FastForth kernel options: MSP430ASSEMBLER, CONDCOMP, DOUBLE_INPUT, SD_CARD_LOADER
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  CHIPSTICK_FR2433    MSP_EXP430FR2433    MSP_EXP430FR2355
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 \ REGISTERS USAGE
20 \ R4 to R7 must be saved before use and restored after
21 \ scratch registers Y to S are free for use
22 \ under interrupt, IP is free for use
23 \
24 \ PUSHM order : PSP,TOS, IP,  S,  T,  W,  X,  Y, rEXIT,rDOVAR,rDOCON, rDODOES, R3, SR,RSP, PC
25 \ PUSHM order : R15,R14,R13,R12,R11,R10, R9, R8,  R7  ,  R6  ,  R5  ,   R4   , R3, R2, R1, R0
26 \
27 \ example : PUSHM #6,IP pushes IP,S,T,W,X,Y registers to return stack
28 \
29 \ POPM  order :  PC,RSP, SR, R3, rDODOES,rDOCON,rDOVAR,rEXIT,  Y,  X,  W,  T,  S, IP,TOS,PSP
30 \ POPM  order :  R0, R1, R2, R3,   R4   ,  R5  ,  R6  ,  R7 , R8, R9,R10,R11,R12,R13,R14,R15
31 \
32 \ example : POPM #6,IP   pop Y,X,W,T,S,IP registers from return stack
33 \
34 \
35 \ FORTH conditionnals:  unary{ 0= 0< 0> }, binary{ = < > U< }
36 \
37 \ ASSEMBLER conditionnal usage with IF UNTIL WHILE  S<  S>=  U<   U>=  0=  0<>  0>=
38 \ ASSEMBLER conditionnal usage with ?JMP ?GOTO      S<  S>=  U<   U>=  0=  0<>  0<
39
40 ; ---------------------------------------------------------------
41 ; SD_TOOLS.f
42 ; BASIC TOOLS for SD Card : DIR FAT SECTOR. CLUSTER.
43 ; ---------------------------------------------------------------
44
45 \ first, we do some tests allowing the download
46     CODE ABORT_SD_TOOLS
47     SUB #4,PSP
48     MOV TOS,2(PSP)
49     [UNDEFINED] LOAD"   \ "
50     [IF]
51         MOV #-1,0(PSP)
52     [ELSE]
53         MOV #0,0(PSP)
54     [THEN]
55     MOV &VERSION,TOS
56     SUB #400,TOS        \ FastForth V4.0
57     COLON
58     'CR' EMIT           \ return to column 1 without 'LF'
59     ABORT" FastForth V4.0 please!"
60     ABORT" Build FastForth with SD_CARD_LOADER addon!"
61     RST_RET             \ remove ABORT_UARTI2CS definition before resuming
62     ;
63
64     ABORT_SD_TOOLS
65
66     [DEFINED] {SD_TOOLS} 
67     [IF] {SD_TOOLS}
68     [THEN]
69     [UNDEFINED] {SD_TOOLS}
70     [IF]
71     MARKER {SD_TOOLS}
72
73 ; ------------------------------------------------------------------
74 ; first we download the set of definitions we need (from CORE_ANS.f)
75 ; ------------------------------------------------------------------
76
77     [UNDEFINED] HERE [IF]
78     CODE HERE
79     MOV #BEGIN,PC
80     ENDCODE
81     [THEN]
82
83 \ https://forth-standard.org/standard/core/Plus
84 \ +       n1/u1 n2/u2 -- n3/u3     add n1+n2
85     [UNDEFINED] + [IF]
86     CODE +
87     ADD @PSP+,TOS
88     MOV @IP+,PC
89     ENDCODE
90     [THEN]
91
92     [UNDEFINED] MAX
93     [IF]    \ define MAX and MIN
94     CODE MAX    \    n1 n2 -- n3       signed maximum
95     CMP @PSP,TOS    \ n2-n1
96     S<  ?GOTO FW1   \ n2<n1
97 BW1 ADD #2,PSP
98     MOV @IP+,PC
99     ENDCODE
100
101     CODE MIN    \    n1 n2 -- n3       signed minimum
102     CMP @PSP,TOS     \ n2-n1
103     S<  ?GOTO BW1    \ n2<n1
104 FW1 MOV @PSP+,TOS
105     MOV @IP+,PC
106     ENDCODE
107     [THEN]
108
109 \ https://forth-standard.org/standard/core/CFetch
110 \ C@     c-addr -- char   fetch char from memory
111     [UNDEFINED] C@
112     [IF]
113     CODE C@
114     MOV.B @TOS,TOS
115     MOV @IP+,PC
116     ENDCODE
117     [THEN]
118
119 \ https://forth-standard.org/standard/core/SPACE
120 \ SPACE   --               output a space
121     [UNDEFINED] SPACE
122     [IF]
123     : SPACE
124     $20 EMIT ;
125     [THEN]
126
127 \ https://forth-standard.org/standard/core/SPACES
128 \ SPACES   n --            output n spaces
129     [UNDEFINED] SPACES
130     [IF]
131     CODE SPACES
132     CMP #0,TOS
133     0<> IF
134         PUSH IP
135         BEGIN
136             LO2HI
137             $20 EMIT
138             HI2LO
139             SUB #2,IP
140             SUB #1,TOS
141         0= UNTIL
142         MOV @RSP+,IP
143     THEN
144     MOV @PSP+,TOS           \ --         drop n
145     NEXT
146     ENDCODE
147     [THEN]
148
149 \ https://forth-standard.org/standard/core/SWAP
150 \ SWAP     x1 x2 -- x2 x1    swap top two items
151     [UNDEFINED] SWAP
152     [IF]
153     CODE SWAP
154     MOV @PSP,W      \ 2
155     MOV TOS,0(PSP)  \ 3
156     MOV W,TOS       \ 1
157     MOV @IP+,PC     \ 4
158     ENDCODE
159     [THEN]
160
161 \ https://forth-standard.org/standard/core/OVER
162 \ OVER    x1 x2 -- x1 x2 x1
163     [UNDEFINED] OVER
164     [IF]
165     CODE OVER
166     MOV TOS,-2(PSP)     \ 3 -- x1 (x2) x2
167     MOV @PSP,TOS        \ 2 -- x1 (x2) x1
168     SUB #2,PSP          \ 1 -- x1 x2 x1
169     MOV @IP+,PC
170     ENDCODE
171     [THEN]
172
173 \ https://forth-standard.org/standard/core/toR
174 \ >R    x --   R: -- x   push to return stack
175     [UNDEFINED] >R
176     [IF]
177     CODE >R
178     PUSH TOS
179     MOV @PSP+,TOS
180     MOV @IP+,PC
181     ENDCODE
182     [THEN]
183
184 \ https://forth-standard.org/standard/core/Rfrom
185 \ R>    -- x    R: x --   pop from return stack ; CALL #RFROM performs DOVAR
186     [UNDEFINED] R>
187     [IF]
188     CODE R>
189     SUB #2,PSP      \ 1
190     MOV TOS,0(PSP)  \ 3
191     MOV @RSP+,TOS   \ 2
192     MOV @IP+,PC     \ 4
193     ENDCODE
194     [THEN]
195
196 \ https://forth-standard.org/standard/core/Minus
197 \ -      n1/u1 n2/u2 -- n3/u3     n3 = n1-n2
198     [UNDEFINED] -
199     [IF]
200     CODE -
201     SUB @PSP+,TOS   \ 2  -- n2-n1 ( = -n3)
202     XOR #-1,TOS     \ 1
203     ADD #1,TOS      \ 1  -- n3 = -(n2-n1) = n1-n2
204     MOV @IP+,PC
205     ENDCODE
206     [THEN]
207
208 \ https://forth-standard.org/standard/core/DO
209 \ DO       -- DOadr   L: -- 0
210     [UNDEFINED] DO
211     [IF]                \ define DO LOOP +LOOP
212     HDNCODE XDO         \ DO run time
213     MOV #$8000,X        \ 2 compute 8000h-limit = "fudge factor"
214     SUB @PSP+,X         \ 2
215     MOV TOS,Y           \ 1 loop ctr = index+fudge
216     ADD X,Y             \ 1 Y = INDEX
217     PUSHM #2,X          \ 4 PUSHM X,Y, i.e. PUSHM LIMIT, INDEX
218     MOV @PSP+,TOS       \ 2
219     MOV @IP+,PC         \ 4
220     ENDCODE
221
222     CODE DO
223     SUB #2,PSP              \
224     MOV TOS,0(PSP)          \
225     ADD #2,&DP              \   make room to compile xdo
226     MOV &DP,TOS             \ -- HERE+2
227     MOV #XDO,-2(TOS)        \   compile xdo
228     ADD #2,&LEAVEPTR        \ -- HERE+2     LEAVEPTR+2
229     MOV &LEAVEPTR,W         \
230     MOV #0,0(W)             \ -- HERE+2     L-- 0
231     MOV @IP+,PC
232     ENDCODE IMMEDIATE
233
234 \ https://forth-standard.org/standard/core/LOOP
235 \ LOOP    DOadr --         L-- an an-1 .. a1 0
236     HDNCODE XLOOP       \   LOOP run time
237     ADD #1,0(RSP)       \ 4 increment INDEX
238 BW1 BIT #$100,SR        \ 2 is overflow bit set?
239     0= IF               \   branch if no overflow
240         MOV @IP,IP
241         MOV @IP+,PC
242     THEN
243     ADD #4,RSP          \ 1 empties RSP
244     ADD #2,IP           \ 1 overflow = loop done, skip branch ofs
245     MOV @IP+,PC         \ 4 14~ taken or not taken xloop/loop
246     ENDCODE             \
247
248     CODE LOOP
249     MOV #XLOOP,X
250 BW2 ADD #4,&DP              \ make room to compile two words
251     MOV &DP,W
252     MOV X,-4(W)             \ xloop --> HERE
253     MOV TOS,-2(W)           \ DOadr --> HERE+2
254     BEGIN                   \ resolve all "leave" adr
255         MOV &LEAVEPTR,TOS   \ -- Adr of top LeaveStack cell
256         SUB #2,&LEAVEPTR    \ --
257         MOV @TOS,TOS        \ -- first LeaveStack value
258         CMP #0,TOS          \ -- = value left by DO ?
259     0<> WHILE
260         MOV W,0(TOS)        \ move adr after loop as UNLOOP adr
261     REPEAT
262     MOV @PSP+,TOS
263     MOV @IP+,PC
264     ENDCODE IMMEDIATE
265
266 \ https://forth-standard.org/standard/core/PlusLOOP
267 \ +LOOP   adrs --   L-- an an-1 .. a1 0
268     HDNCODE XPLOO   \   +LOOP run time
269     ADD TOS,0(RSP)  \ 4 increment INDEX by TOS value
270     MOV @PSP+,TOS   \ 2 get new TOS, doesn't change flags
271     GOTO BW1        \ 2
272     ENDCODE         \
273
274     CODE +LOOP
275     MOV #XPLOO,X
276     GOTO BW2        \ goto BW1 LOOP
277     ENDCODE IMMEDIATE
278     [THEN]
279
280 \ https://forth-standard.org/standard/core/I
281 \ I        -- n   R: sys1 sys2 -- sys1 sys2
282 \                  get the innermost loop index
283     [UNDEFINED] I
284     [IF]
285     CODE I
286     SUB #2,PSP              \ 1 make room in TOS
287     MOV TOS,0(PSP)          \ 3
288     MOV @RSP,TOS            \ 2 index = loopctr - fudge
289     SUB 2(RSP),TOS          \ 3
290     MOV @IP+,PC             \ 4 13~
291     ENDCODE
292     [THEN]
293
294 \ https://forth-standard.org/standard/core/CR
295 \ CR      --               send CR+LF to the output device
296     [UNDEFINED] CR
297     [IF]
298 \ create a primary defered word, i.e. with its default runtime beginning at the >BODY of the definition
299     CODE CR     \ part I : DEFERed definition of CR
300     MOV #NEXT_ADR,PC                \ [PFA] = NEXT_ADR
301     ENDCODE
302
303     :NONAME
304     'CR' EMIT 'LF' EMIT
305     ; IS CR
306     [THEN]
307
308 ; ------------------------------------------------------------------
309 ; then we download the set of definitions we need (from UTILITY.f)
310 ; ------------------------------------------------------------------
311
312     [UNDEFINED] U.R
313     [IF]        \ defined in {UTILITY}
314     : U.R                       \ u n --           display u unsigned in n width (n >= 2)
315     >R  <# 0 # #S #>
316     R> OVER - 0 MAX SPACES TYPE
317     ;
318     [THEN]
319
320 \ https://forth-standard.org/standard/tools/DUMP
321     [UNDEFINED] DUMP
322     [IF]       \ defined in {UTILITY}
323     CODE DUMP                   \ adr n  --   dump memory
324     PUSH IP
325     PUSH &BASEADR               \ save current base
326     MOV #$10,&BASEADR           \ HEX base
327     ADD @PSP,TOS                \ -- ORG END
328     LO2HI
329     SWAP                        \ -- END ORG
330     CR
331     4 SPACES $10 0
332     DO I 3 U.R  LOOP            \ -- END ORG
333     DO  CR                      \ generate line
334         I 4 U.R                 \ generate address
335         I $10 + I
336         DO I C@ 3 U.R LOOP
337         SPACE SPACE
338         I $10 + I             \ display 16 chars
339         DO I C@ $7E MIN $20 MAX EMIT LOOP
340     $10 +LOOP
341     R> BASEADR !              \ restore current base
342     ;
343     [THEN]
344
345 ; --------------------------
346 ; end of definitions we need
347 ; --------------------------
348
349 \ display content of a sector
350 \ to Display MBR_FirstSector, type : 0. SECTOR.
351 \   --------------------------------\
352     CODE SECTOR.                    \ sector. --     don't forget to add decimal point to your sector number
353 \   --------------------------------\
354 BW1 MOV     TOS,X                   \ X = SectorH
355     MOV     @PSP,W                  \ W = sectorL
356     CALL    #RD_SECT                \ W = SectorLO  X = SectorHI
357     COLON                           \
358     SPACE <# #S #> TYPE             \ ud --            display the double number
359     SD_BUF $200 DUMP CR ;           \ then dump the sector
360 \   --------------------------------\
361
362 \ display first sector of a Cluster
363 \   --------------------------------\
364     CODE CLUSTER.                   \ cluster.  --        don't forget to add decimal point to your cluster number
365 \   --------------------------------\
366 BW2 BIT.B   #CD_SD,&SD_CDIN         \ test Card Detect: memory card present ?
367     0<> IF                          \ no: force COLD
368         MOV #COLD,PC                \ no
369     THEN
370     MOV.B &SecPerClus,W             \ SecPerClus(54321) = multiplicator
371     MOV @PSP,X                      \ X = ClusterL
372     BEGIN
373         RRA W                       \ shift one right multiplicator
374     U< WHILE                        \ carry clear
375         ADD X,X                     \ (RLA) shift one left MULTIPLICANDlo16
376         ADDC TOS,TOS                \ (RLC) shift one left MULTIPLICANDhi8
377     REPEAT
378     ADD     &OrgClusters,X          \ add OrgClusters = sector of virtual cluster 0 (word size)
379     MOV     X,0(PSP)
380     ADDC    #0,TOS                  \ don't forget carry
381     GOTO    BW1                     \ jump to SECTOR
382     ENDCODE
383 \   --------------------------------\
384
385 \   --------------------------------\
386     CODE FAT                        \ Display FATsector
387 \   --------------------------------\
388     SUB     #4,PSP                  \
389     MOV     TOS,2(PSP)              \
390     MOV     &OrgFAT1,0(PSP)         \
391     MOV     #0,TOS                  \ FATsectorHI = 0
392     GOTO    BW1                     \ jump to SECTOR
393     ENDCODE
394 \   --------------------------------\
395
396 \   --------------------------------\
397     CODE DIR                        \ Display CurrentDir first sector
398 \   --------------------------------\
399     SUB     #4,PSP                  \
400     MOV     TOS,2(PSP)              \           save TOS
401     MOV     &DIRclusterL,0(PSP)     \
402     MOV     &DIRclusterH,TOS        \
403     CMP     #0,TOS
404     0<>     ?GOTO BW2               \ jump to CLUSTER
405     CMP     #1,0(PSP)               \ cluster 1 ?
406     0<>     ?GOTO BW2               \ jump to CLUSTER
407     MOV     &OrgRootDir,0(PSP)      \ if yes, special case of FAT16 OrgRootDir
408     GOTO    BW1                     \ jump to SECTOR
409     ENDCODE
410 \   --------------------------------\
411
412     RST_SET 
413
414     [THEN] \ endof [UNDEFINED] {SD_TOOLS} 
415
416     ECHO