OSDN Git Service

modified word # ; refreshed source folders
[fast-forth/master.git] / forthMSP430FR_SD_LowLvl.asm
1 ; -*- coding: utf-8 -*-
2 ; forthMSP430FR_SD_lowLvl.asm
3
4 ; Copyright (C) <2017>  <J.M. THOORENS>
5 ;
6 ; This program is free software: you can redistribute it and/or modify
7 ; it under the terms of the GNU General Public License as published by
8 ; the Free Software Foundation, either version 3 of the License, or
9 ; (at your option) any later version.
10 ;
11 ; This program is distributed in the hope that it will be useful,
12 ; but WITHOUT ANY WARRANTY; without even the implied warranty of
13 ; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14 ; GNU General Public License for more details.
15 ;
16 ; You should have received a copy of the GNU General Public License
17 ; along with this program.  If not, see <http://www.gnu.org/licenses/>.
18
19 ; =====================================================================
20 ; goal : accept 64 MB up to 64 GB SD_CARD
21 ; =====================================================================
22 ; thus FAT and RootClus logical sectors are word addressable.
23
24 ; FAT is a little endian structure.
25 ; CMD frame is sent as big endian.
26
27 ; we assume that SDSC Card (up to 2GB) is FAT16 with a byte addressing
28 ; and that SDHC Card (4GB up to 64GB) is FAT32 with a sector addressing (sector = 512 bytes)
29 ; for SDHC Card = 64 GB, cluster = 64 sectors ==> max clusters = 20 0000h ==> FAT size = 16384 sectors
30 ; ==> FAT1 and FAT2 can be addressed with a single word.
31
32 ; ref. https://en.wikipedia.org/wiki/Extended_boot_record
33 ; ref. https://en.wikipedia.org/wiki/Partition_type
34
35 ; Formatage FA16 d'une SDSC Card 2GB
36 ; First sector of physical drive (sector 0) content :
37 ; ---------------------------------------------------
38 ; dec@| HEX@
39 ; 446 |0x1BE    : partition table first record  ==> logical drive 0       
40 ; 446 |0x1CE    : partition table 2th record    ==> logical drive 1
41 ; 446 |0x1DE    : partition table 3th record    ==> logical drive 2
42 ; 446 |0x1EE    : partition table 4th record    ==> logical drive 3
43
44 ; partition record content :
45 ; ---------------------------------------------------
46 ; dec@|HEX@ =  HEX                                                           decimal
47 ; 0   |0x00 =  0x00     : not bootable
48 ; 1   |0x01 =  02 0C 00 : Org Cylinder/Head/Sector offset (CHS-addressing) = not used
49 ; 4   |0x04 =  0x0E     : type FAT16 using LBA addressing                  = 14 ==> FAT16
50 ; 5   |0x05 =  ED 3F EE : End Cylinder/Head/Sector offset (CHS-addressing) = not used
51 ; 8   |0x08 =  00 20 00 00 : sectors offset of logical drive               = 8192
52 ; 12  |0x0C =  00 40 74 00 : sectors size of logical drive                 = 7618560 sectors
53
54 ; 450 |0x04 =  0x0E     : type FAT16 using LBA addressing                  = 14 ==> set FATtype = FAT16 with byte CMD addressing
55 ; 454 |0x1C6 = 89 00    : FirstSector (of logical drive 0) BS_FirstSector  = 137
56
57
58 ; ref. https://www.compuphase.com/mbr_fat.htm#BOOTSECTOR
59
60 ; FirstSector of logical drive (sector 0) content :
61 ; -------------------------------------------------
62 ; dec@| HEX@ =  HEX                                                       decimal
63 ; 11  | 0x0B = 00 02        : 512 bytes/sector          BPB_BytsPerSec  = 512
64 ; 13  | 0x0D = 40           : 64 sectors/cluster        BPB_SecPerClus  = 64
65 ; 14  | 0x0E = 01 00        : 2 reserved sectors        BPB_RsvdSecCnt  = 1
66 ; 16  | 0x10 = 02           : 2 FATs                    BPB_NumFATs     = 2 (always 2)
67 ; 17  | 0x11 = 00 02        : 512 entries/directory     BPB_RootEntCnt  = 512
68 ; 19  | 0x13 = 00 00        : BPB_TotSec16 (if < 65535) BPB_TotSec16    = 0
69 ; 22  | 0x16 = EB 00        : 235 sectors/FAT (FAT16)   BPB_FATSize     = 235
70 ; 32  | 0x20 = 77 9F 3A 00  : ‭3841911‬ total sectors     BPB_TotSec32    = ‭3841911‬
71 ; 54  | 0x36 = "FAT16"                                  BS_FilSysType   (not used)
72
73 ; all values below are evaluated in logical sectors
74 ; FAT1           = BPB_RsvdSecCnt = 1
75 ; FAT2           = BPB_RsvdSecCnt + BPB_FATSz32 = 1 + 235 = 236
76 ; OrgRootDirL    = BPB_RsvdSecCnt + (BPB_FATSize * BPB_NumFATs) = 471
77 ; RootDirSize    = BPB_RootEntCnt * 32 / BPB_BytsPerSec         = 32 sectors
78 ; OrgDatas       = OrgRootDir + RootDirSize                     = 503
79 ; OrgCluster     = OrgRootDir - 2*BPB_SecPerClus                = 375 (virtual value)
80 ; FirstSectorOfCluster(n) = OrgCluster + n*BPB_SecPerClus       ==> cluster(3) = 705
81
82 ; ====================================================================================
83
84 ; Formatage FA32 d'une SDSC Card 8GB
85 ; First sector of physical drive (sector 0) content :
86 ; ---------------------------------------------------
87 ; dec@| HEX@
88 ; 446 |0x1BE    : partition table first record  ==> logical block 0       
89 ; 446 |0x1CE    : partition table 2th record    ==> logical block 1
90 ; 446 |0x1DE    : partition table 3th record    ==> logical block 2
91 ; 446 |0x1EE    : partition table 4th record    ==> logical block 3
92
93 ; partition record content :
94 ; ---------------------------------------------------
95 ; dec@|HEX@ =  HEX                                                        decimal
96 ; 0   |0x00 =  0x00     : not bootable
97 ; 1   |0x01 =  82 03 00 : Org CHS offset (Cylinder/Head/Sector)         = not used
98 ; 4   |0x04 =  0x0C     : type FAT32 using LBA addressing               = 12 ==> set FATtype = FAT32 with sector CMD addressing
99 ; 5   |0x05 =  82 03 00 : End offset (Cylinder/Head/Sector offset)      = not used
100 ; 8   |0x08 =  00 20 00 00 : sectors offset of logical block            = 8192
101 ; 12  |0x0C =  00 40 74 00 : sectors size of logical block              = 7618560
102
103 ; 454 |0x1C6 = 00 20 00 00 : FirstSector (of logical drive 0) = BS_FirstSector = 8192
104
105
106 ; FirstSector of logical block (sector 0) content :
107 ; -------------------------------------------------
108 ; dec@| HEX@ =  HEX                                                       decimal
109 ; 11  | 0x0B = 00 02        : 512 bytes/sector          BPB_BytsPerSec  = 512
110 ; 13  | 0x0D = 08           : 8 sectors/cluster         BPB_SecPerClus  = 8
111 ; 14  | 0x0E = 20 00        : 32 reserved sectors       BPB_RsvdSecCnt  = 32
112 ; 16  | 0x10 = 02           : 2 FATs                    BPB_NumFATs     = 2 (always 2)
113 ; 17  | 0x11 = 00 00        : 0                         BPB_RootEntCnt  = 0 (always 0 for FAT32)
114
115 ; 32  | 0x20 = 00 C0 EC 00  : BPB_TotSec32              BPB_TotSec32    = 15515648
116 ; 36  | 0x24 = 30 3B 00 00  : BPB_FATSz32               BPB_FATSz32     = 15152
117 ; 40  | 0x28 = 00 00        : BPB_ExtFlags              BPB_ExtFlags 
118 ; 44  | 0x2C = 02 00 00 00  : BPB_RootClus              BPB_RootClus    = 2
119 ; 48  | 0x30 = 01 00        : BPB_FSInfo                BPB_FSInfo      = 1
120 ; 50  | 0x33 = 06 00        : BPB_BkBootSec             BPB_BkBootSec   = 6
121 ; 82  | 0x52 = "FAT32"      : BS_FilSysType             BS_FilSysType   (not used)
122
123
124 ; all values below are evaluated in logical sectors
125 ; FAT1           = BPB_RsvdSecCnt = 32
126 ; FAT2           = BPB_RsvdSecCnt + BPB_FATSz32 = 32 + 15152 = 15184
127 ; OrgRootDirL    = BPB_RsvdSecCnt + BPB_FATSz32 * BPB_NumFATs = 32 + 15152*2 = 30336
128 ; OrgCluster     = OrgRootDir - 2*BPB_SecPerClus = 30320
129 ; RootDirSize    = BPB_RootEntCnt * 32 / BPB_BytsPerSec         = 0
130 ; OrgDatas       = OrgRootDir + RootDirSize                     = 30336
131 ; FirstSectorOfCluster(n) = OrgCluster + n*BPB_SecPerClus       ==> cluster(6) = 30368
132
133
134
135 BytsPerSec      .equ 512
136
137 ; all sectors are computed as logical, then physically translated at last time by RW_Sector_CMD
138
139 ; in SPI mode CRC is not required, but CMD frame must be ended with a stop bit
140 ; ==================================;
141 RW_Sector_CMD                       ;WX <=== CMD17 or CMD24 (read or write Sector CMD)
142 ; ==================================;
143     BIC.B   #SD_CS,&SD_CSOUT        ; set SD_CS low
144     BIT.B   #SD_CD,&SD_CDIN         ; test CD: memory card present ?
145     JZ      ComputePhysicalSector   ; yes
146     MOV     #COLD,PC                ; no: force COLD
147 ; ----------------------------------;
148 ComputePhysicalSector               ;
149 ; ----------------------------------; input = logical sector...
150     ADD     &BS_FirstSectorL,W      ;3
151     ADDC    &BS_FirstSectorH,X      ;3
152 ; ----------------------------------; ...output = physical sector
153 ;Compute CMD                        ;
154 ; ----------------------------------;
155     MOV     #1,&SD_CMD_FRM          ;3 $(01 00 xx xx xx CMD) set stop bit in CMD frame
156     CMP     #2,&FATtype             ;3 FAT32 ?          
157     JZ      FAT32_CMD               ;2 yes
158 FAT16_CMD                           ;  FAT16 : CMD17/24 byte address = Sector * BPB_BytsPerSec
159     ADD     W,W                     ;  shift left one Sector
160     ADDC.B  X,X                     ;
161     MOV     W,&SD_CMD_FRM+2         ;  $(01 00 ll LL xx CMD)
162     MOV.B   X,&SD_CMD_FRM+4         ;  $(01 00 ll LL hh CMD) 
163     JMP     WaitIdleBeforeSendCMD   ;
164 FAT32_CMD                           ;  FAT32 : CMD17/24 sector address
165     MOV.B   W,&SD_CMD_FRM+1         ;3 $(01 ll xx xx xx CMD)
166     SWPB    W                       ;1
167     MOV.B   W,&SD_CMD_FRM+2         ;3 $(01 ll LL xx xx CMD)
168     MOV.B   X,&SD_CMD_FRM+3         ;3 $(01 ll LL hh xx CMD)
169     SWPB    X                       ;1
170     MOV.B   X,&SD_CMD_FRM+4         ;3 $(01 ll LL hh HH CMD)
171 ; ==================================;
172 WaitIdleBeforeSendCMD               ; <=== CMD41, CMD1, CMD16 (forthMSP430FR_SD_INIT.asm)
173 ; ==================================;
174     CALL #SPI_GET                   ;
175     CMP.B   #-1,W                   ; FFh = expected value <==> MISO = 1 = not busy = idle state
176     JNE WaitIdleBeforeSendCMD       ; loop back until idle state
177     MOV     #0,W                    ; W = expected R1 response = ready, for CMD41,CMD16, CMD17, CMD24
178 ; ==================================;
179 sendCommand                         ;X <=== CMD0, CMD8, CMD55: W = R1 expected response = idle (forthMSP430FR_SD_INIT.asm)
180 ; ==================================;
181                                     ; input : SD_CMD_FRM : {CRC,byte_l,byte_L,byte_h,byte_H,CMD} 
182                                     ;         W = expected return value
183                                     ; output  W is unchanged, flag Z is positionned
184                                     ; reverts CMD bytes before send : $(CMD hh LL ll 00 CRC)
185     MOV     #5,X                    ; X = SD_CMD_FRM ptr AND countdown
186 ; ----------------------------------;
187 Send_CMD_PUT                        ; performs little endian --> big endian conversion
188 ; ----------------------------------;
189     MOV.B   SD_CMD_FRM(X),&SD_TXBUF ;5 
190     CMP     #0,&SD_BRW              ;3 full speed ?
191     JZ      FullSpeedSend           ;2 yes
192 Send_CMD_Loop                       ;
193     BIT     #UCRXIFG,&SD_IFG        ;3 no: case of low speed during memCardInit
194     JZ      Send_CMD_Loop           ;2
195     CMP.B   #0,&SD_RXBUF            ;3 to clear UCRXIFG
196 FullSpeedSend                       ;
197 ;   NOP                             ;0 NOPx adjusted to avoid SD error
198     SUB.B   #1,X                    ;1
199     JHS     Send_CMD_PUT            ;2 U>= : don't skip SD_CMD_FRM(0) !
200
201                                     ; host must provide height clock cycles to complete operation
202                                     ; here X=255, so wait for CMD return expected value with PUT FFh 256 times
203
204 ;    MOV     #4,X                    ; to pass made in PRC SD_Card init 
205 ;    MOV     #16,X                   ; to pass Transcend SD_Card init
206 ;    MOV     #32,X                   ; to pass Panasonic SD_Card init
207 ;    MOV     #64,X                   ; to pass SanDisk SD_Card init
208 ; ----------------------------------;
209 Wait_Command_Response               ; expect W = return value during X = 255 times
210 ; ----------------------------------;
211     SUB     #1,X                    ;1
212     JN      SPI_WAIT_RET            ;2 error on time out with flag Z = 0
213     MOV.B   #-1,&SD_TXBUF           ;3 PUT FFh
214     CMP     #0,&SD_BRW              ;3 full speed ?
215     JZ      FullSpeedGET            ;2 yes
216 cardResp_Getloop                    ;  no: case of low speed during memCardInit (CMD0,CMD8,ACMD41,CMD16)
217     BIT     #UCRXIFG,&SD_IFG        ;3
218     JZ      cardResp_Getloop        ;2
219 FullSpeedGET                        ;
220 ;    NOP                            ;  NOPx adjusted to avoid SD_error
221     CMP.B   &SD_RXBUF,W             ;3 return value = ExpectedValue ?
222     JNZ     Wait_Command_Response   ;2 16~ full speed loop
223 SPI_WAIT_RET                        ; flag Z = 1 <==> Returned value = expected value
224     RET                             ; W = expected value, unchanged
225 ; ----------------------------------;
226
227
228 ; SPI_GET and SPI_PUT are adjusted for SD_CLK = MCLK
229 ; PUT value must be a word or  byte:byte because little endian to big endian conversion
230
231 ; ==================================;
232 SPI_GET                             ; PUT(FFh)
233 ; ==================================; output : W = received byte, X = 0 always
234     MOV #1,X                        ;1
235 ; ==================================;
236 SPI_X_GET                           ; PUT(FFh) X times
237 ; ==================================; output : W = last received byte, X = 0
238     MOV #-1,W                       ;1
239 ; ==================================;
240 SPI_PUT                             ; PUT(W) X time
241 ; ==================================; output : W = last received byte, X = 0
242             SWPB W                  ;1
243             MOV.B W,&SD_TXBUF       ;3 put W high byte then W low byte and so forth, that performs little to big endian conversion
244             CMP #0,&SD_BRW          ;3 full speed ?
245             JZ FullSpeedPut         ;2 
246 SPI_PUTWAIT BIT #UCRXIFG,&SD_IFG    ;3
247             JZ SPI_PUTWAIT          ;2
248             CMP.B #0,&SD_RXBUF      ;3 reset RX flag
249 FullSpeedPut
250 ;           NOP                     ;  NOPx adjusted to avoid SD error
251             SUB #1,X                ;1
252             JNZ SPI_PUT             ;2 12~ loop
253 SPI_PUT_END MOV.B &SD_RXBUF,W       ;3
254             RET                     ;4
255 ; ----------------------------------;
256
257 ; ==================================;
258 readFAT1SectorW                     ; read a FAT1 sector
259 ; ==================================;
260     ADD     &OrgFAT1,W              ;
261 ; ==================================;
262 readSectorW                         ; read a logical sector up to 65535 (case of FAT1,FAT2)
263 ; ==================================;
264     MOV     #0,X                    ;
265 ; ==================================;
266 readSectorWX                        ; read a logical sector
267 ; ==================================;
268     BIS     #1,S                    ; preset sd_read error
269     MOV.B   #51h,&SD_CMD_FRM+5      ; CMD17 = READ_SINGLE_BLOCK
270     CALL    #RW_Sector_CMD          ; which performs logical sector to physical sector then little endian to big endian conversion
271     JNE     SD_CARD_ERROR           ; time out error if R1 <> 0 
272 ; ----------------------------------;
273 WaitFEhResponse                     ; wait SD_Card response FEh
274 ; ----------------------------------;
275     CALL #SPI_GET                   ;
276     CMP.B   #-2,W                   ; FEh expected value
277     JZ  ReadSectorfirst             ; 2
278     JNZ WaitFEhResponse             ;
279 ; ----------------------------------;
280 ReadSectorLoop                      ; get 512+1 bytes, write 512 bytes
281 ; ----------------------------------;
282     MOV.B   &SD_RXBUF,BUFFER-1(X)   ; 5
283 ReadSectorfirst                     ;
284     MOV.B   #-1,&SD_TXBUF           ; 3 put FF
285     NOP                             ; 1 NOPx adjusted to avoid read SD_error
286     ADD     #1,X                    ; 1
287     CMP     #BytsPerSec+1,X         ; 2
288     JNZ     ReadSectorLoop          ; 2 14 cycles loop read byte
289 ; ----------------------------------;
290     MOV.B   #-1,&SD_TXBUF           ; 3 put only one FF because first CRC byte is already received...
291 ; ----------------------------------;
292 ReadWriteHappyEnd                   ; <==== WriteSector
293 ; ----------------------------------;
294     BIC     #3,S                    ; reset read and write errors
295     BIS.B   #SD_CS,&SD_CSOUT        ; SD_CS = high  
296     RET                             ; 
297 ; ----------------------------------;
298
299     .IFDEF SD_CARD_READ_WRITE
300
301 ; ==================================;
302 WriteSectorW                        ; write a logical sector up to 65535 (FAT1,FAT2)
303 ; ==================================;
304     MOV     #0,X                    ;
305 ; ==================================;
306 WriteSectorWX                       ; write a logical sector
307 ; ==================================;
308     BIS     #2,S                    ; preset sd_write error
309     MOV.B   #058h,SD_CMD_FRM+5      ; CMD24 = WRITE_SINGLE_BLOCK
310     CALL    #RW_Sector_CMD          ; which performs logical sector to physical sector then little endian to big endian conversions
311     JNE     SD_CARD_ERROR           ; ReturnError = 2
312     MOV     #0FFFEh,W               ; PUT FFFEh as preamble requested for sector write
313     MOV     #2,X                    ; to put 16 bits value
314     CALL    #SPI_PUT                ; which performs little endian to big endian conversion
315 ; ----------------------------------;
316 WriteSectorLoop                     ; 11 cycles loop write, starts with X = 0
317 ; ----------------------------------;
318     MOV.B   BUFFER(X),&SD_TXBUF     ; 5
319     NOP                             ; 1 NOPx adjusted to avoid write SD_error
320     ADD     #1,X                    ; 1
321     CMP     #BytsPerSec,X           ; 2
322     JNZ     WriteSectorLoop         ; 2
323 ; ----------------------------------;
324 WriteSkipCRC16                      ; CRC not used in SPI mode
325 ; ----------------------------------;
326     MOV     #3,X                    ; PUT 2 bytes to skip CRC16
327     CALL    #SPI_X_GET              ; + 1 byte to get data token in W
328 ; ----------------------------------;
329 CheckWriteState                     ;
330 ; ----------------------------------;
331     BIC.B   #0E1h,W                 ; apply mask for Data response
332     CMP.B   #4,W                    ; data accepted
333     JZ      ReadWriteHappyEnd       ;
334 ; ----------------------------------;
335
336     .ENDIF ; SD_CARD_READ_WRITE
337
338 ; SD Error n°
339 ; High byte
340 ; 1  = CMD17    read error
341 ; 2  = CMD24    write error 
342 ; 4  = CMD0     time out (GO_IDLE_STATE)
343 ; 8  = ACMD41   time out (APP_SEND_OP_COND)
344 ; 10 = CMD16    time out (SET_BLOCKLEN)
345 ; 20 = not FAT16/FAT32 media, low byte = partition ID
346
347 ; low byte, if CMD R1 response : |0|7|6|5|4|3|2|1|
348 ; 1th bit = In Idle state
349 ; 2th bit = Erase reset
350 ; 3th bit = Illegal command
351 ; 4th bit = Command CRC error
352 ; 5th bit = erase sequence error
353 ; 6th bit = address error
354 ; 7th bit = parameter error
355
356 ; ----------------------------------;
357 SD_CARD_ERROR                       ; <=== SD_INIT errors 4,8,$10
358 ; ----------------------------------;
359     SWPB S                          ; High Level error in High byte
360     ADD &SD_RXBUF,S                 ; add SPI(GET) return value to high level error
361 SD_CARD_ID_ERROR                    ; <=== SD_INIT error $20
362     BIS.B #SD_CS,&SD_CSOUT          ; SD_CS = high
363     mDOCOL                          ;
364     .word   XSQUOTE                 ;
365     .byte   11,"< SD Error!"        ;
366 ; ----------------------------------;
367 SD_QABORTYES                        ; <=== OPEN/READ and WRITE errors
368 ; ----------------------------------;
369     FORTHtoASM                      ;
370     SUB #4,PSP                      ;
371     MOV TOS,2(PSP)                  ;
372     MOV &BASE,0(PSP)                ;
373     MOV #10h,&BASE                  ; select hex
374     MOV S,TOS                       ;
375     ASMtoFORTH                      ;
376     .word   UDOT                    ;
377     .word   FBASE,STORE             ; restore base
378     .word   QABORTYES               ;
379 ; ----------------------------------;
380