OSDN Git Service

Update FF_SPECS.f
[fast-forth/master.git] / forthMSP430FR_SD_LOAD.asm
1 ; -*- coding: utf-8 -*-
2 ; forthMSP430FR_SD_LOAD.asm
3
4 ;Z SD_ACCEPT  addr addr len -- addr' len'  get line to interpret from a SD Card file
5 ; no interrupt allowed
6 ; defered word ACCEPT is redirected here by the word LOAD"
7 ; "defered" word CIB is redirected to SDIB (PAD if RAM<2k) by the word LOAD"
8 ; sequentially move an input line ended by CRLF from SD_BUF to PAD
9 ;   if end of SD_BUF is reached before CRLF, asks Read_HandledFile to refill buffer with next sector
10 ;   then load the end of the line to PAD ptr.
11 ; when all LOAD"ed files are read, redirects defered word ACCEPT to default ACCEPT and restore interpret pointers.
12 ; see CloseHandleT.
13
14 ; used variables : BufferPtr, BufferLen
15
16 ;-----------------------------------------------------------------------
17 ; SD card OPEN, LOAD subroutines
18 ;-----------------------------------------------------------------------
19
20 ; used variables : BufferPtr, BufferLen
21
22 ; rules for registers use
23 ; S = error
24 ; T = CurrentHdl, pathname
25 ; W = SectorL, (RTC) TIME
26 ; X = SectorH, (RTC) DATE
27 ; Y = BufferPtr, (DIR) EntryOfst, FAToffset
28
29
30 ; ----------------------------------;
31 HDLCurClusToFAT1sectWofstY          ;WXY Input: T=currentHandle, Output: W=FATsector, Y=FAToffset, Cluster=HDL_CurCluster
32 ; ----------------------------------;
33     MOV HDLL_CurClust(T),&ClusterL  ;
34     MOV HDLH_CurClust(T),&ClusterH  ;
35 ; ----------------------------------;
36 ClusterToFAT1sectWofstY             ;WXY Input : Cluster ; Output: W = FATsector, Y = FAToffset
37 ; ----------------------------------;
38     MOV.B &ClusterL+1,W             ;3 W = ClusterLoHI
39     MOV.B &ClusterL,Y               ;3 Y = ClusterLoLo
40     CMP #1,&FATtype                 ;3 FAT16?
41     JZ CTF1S_end                    ;2 yes
42
43 ; input : Cluster n, max = 7FFFFF (SDcard up to 256 GB)
44 ; ClusterLoLo*4 = displacement in 512 bytes sector   ==> FAToffset
45 ; ClusterHiLo&ClusterLoHi +C  << 1 = relative FATsector + orgFAT1       ==> FATsector
46 ; ----------------------------------;
47     MOV.B &ClusterH,X               ;  X = 0:ClusterHiLo
48     SWPB X                          ;  X = ClusterHiLo:0
49     ADD X,W                         ;  W = ClusterHiLo:ClusterLoHi  
50 ; ----------------------------------;
51     SWPB Y                          ;  Y = ClusterLoLo:0
52     ADD Y,Y                         ;1 Y = ClusterLoLo:0 << 1 + carry for FATsector
53     ADDC W,W                        ;  W = ClusterHiLo:ClusterLoHi << 1 = ClusterHiLo:ClusterL / 128
54     SWPB Y   
55 CTF1S_end
56     ADD Y,Y                         ;  Y = 0:ClusterLoLo << 1
57     MOV @RSP+,PC                    ;4
58 ; ----------------------------------;
59
60
61 ; use no registers
62 ; ----------------------------------; Input : Cluster, output: Sector = Cluster_first_sector
63 ComputeClusFrstSect                 ; If Cluster = 1 ==> RootDirectory ==> SectorL = OrgRootDir
64 ; ----------------------------------; Output: SectorL of Cluster
65     MOV     #0,&SectorH             ;
66     MOV     &OrgRootDir,&SectorL    ;
67     CMP.B   #0,&ClusterH            ; clusterH <> 0 ?
68     JNE     CCFS_AllOthers          ; yes
69     CMP     #1,&ClusterL            ; clusterHL = 1 ? (FAT16 specificity)
70     JZ      CCFS_RET                ; yes, sectorL for FAT16 OrgRootDIR is done
71 CCFS_AllOthers                      ;
72 ; ----------------------------------;
73     .IFDEF MPY                      ; general case
74 ; ----------------------------------;
75     MOV     &ClusterL,&MPY32L       ;3
76     MOV     &ClusterH,&MPY32H       ;3
77     MOV     &SecPerClus,&OP2        ;5+3
78     MOV     &RES0,&SectorL          ;5
79     MOV     &RES1,&SectorH          ;5
80     ADD     &OrgClusters,&SectorL   ;5 OrgClusters = sector of virtual cluster 0, word size
81     ADDC    #0,&SectorH             ;3 32~
82 ; ----------------------------------;
83     .ELSEIF                         ; case of no hardware multiplier
84 ; ----------------------------------; Cluster24<<SecPerClus --> ClusFrstSect; SecPerClus = {1,2,4,8,16,32,64}
85     PUSHM  #3,W                     ;5 PUSHM W,X,Y
86     MOV.B &SecPerClus,W             ;3 SecPerClus(5-1) = multiplicator
87     MOV &ClusterL,X                 ;3 Cluster(16-1) --> MULTIPLICANDlo
88     MOV.B &ClusterH,Y               ;3 Cluster(24-17) -->  MULTIPLICANDhi
89     JMP CCFS_ENTRY                  ;
90 CCFS_LOOP                           ;
91     ADD X,X                         ;1 (RLA) shift one left MULTIPLICANDlo16
92     ADDC Y,Y                        ;1 (RLC) shift one left MULTIPLICANDhi8
93 CCFS_ENTRY
94     RRA W                           ;1 shift one right multiplicator
95     JNC CCFS_LOOP                   ;2 C = 0 loop back
96 CCFS_NEXT                           ;  C = 1, it's done
97     ADD &OrgClusters,X              ;3 OrgClusters = sector of virtual_cluster_0, word size
98     ADDC #0,Y                       ;1
99     MOV X,&SectorL                  ;3 low result
100     MOV Y,&SectorH                  ;3 high result
101     POPM  #3,W                      ;5 POPM Y,X,W
102 ; ----------------------------------;32~ + 5~ by 2* shift
103     .ENDIF ; MPY
104 ; ----------------------------------;
105 CCFS_RET                            ;
106     MOV @RSP+,PC                    ;
107 ; ----------------------------------;
108
109
110 ; ----------------------------------;
111 ComputeHDLcurrentSector             ; input: currentHandle, output: Cluster, Sector
112 ; ----------------------------------;
113     MOV HDLL_CurClust(T),&ClusterL  ;
114     MOV HDLH_CurClust(T),&ClusterH  ;
115     CALL #ComputeClusFrstSect       ;
116     MOV.B HDLB_ClustOfst(T),W       ;
117     ADD W,&SectorL                  ;
118     ADDC #0,&SectorH                ;
119     MOV @RSP+,PC                    ;
120 ; ----------------------------------;
121
122
123 ; ----------------------------------; input : X = countdown_of_spaces, Y = name pointer in buffer
124 ParseEntryNameSpaces                ;XY
125 ; ----------------------------------; output: Z flag, Y is set after the last space char
126     CMP     #0,X                    ; 
127     JZ      PENSL_END               ;
128 ; ----------------------------------;
129 ParseEntryNameSpacesLoop            ;
130 ; ----------------------------------;
131     CMP.B   #32,SD_BUF(Y)           ; SPACE ? 
132     JNZ     PENSL_END               ; no: RET
133     ADD     #1,Y                    ;
134     SUB     #1,X                    ;
135     JNZ     ParseEntryNameSpacesLoop;
136 PENSL_END                           ;
137     MOV @RSP+,PC                    ; 
138 ; ----------------------------------; 
139
140
141 ; sequentially load in SD_BUF bytsPerSec bytes of a file opened as read or as load
142 ; if new bufferLen have a size <= BufferPtr, closes the file then RET.
143 ; if previous bufferLen had a size < bytsPerSec, closes the file and reloads previous LOADed file if exist.
144 ; HDLL_CurSize leaves the not yet read size 
145 ; All used registers must be initialized. 
146 ; ==================================;
147 Read_File                           ; <== SD_ACCEPT, READ
148 ; ==================================;
149     MOV     &CurrentHdl,T           ;
150     MOV     #0,&BufferPtr           ; reset BufferPtr (the buffer is already read)
151 ; ----------------------------------;
152     CMP     #bytsPerSec,&BufferLen  ;
153     JNZ     CloseHandleT            ; because this last and incomplete sector is already read
154     SUB #bytsPerSec,HDLL_CurSize(T) ; HDLL_CurSize is decremented of one sector lenght
155     SUBC    #0,HDLH_CurSize(T)      ;
156     ADD.B   #1,HDLB_ClustOfst(T)    ; current cluster offset is incremented
157     CMP.B &SecPerClus,HDLB_ClustOfst(T) ; Cluster Bound reached ?
158     JNC SetBufLenAndLoadCurSector   ; no
159 ; ----------------------------------;
160 ;SearchNextCluster                  ; yes
161 ; ----------------------------------;
162     MOV.B   #0,HDLB_ClustOfst(T)    ; reset Current_Cluster sectors offset
163     CALL #HDLCurClusToFAT1sectWofstY;WXY  Output: W=FATsector, Y=FAToffset, Cluster=HDL_CurCluster
164     ADD     &OrgFAT1,W              ;
165     MOV     #0,X                    ;
166     CALL    #ReadSectorWX           ;SWX (< 65536)
167     MOV     #0,HDLH_CurClust(T)     ;
168     MOV SD_BUF(Y),HDLL_CurClust(T)  ;
169     CMP     #1,&FATtype             ; FAT16?
170     JZ SetBufLenAndLoadCurSector    ;
171     MOV SD_BUF+2(Y),HDLH_CurClust(T);
172 ; ==================================;
173 SetBufLenAndLoadCurSector           ;WXY <== previous handle reLOAD with BufferPtr<>0
174 ; ==================================;
175     MOV     #bytsPerSec,&BufferLen  ; preset BufferLen
176     CMP     #0,HDLH_CurSize(T)      ; CurSize > 65535 ?
177     JNZ     LoadHDLcurrentSector    ; yes
178     CMP HDLL_CurSize(T),&BufferPtr  ; BufferPtr >= CurSize ? (BufferPtr = 0 or see RestorePreviousLoadedBuffer)
179     JC       CloseHandleT           ; yes
180     CMP #bytsPerSec,HDLL_CurSize(T) ; CurSize >= 512 ?
181     JC      LoadHDLcurrentSector    ; yes
182     MOV HDLL_CurSize(T),&BufferLen  ; no: adjust BufferLen
183 ; ==================================;
184 LoadHDLcurrentSector                ; <=== OPEN_WRITE_APPEND
185 ; ==================================;
186     CALL #ComputeHDLcurrentSector   ; use no registers
187 ; ==================================;
188 ReadSector                          ;
189 ; ==================================;
190     MOV     &SectorL,W              ; Low
191     MOV     &SectorH,X              ; High
192     JMP     ReadSectorWX            ; SWX then RET
193 ; ----------------------------------;
194
195
196 ; if first open_load token, save DefaultInputStream
197 ; if other open_load token, decrement token, save previous context
198
199 ; OPEN subroutine
200 ; Input : EntryOfst, Cluster = EntryOfst(HDLL_FirstClus())
201 ; init handle(HDLL_DIRsect,HDLW_DIRofst,HDLL_FirstClus,HDLL_CurClust,HDLL_CurSize)
202 ; Output: Cluster = first Cluster of file, X = CurrentHdl
203 ; ----------------------------------; input : Cluster, EntryOfst
204 GetFreeHandle                       ;STWXY init handle(HDLL_DIRsect,HDLW_DIRofst,HDLL_FirstClus = HDLL_CurClust,HDLL_CurSize)
205 ; ----------------------------------; output : T = new CurrentHdl
206     MOV #8,S                        ; prepare file already open error
207     MOV #FirstHandle,T              ;
208     MOV #0,X                        ; X = init previous handle as 0
209 ; ----------------------------------;
210 SearchHandleLoop                    ;
211 ; ----------------------------------;
212     CMP.B #0,HDLB_Token(T)          ; free handle ?
213     JZ FreeHandleFound              ; yes
214 AlreadyOpenTest                     ; no
215     CMP     &ClusterH,HDLH_FirstClus(T);
216     JNE     SearchNextHandle        ;
217     CMP     &ClusterL,HDLL_FirstClus(T);
218     JZ      InitHandleRET           ; error 8: Already Open abort ===> 
219 SearchNextHandle                    ;
220     MOV     T,X                     ; handle is occupied, keep it in X as previous handle
221     ADD     #HandleLenght,T         ;
222     CMP     #HandleEnd,T            ;
223     JNZ     SearchHandleLoop        ;
224     ADD     S,S                     ; 16 = no more handle error, abort ===>
225 InitHandleRET                       ;
226     MOV @RSP+,PC                             ;
227 ; ----------------------------------;
228 FreeHandleFound                     ; T = new handle, X = previous handle
229 ; ----------------------------------;
230     MOV     #0,S                    ; prepare Happy End (no error)
231     MOV     T,&CurrentHdl           ;
232     MOV     X,HDLW_PrevHDL(T)       ; link to previous handle
233 ; ----------------------------------;
234 CheckCaseOfPreviousToken            ;
235 ; ----------------------------------;
236     CMP     #0,X                    ; existing previous handle?
237     JZ      InitHandle              ; no
238     ADD     &TOIN,HDLW_BUFofst(X)   ; in previous handle, add interpret offset to Buffer offset
239 ; ----------------------------------;
240 CheckCaseOfLoadFileToken            ;
241 ; ----------------------------------;
242     CMP.B   #0,W                    ; open_type is LOAD (-1) ?
243     JGE     InitHandle              ; W>=0, no
244     CMP.B   #0,HDLB_Token(X)        ; previous token is negative? (open_load type)
245     JGE     InitHandle              ; no
246     ADD.B   HDLB_Token(X),W         ; LOAD token = previous LOAD token -1
247 ; ----------------------------------;
248 InitHandle                          ;
249 ; ----------------------------------;
250     MOV.B   W,HDLB_Token(T)         ; marks handle as open type: <0=LOAD, 1=READ, 2=WRITE, 4=DEL
251     MOV.B   #0,HDLB_ClustOfst(T)    ; clear ClustOfst
252     MOV     &SectorL,HDLL_DIRsect(T); init handle DIRsectorL
253     MOV     &SectorH,HDLH_DIRsect(T); 
254     MOV     &EntryOfst,Y            ;
255     MOV     Y,HDLW_DIRofst(T)       ; init handle SD_BUF offset of DIR entry
256     MOV SD_BUF+26(Y),HDLL_FirstClus(T); init handle firstcluster of file (to identify file)
257     MOV SD_BUF+20(Y),HDLH_FirstClus(T)
258     MOV SD_BUF+26(Y),HDLL_CurClust(T)  ; init handle CurrentCluster
259     MOV SD_BUF+20(Y),HDLH_CurClust(T) 
260     MOV SD_BUF+28(Y),HDLL_CurSize(T); init handle LOW currentSizeL
261     MOV SD_BUF+30(Y),HDLH_CurSize(T);
262     MOV     #0,&BufferPtr           ; reset BufferPtr all type of files
263     CMP.B   #2,W                    ; is a WRITE file handle?
264     JZ      ComputeHDLcurrentSector ; = 2, is a WRITE file
265     JGE     InitHandleRET           ; > 2, is a file to be deleted
266     MOV     #0,HDLW_BUFofst(T)      ; < 2, is a READ or a LOAD file
267     CMP.B   #-1,W                   ;
268     JZ      ReplaceInputBuffer      ; case of first loaded file
269     JL      SaveBufferContext       ; case of other loaded file
270     JMP SetBufLenAndLoadCurSector   ; case of READ file
271 ; ----------------------------------;
272 ReplaceInputBuffer                  ;
273 ; ----------------------------------;
274     MOV #SDIB_ORG,&CIB_ADR          ; set SD Input Buffer as Current Input Buffer before return to QUIT
275     MOV #SD_ACCEPT,&PFAACCEPT       ; redirect ACCEPT to SD_ACCEPT before return to QUIT
276 ; ----------------------------------;
277 SaveBufferContext                   ; (see CloseHandleT) 
278 ; ----------------------------------;
279     MOV &SOURCE_LEN,HDLW_PrevLEN(T) ; = CPL
280     SUB &TOIN,HDLW_PrevLEN(T)       ; PREVLEN = CPL - >IN
281     MOV &SOURCE_ORG,HDLW_PrevORG(T) ; = CIB
282     ADD &TOIN,HDLW_PrevORG(T)       ; PrevORG = CIB + >IN
283     JMP SetBufLenAndLoadCurSector   ; then RET
284 ; ----------------------------------;
285
286
287 ; ----------------------------------;
288 CloseHandleHere                     ;
289 ; ----------------------------------;
290     MOV.B #0,HDLB_Token(T)          ; release the handle
291     MOV @T,T                        ; T = previous handle
292     MOV T,&CurrentHdl               ; becomes current handle
293     CMP #0,T                        ;
294     JZ CloseHandleRet               ; if no more handle
295 ; ----------------------------------;
296 RestorePreviousLoadedBuffer         ;
297 ; ----------------------------------;
298     MOV HDLW_BUFofst(T),&BufferPtr  ; restore previous BufferPtr
299     CALL #SetBufLenAndLoadCurSector ; then reload previous buffer
300     BIC #Z,SR                       ; 
301 ; ----------------------------------;
302 CloseHandleRet                      ;
303     MOV @RSP+,PC                    ; Z = 1 if no more handle
304 ; ----------------------------------;
305
306
307 ; ==================================;
308 CloseHandleT                        ; <== CLOSE, Read_File, TERM2SD", OPEN_DEL
309 ; ==================================;
310     MOV &CurrentHdl,T               ;
311     CMP #0,T                        ; no handle?
312     JZ CloseHandleRet               ; RET
313 ; ----------------------------------;
314     .IFDEF SD_CARD_READ_WRITE
315     CMP.B #2,HDLB_Token(T)          ; opened as write (updated) file ?
316     JNZ TestClosedToken             ; no
317     CALL #WriteBuffer               ;SWXY
318     CALL #OPWW_UpdateDirectory      ;SWXY
319     .ENDIF                          ;
320 ; ----------------------------------;
321 TestClosedToken                     ;
322 ; ----------------------------------;
323     CMP.B #0,HDLB_Token(T)          ;
324 ; ----------------------------------;
325 CaseOfAnyReadWriteDelFileIsClosed   ; token >= 0
326 ; ----------------------------------;
327     JGE CloseHandleHere             ; then RET
328 ; ----------------------------------;
329 CaseOfAnyLoadedFileIsClosed         ; -- org' len'   R-- QUIT3 dst_ptr dst_len SD_ACCEPT
330 ; ----------------------------------;
331 RestoreSD_ACCEPTContext             ;
332 ; ----------------------------------;
333     MOV HDLW_PrevLEN(T),TOS         ;
334     MOV HDLW_PrevORG(T),0(PSP)      ; -- org len
335 ; ----------------------------------;
336 ReturnOfSD_ACCEPT                   ;
337 ; ----------------------------------;
338     ADD #6,RSP                      ; R-- QUIT4     empties return stack
339     MOV @RSP+,IP                    ;               skip return to SD_ACCEPT
340 ; ----------------------------------;
341     CALL #CloseHandleHere           ;               Z = 1 if no more handle
342 ; ----------------------------------;
343 CheckFirstLoadedFileIsClosed        ;
344 ; ----------------------------------;
345     JZ RestoreDefaultACCEPT         ;
346     MOV #NOECHO,PC                  ; -- org len    if return to SD_ACCEPT
347 ; ----------------------------------;
348 RestoreDefaultACCEPT                ;               if no more handle, first loaded file is closed...
349 ; ----------------------------------;
350     MOV #TIB_ORG,&CIB_ADR           ;               restore TIB as Current Input Buffer for next line (next QUIT)
351     MOV #BODYACCEPT,&PFAACCEPT      ;               restore default ACCEPT for next line (next QUIT)
352     MOV #ECHO,PC                    ; -- org len    if return to Terminal ACCEPT
353 ; ----------------------------------;
354
355
356    .IFDEF SD_CARD_READ_WRITE
357
358 ;-----------------------------------------------------------------------
359 ; SD_READ_WRITE FORTH words
360 ;-----------------------------------------------------------------------
361
362 ;Z READ"         --
363 ; parse string until " is encountered, convert counted string in String
364 ; then parse string until char '0'.
365 ; media identifiers "A:", "B:" ... are ignored (only one SD_Card),
366 ; char "\" as first one initializes rootDir as SearchDir.
367 ; if file found, if not already open and if free handle...
368 ; ...open the file as read and return the handle in CurrentHdl.
369 ; then load first sector in buffer, bufferLen and bufferPtr are ready for read
370 ; currentHdl keep handle that is flagged as "read".
371
372 ; to read sequentially next sectors use READ word. A flag is returned : true if file is closed.
373 ; the last sector so is in buffer.
374
375 ; if pathname is a directory, change current directory.
376 ; if an error is encountered, no handle is set, error message is displayed.
377
378 ; READ" acts also as CD dos command : 
379 ;     - READ" a:\misc\" set a:\misc as current directory
380 ;     - READ" a:\" reset current directory to root
381 ;     - READ" ..\" change to parent directory
382
383 ; to close all files type : WARM (or COLD, RESET)
384
385 ; ----------------------------------;
386     FORTHWORDIMM "READ\34"          ; immediate
387 ; ----------------------------------;
388 READDQ
389     MOV.B   #1,W                    ; W = OpenType
390     JMP     Open_File               ;
391 ; ----------------------------------;
392
393 ;Z WRITE" pathame"   --       immediate
394 ; open or create the file designed by pathname.
395 ; an error occurs if the file is already opened.
396 ; the last sector of the file is loaded in buffer, and bufferPtr leave the address of the first free byte.
397 ; compile state : compile WRITE" pathname"
398 ; exec state : open or create entry selected by pathname
399 ; ----------------------------------;
400     FORTHWORDIMM "WRITE\34"         ; immediate
401 ; ----------------------------------;
402 WRITEDQ
403     MOV.B   #2,W                    ; W = OpenType
404     JMP     Open_File               ;
405 ; ----------------------------------;
406
407
408 ;Z DEL" pathame"   --       immediate
409 ; compile state : compile DEL" pathname"
410 ; exec state : DELETE entry selected by pathname
411
412 ; ----------------------------------;
413     FORTHWORDIMM "DEL\34"           ; immediate
414 ; ----------------------------------;
415 DELDQ
416     MOV.B   #4,W                    ; W = OpenType
417     JMP     Open_File               ;
418 ; ----------------------------------;
419
420
421 ;Z CLOSE      --     
422 ; close current handle
423 ; ----------------------------------;
424     FORTHWORD "CLOSE"               ;
425 ; ----------------------------------;
426     CALL    #CloseHandleT           ;
427     MOV @IP+,PC                           ;
428 ; ----------------------------------;
429
430     .ENDIF ; SD_CARD_READ_WRITE
431
432 ;-----------------------------------------------------------------------
433 ; SD_CARD_LOADER FORTH word
434 ;-----------------------------------------------------------------------
435
436 ;Z LOAD" pathame"   --       immediate
437 ; compile state : compile LOAD" pathname"
438 ; exec state : open a file from SD card via its pathname
439 ; see Open_File primitive for pathname conventions 
440 ; the opened file becomes the new input stream for INTERPRET
441 ; this command is recursive, limited only by the count of free handles (up to 8)
442 ; LOAD" acts also as dos command "CD" : 
443 ;     - LOAD" \misc\" set a:\misc as current directory
444 ;     - LOAD" \" reset current directory to root
445 ;     - LOAD" ..\" change to parent directory
446
447 ; ----------------------------------;
448     FORTHWORDIMM "LOAD\34"          ; immediate
449 ; ----------------------------------;
450     MOV.B   #-1,W                   ; W = OpenType
451 ; ----------------------------------;
452
453
454 ; ======================================================================
455 ; OPEN FILE primitive
456 ; ======================================================================
457 ; Open_File               --
458 ; primitive for LOAD" READ" CREATE" WRITE" DEL"
459 ; store OpenType on TOS,
460 ; compile state : compile OpenType, compile SQUOTE and the string of provided pathname
461 ; exec state :  open a file from SD card via its pathname
462 ;               convert counted string found at HERE in a String then parse it
463 ;                   media identifiers "A:", "B:" ... are ignored (only one SD_Card),
464 ;                   char "\" as first one initializes rootDir as SearchDir.
465 ;               if file found, if not already open and if free handle...
466 ;                   ...open the file as read and return the handle in CurrentHdl.
467 ;               if the pathname is a directory, change current directory, no handle is set.
468 ;               if an error is encountered, no handle is set, an error message is displayed.
469 ; ----------------------------------;
470 Open_File                           ; --
471 ; ----------------------------------;
472     SUB     #2,PSP                  ;
473     MOV     TOS,0(PSP)              ;
474     MOV     W,TOS                   ; -- Open_type (0=LOAD", 1=READ", 2=WRITE", 4=DEL")
475     CMP     #0,&STATE               ;
476     JZ      OPEN_EXEC               ;
477 ; ----------------------------------;
478 OPEN_COMP                           ;
479     mDOCOL                          ; if compile state                              R-- LOAD"_return
480     .word   lit,lit,COMMA,COMMA     ; compile open_type as literal
481     .word   SQUOTE                  ; compile string_exec + string
482     .word   lit,ParenOpen,COMMA     ; compile (OPEN)
483     .word   EXIT                    ;
484 ; ----------------------------------;
485 OPEN_EXEC                           ;
486     mDOCOL                          ; if exec state
487     .word   lit,'"',WORDD,COUNT     ; -- open_type addr u
488     .word   $+2                     ;
489     MOV     @RSP+,IP                ;
490 ; ----------------------------------;
491 ParenOpen                           ; -- open_type HERE             HERE as pathname ptr
492 ; ----------------------------------;
493     MOV     @PSP+,rDOCON            ; rDOCON = addr = pathname PTR
494     ADD     rDOCON,TOS              ; TOS = EOS (End Of String) = pathname end
495     .IFDEF SD_CARD_READ_WRITE       ;
496     MOV     TOS,&EndOfPath          ; for WRITE CREATE part
497     .ENDIF
498 ; ----------------------------------;
499 OPN_PathName                        ;
500 ; ----------------------------------;
501     MOV     #1,S                    ; error 1
502     MOV     &DIRClusterL,&ClusterL  ;
503     MOV     &DIRclusterH,&ClusterH  ;
504     CMP     rDOCON,TOS              ; PTR = EOS ? (end of pathname ?)
505     JZ      OPN_NoPathName          ; yes: error 1 ===>
506 ; ----------------------------------;
507     CMP.B   #':',1(rDOCON)          ; A: B: C: ... in pathname ?
508     JNZ     OPN_AntiSlashStartTest  ; no
509     ADD     #2,rDOCON               ; yes : skip drive because not used, only one SD_card
510 ; ----------------------------------;
511 OPN_AntiSlashStartTest              ;
512     CMP.B   #'\\',0(rDOCON)          ; "\" as first char ?
513     JNZ     OPN_SearchDirSector     ; no
514     ADD     #1,rDOCON               ; yes : skip '\' char
515     MOV     &FATtype,&ClusterL      ;       FATtype = 1 as FAT16 RootDIR, FATtype = 2 = FAT32RootDIR
516     MOV     #0,&ClusterH            ;
517 ; ----------------------------------;
518 OPN_EndOfStringTest                 ; <=== dir found in path
519 ; ----------------------------------;
520     CMP     rDOCON,TOS              ; PTR = EOS ? (end of pathname ?)
521     JZ      OPN_SetCurrentDIR       ; yes
522 ; ----------------------------------;
523 OPN_SearchDirSector                 ;
524 ; ----------------------------------;
525     MOV     rDOCON,&Pathname        ; save Pathname ptr
526     CALL    #ComputeClusFrstSect    ; output: SectorHL
527     MOV     #32,rDODOES             ; preset countdown for FAT16 RootDIR sectors
528     CMP     #2,&FATtype             ; FAT32?
529     JZ      OPN_SetDirSectors       ; yes
530     CMP     &ClusterL,&FATtype      ; FAT16 AND RootDIR ?
531     JZ      OPN_LoadDIRsector       ; yes
532 OPN_SetDirSectors                   ;
533     MOV     &SecPerClus,rDODOES     ;
534 ; ----------------------------------;
535 OPN_LoadDIRsector                   ; <=== Dir Sector loopback
536 ; ----------------------------------;
537     CALL    #ReadSector             ;SWX
538 ; ----------------------------------;
539     MOV     #2,S                    ; prepare no such file error
540     MOV     #0,W                    ; init entries count
541 ; ----------------------------------;
542 OPN_SearchDIRentry                  ; <=== DIR Entry loopback
543 ; ----------------------------------;
544     MOV     W,Y                     ; 1
545     RLAM    #4,Y                    ;             --> * 16
546     ADD     Y,Y                     ; 1           --> * 2
547     MOV     Y,&EntryOfst            ; EntryOfst points to first free entry
548     CMP.B   #0,SD_BUF(Y)            ; free entry ? (end of entries in DIR)
549     JZ      OPN_NoSuchFile          ; error 2 NoSuchFile, used by create ===>
550     MOV     #8,X                    ; count of chars in entry name
551 ; ----------------------------------;
552 OPN_CompareName8chars               ;
553 ; ----------------------------------;
554     CMP.B   @rDOCON+,SD_BUF(Y)      ; compare Pathname(char) with DirEntry(char)
555     JNZ     OPN_FirstCharMismatch   ;
556     ADD     #1,Y                    ;
557     SUB     #1,X                    ;
558     JNZ     OPN_CompareName8chars   ; loopback if chars 1 to 7 of string and DirEntry are equal
559     ADD     #1,rDOCON               ; 9th char of Pathname is always a dot
560 ; ----------------------------------;
561 OPN_FirstCharMismatch               ;
562     CMP.B   #'.',-1(rDOCON)         ; FirstNotEqualChar of Pathname = dot ?
563     JZ      OPN_DotFound            ;
564 ; ----------------------------------;
565 OPN_DotNotFound                     ; 
566 ; ----------------------------------;
567     ADD     #3,X                    ; for next cases not equal chars of entry until 11 must be spaces
568     CALL    #ParseEntryNameSpaces   ; for X + 3 chars
569     JNZ     OPN_DIRentryMismatch    ; if a char entry <> space  
570     CMP.B   #'\\',-1(rDOCON)        ; FirstNotEqualChar of Pathname = "\" ?
571     JZ      OPN_EntryFound          ;
572     CMP     rDOCON,TOS              ; EOS exceeded ?
573     JNC     OPN_EntryFound          ; yes
574 ; ----------------------------------;
575 OPN_DIRentryMismatch                ;
576 ; ----------------------------------;
577     MOV     &pathname,rDOCON        ; reload Pathname
578     ADD     #1,W                    ; inc entry
579     CMP     #16,W                   ; 16 entry in a sector
580     JNZ     OPN_SearchDIRentry      ; ===> loopback for search next DIR entry
581 ; ----------------------------------;
582     ADD     #1,&SectorL             ;
583     ADDC    #0,&SectorH             ;
584     SUB     #1,rDODOES              ; dec count of Dir sectors
585     JNZ     OPN_LoadDIRsector       ; ===> loopback for search next DIR sector
586 ; ----------------------------------;
587     MOV     #4,S                    ;
588     JMP     OPN_EndOfDIR            ; error 4 ===> 
589 ; ----------------------------------;
590
591 ; ----------------------------------;
592 OPN_DotFound                        ; not equal chars of entry name until 8 must be spaces
593 ; ----------------------------------;
594     CMP.B   #'.',-2(rDOCON)         ; LastCharEqual = dot ?
595     JZ      OPN_DIRentryMismatch    ; case of first DIR entry = "." and Pathname = "..\" 
596     CALL    #ParseEntryNameSpaces   ; parse X spaces, X{0,...,7}
597     JNZ     OPN_DIRentryMismatch    ; if a char entry <> space
598     MOV     #3,X                    ;
599 ; ----------------------------------;
600 OPN_CompareExt3chars                ;
601 ; ----------------------------------;
602     CMP.B   @rDOCON+,SD_BUF(Y)      ; compare string(char) with DirEntry(char)
603     JNZ     OPN_ExtNotEqualChar     ;
604     ADD     #1,Y                    ;
605     SUB     #1,X                    ;
606     JNZ     OPN_CompareExt3chars    ; nothing to do if chars equal
607     JMP     OPN_EntryFound          ;
608 OPN_ExtNotEqualChar                 ;
609     CMP     rDOCON,TOS              ; EOS exceeded ?
610     JC      OPN_DIRentryMismatch    ; no, loop back   
611     CMP.B   #'\\',-1(rDOCON)        ; FirstNotEqualChar = "\" ?
612     JNZ     OPN_DIRentryMismatch    ;
613     CALL    #ParseEntryNameSpaces   ; parse X spaces, X{0,...,3}
614     JNZ     OPN_DIRentryMismatch    ; if a char entry <> space, loop back
615 ; ----------------------------------;
616 OPN_EntryFound                      ; Y points on the file attribute (11th byte of entry)
617 ; ----------------------------------;
618     MOV     &EntryOfst,Y            ; reload DIRentry
619     MOV     SD_BUF+26(Y),&ClusterL  ; first clusterL of file
620     MOV     SD_BUF+20(Y),&ClusterH  ; first clusterT of file, always 0 if FAT16
621 OPN_EntryFoundNext
622     BIT.B   #10h,SD_BUF+11(Y)       ; test if Directory or File
623     JZ      OPN_FileFound           ;
624 ; ----------------------------------;
625 OPN_DIRfound                        ; entry is a DIRECTORY
626 ; ----------------------------------;
627     CMP     #0,&ClusterH            ; case of ".." entry, when parent directory is root
628     JNZ     OPN_DIRfoundNext        ;
629     CMP     #0,&ClusterL            ; case of ".." entry, when parent directory is root
630     JNZ     OPN_DIRfoundNext        ;
631     MOV     &FATtype,&ClusterL      ; set cluster as RootDIR cluster
632 OPN_DIRfoundNext                    ;
633     CMP     rDOCON,TOS              ; EOS exceeded ?
634     JC      OPN_EndOfStringTest     ; no: (we presume that FirstNotEqualChar = "\") ==> loop back
635 ; ----------------------------------;
636 OPN_SetCurrentDIR                   ; -- open_type ptr
637 ; ----------------------------------;
638     MOV     &ClusterL,&DIRClusterL  ;
639     MOV     &ClusterH,&DIRclusterH  ;
640     MOV     #0,0(PSP)               ; -- open_type ptr      open_type = 0 
641     JMP     OPN_Dir
642 ; ----------------------------------;
643 OPN_FileFound                       ; -- open_type ptr
644 ; ----------------------------------;
645     MOV     @PSP,W                  ;   
646     CALL    #GetFreeHandle          ;STWXY init handle(HDLL_DIRsect,HDLW_DIRofst,HDLL_FirstClus = HDLL_CurClust,HDLL_CurSize)
647 ; ----------------------------------; output : T = CurrentHdl*, S = ReturnError, Y = DIRentry offset
648 OPN_NomoreHandle                    ; S = error 16
649 OPN_alreadyOpen                     ; S = error 8
650 OPN_EndOfDIR                        ; S = error 4
651 OPN_NoSuchFile                      ; S = error 2
652 OPN_NoPathName                      ; S = error 1
653 OPN_Dir
654     MOV     #xdodoes,rDODOES        ;                   restore rDODOES
655     MOV     #xdocon,rDOCON          ;                   restore rDODOES
656     MOV     @PSP+,W                 ; -- ptr            W = open_type
657     MOV     @PSP+,TOS               ; --
658 ; ----------------------------------; then go to selected OpenType subroutine (OpenType = W register)
659
660
661 ; ======================================================================
662 ; LOAD" primitive as part of Open_File
663 ; input from open:  S = OpenError, W = open_type, SectorHL = DIRsectorHL,
664 ;                   Buffer = [DIRsector], ClusterHL = FirstClusterHL
665 ;       from open(GetFreeHandle): Y = DIRentry, T = CurrentHdl
666 ; output: nothing else abort on error
667 ; ======================================================================
668     
669 ; ----------------------------------;
670 OPEN_QDIR                           ;
671 ; ----------------------------------;
672     CMP     #0,W                    ;
673     JZ      OPEN_LOAD_END           ; nothing to do
674 ; ----------------------------------;
675 OPEN_QLOAD                          ;
676 ; ----------------------------------;
677     .IFDEF SD_CARD_READ_WRITE       ;
678     CMP.B   #-1,W                   ; open_type = LOAD"
679     JNZ     OPEN_QREAD              ; next step
680     .ENDIF                          ;
681 ; ----------------------------------; here W is free
682 OPEN_LOAD                           ;
683 ; ----------------------------------;
684     CMP     #0,S                    ; open file happy end ?
685     JNZ     OPEN_Error              ; no
686 OPEN_LOAD_END
687     MOV @IP+,PC                     ;
688 ; ----------------------------------;
689
690 ; ----------------------------------;
691 OPEN_Error                          ; S= error
692 ; ----------------------------------;
693 ; Error 1  : PathNameNotFound       ; S = error 1
694 ; Error 2  : NoSuchFile             ; S = error 2
695 ; Error 4  : DIRisFull              ; S = error 4
696 ; Error 8  : alreadyOpen            ; S = error 8
697 ; Error 16 : NomoreHandle           ; S = error 16
698 ; ----------------------------------;
699     mDOCOL                          ; set ECHO, type Pathname, type #error, type "< OpenError"; no return
700     .word   ECHO                    ;
701     .word   XSQUOTE                 ; don't use S register
702     .byte   11,"< OpenError"        ;
703     .word   BRAN,ABORT_SD           ; to insert S error as flag, no return
704 ; ----------------------------------;
705
706
707     .IFDEF BOOTLOADER
708
709             FORTHWORD "[PFA]"       
710 ; [PFA]         CFA -- [PFA]        ; add source indirection to DEFERSTORE
711             ADD #2,TOS 
712             MOV @TOS,TOS
713             MOV @IP+,PC
714
715 ; to enable bootstrap:  ' BOOT IS WARM
716 ; to disable bootstrap: ' BOOT [PFA] IS WARM
717
718             FORTHWORD "BOOT"
719 ; BOOT          RSTIV_MEM --
720 ; performs bootstrap from SD_CARD\BOOT.4th file
721 BOOT        MOV @PC+,X
722 PFA_BOOT    .word INI_HARD_SD       ; X = INI_HARD_SD addr, 2(X) = [PFA_X] = previous INI_HARD_APP (INIT_TERM) addr , see forthMSP430FR_SD_INIT.asm
723             CMP #2,TOS              ; RSTIV_MEM <> WARM ?
724             JC QSD_MEM              ; yes
725             MOV @RSP+,PC            ; if RSTIV_MEM U< 2, return to BODYWARM
726 QSD_MEM     BIT.B #CD_SD,&SD_CDIN   ; SD_memory in SD_Card socket ?
727             JZ BOOT_YES             ;
728 NO_BOOT     MOV 2(X),PC             ; if no, goto previous INIT: INIT TERMINAL then ret to PFAWARM
729 ;---------------------------------------------------------------------------------
730 ; RESET 7: if RSTIV_MEM <> WARM, init TERM, init SD
731 ;---------------------------------------------------------------------------------
732 BOOT_YES    CALL X                  ; init TERM UC first then init SD card, TOS = RSTIV_MEM
733 ;---------------------------------------------------------------------------------
734 ; END OF RESET
735 ;---------------------------------------------------------------------------------
736             MOV #PSTACK-2,PSP       ;
737             MOV #0,0(PSP)           ; PUSH 0 on Stack
738             MOV #0,&STATE           ; )
739             MOV #LSTACK,&LEAVEPTR   ; > same as QUIT
740             MOV #RSTACK,RSP         ; )
741             ASMtoFORTH              ;
742             .word XSQUOTE                   ; -- RSTIV_MEM addr u
743             .byte 15,"LOAD\34 BOOT.4TH\34"  ; LOAD" BOOT.4TH" issues error 2 if no such file...
744             .word BRAN,QUIT4                ; to interpret this string
745         .ENDIF