OSDN Git Service

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