OSDN Git Service

V4.0
[fast-forth/master.git] / forthMSP430FR_SD_LowLvl.asm
1 ; -*- coding: utf-8 -*-
2 ; forthMSP430FR_SD_lowLvl.asm
3
4 BytsPerSec      .equ 512
5
6 ; all sectors are computed as logical, then physically translated at last time by RW_Sector_CMD
7
8 ; in SPI mode CRC is not required, but CMD frame must be ended with a stop bit
9 ; ==================================;
10 RW_Sector_CMD                       ;WX <=== CMD17 or CMD24 (read or write Sector CMD)
11 ; ==================================;
12     BIC.B   #CS_SD,&SD_CSOUT        ; set Chip Select low
13 ; ----------------------------------;
14 ComputePhysicalSector               ; input = logical sector...
15 ; ----------------------------------;
16     ADD     &BS_FirstSectorL,W      ;3
17     ADDC    &BS_FirstSectorH,X      ;3
18 ; ----------------------------------; ...output = physical sector
19 ;Compute CMD                        ;
20 ; ----------------------------------;
21     MOV     #1,&SD_CMD_FRM          ;3 $(01 00 xx xx xx CMD) set stop bit in CMD frame
22 FAT32_CMD                           ;  FAT32 : CMD17/24 sector address
23     MOV.B   W,&SD_CMD_FRM+1         ;3 $(01 ll xx xx xx CMD)
24     SWPB    W                       ;1
25     MOV.B   W,&SD_CMD_FRM+2         ;3 $(01 ll LL xx xx CMD)
26     MOV.B   X,&SD_CMD_FRM+3         ;3 $(01 ll LL hh xx CMD)
27     SWPB    X                       ;1
28     MOV.B   X,&SD_CMD_FRM+4         ;3 $(01 ll LL hh HH CMD)
29 ; ==================================;
30 WaitIdleBeforeSendCMD               ; <=== CMD41, CMD1, CMD16 (forthMSP430FR_SD_INIT.asm)
31 ; ==================================;
32     CALL #SPI_GET                   ;
33     ADD.B   #1,W                    ; expected value = FFh <==> MISO = 1 = SPI idle state
34     JNZ WaitIdleBeforeSendCMD       ; loop back if <> FFh
35 ; ==================================; W = 0 = expected R1 response = ready, for CMD41,CMD16, CMD17, CMD24
36 sendCommand                         ;
37 ; ==================================;
38                                     ; input : SD_CMD_FRM : {CRC,byte_l,byte_L,byte_h,byte_H,CMD}
39                                     ;         W = expected return value
40                                     ; output  W is unchanged, flag Z is positionned
41                                     ; reverts CMD bytes before send : $(CMD hh LL ll 00 CRC)
42     MOV     #5,X                    ; X = SD_CMD_FRM ptr AND countdown
43 ; ----------------------------------;
44 Send_CMD_PUT                        ; performs little endian --> big endian conversion
45 ; ----------------------------------;
46     MOV.B   SD_CMD_FRM(X),&SD_TXBUF ;5
47     CMP     #0,&SD_BRW              ;3 full speed ?
48     JZ      FullSpeedSend           ;2 yes
49 Send_CMD_Loop                       ;  case of low speed during memCardInit
50     BIT     #RX_SD,&SD_IFG          ;3
51     JZ      Send_CMD_Loop           ;2
52     CMP.B   #0,&SD_RXBUF            ;3 to clear UCRXIFG
53 FullSpeedSend                       ;
54 ;   NOP                             ;0 NOPx adjusted to avoid SD error
55     SUB.B   #1,X                    ;1
56     JC      Send_CMD_PUT            ;2 U>= : don't skip SD_CMD_FRM(0) !
57                                     ; host must provide height clock cycles to complete operation
58                                     ; here X=255, so wait for CMD return expected value with PUT FFh 256 times
59 ;    MOV     #4,X                    ; to pass made in PRC SD_Card init
60 ;    MOV     #16,X                   ; to pass Transcend SD_Card init
61 ;    MOV     #32,X                   ; to pass Panasonic SD_Card init
62 ;    MOV     #64,X                   ; to pass SanDisk SD_Card init
63 ; ----------------------------------;
64 Wait_Command_Response               ; expect W = return value during X = 255 times
65 ; ----------------------------------;
66     SUB     #1,X                    ;1
67     JN      SPI_WAIT_RET            ;2 error on time out with flag Z = 0
68     MOV.B   #-1,&SD_TXBUF           ;3 PUT FFh
69     CMP     #0,&SD_BRW              ;3 full speed ?
70     JZ      FullSpeedGET            ;2 yes
71 cardResp_Getloop                    ;  case of low speed during memCardInit (CMD0,CMD8,ACMD41,CMD16)
72     BIT     #RX_SD,&SD_IFG          ;3
73     JZ      cardResp_Getloop        ;2
74 FullSpeedGET                        ;
75 ;    NOP                            ;  NOPx adjusted to avoid SD_error
76     CMP.B   &SD_RXBUF,W             ;3 return value = ExpectedValue ?
77     JNZ     Wait_Command_Response   ;2 16~ full speed loop
78 SPI_WAIT_RET                        ; flag Z = 1 <==> Returned value = expected value
79     MOV @RSP+,PC                    ; W = expected value, unchanged
80 ; ----------------------------------;
81
82 ; ----------------------------------;
83 sendCommandIdleRet                  ; <=== CMD0, CMD8, CMD55: W = 1 = R1 expected response = idle (forthMSP430FR_SD_INIT.asm)
84 ; ----------------------------------;
85     MOV     #1,W                    ; expected R1 response (first byte of SPI R7) = 01h : idle state
86     JMP     sendCommand             ;
87 ; ----------------------------------;
88
89
90 ; SPI_GET and SPI_PUT are adjusted for SD_CLK = MCLK
91 ; PUT value must be a word or  byte:byte because little endian to big endian conversion
92
93 ; ==================================;
94 SPI_GET                             ; PUT(FFh) one time, output : W = received byte, X = 0
95 ; ==================================;
96     MOV #1,X                        ;
97 ; ==================================;
98 SPI_X_GET                           ; PUT(FFh) X times, output : W = last received byte, X = 0
99 ; ==================================;
100     MOV #-1,W                       ;
101 ; ==================================;
102 SPI_PUT                             ; PUT(W) X times, output : W = last received byte, X = 0
103 ; ==================================;
104             SWPB W                  ;1
105             MOV.B W,&SD_TXBUF       ;3 put W high byte then W low byte and so forth, that performs little to big endian conversion
106             CMP #0,&SD_BRW          ;3 full speed ?
107             JZ FullSpeedPut         ;2
108 SPI_PUTWAIT BIT #RX_SD,&SD_IFG      ;3
109             JZ SPI_PUTWAIT          ;2
110             CMP.B #0,&SD_RXBUF      ;3 reset RX flag
111 FullSpeedPut
112 ;           NOP                     ;  NOPx adjusted to avoid SD error
113             SUB #1,X                ;1
114             JNZ SPI_PUT             ;2 12~ loop
115 SPI_PUT_END MOV.B &SD_RXBUF,W       ;3
116             MOV @RSP+,PC            ;4
117 ; ----------------------------------;
118
119     .IFDEF SD_CARD_READ_WRITE
120         ASMWORD "RD_SECT"           ; ReaD SECTor W=lo, X=Hi
121     .ENDIF ; SD_CARD_READ_WRITE
122 ; ==================================;
123 ReadSectorWX                        ; SWX read a logical sector
124 ; ==================================;
125     BIS     #1,S                    ; preset sd_read error
126     MOV.B   #51h,&SD_CMD_FRM+5      ; CMD17 = READ_SINGLE_BLOCK
127     CALL    #RW_Sector_CMD          ; which performs logical sector to physical sector then little endian to big endian conversion
128     JNE     SD_CARD_ERROR           ; time out error if R1 <> 0
129 ; ----------------------------------;
130 WaitFEhResponse                     ; wait for SD_Card response = FEh
131 ; ----------------------------------;
132     CALL #SPI_GET                   ;
133     ADD.B   #2,W                    ;1 W = 0 ?
134     JZ  ReadSectorFirstByte         ;2 yes, X = 0
135     JNZ WaitFEhResponse             ;2
136 ; ----------------------------------;
137 ReadSectorLoop                      ; get 512 bytes + CRC16 in SD_BUF
138 ; ----------------------------------;
139     MOV.B   &SD_RXBUF,SD_BUF-1(X)   ; 5
140 ReadSectorFirstByte                 ; W=0
141     MOV.B   #-1,&SD_TXBUF           ; 3 put FF
142     NOP                             ; 1 NOPx adjusted to avoid read SD_error
143     ADD     #1,X                    ; 1
144     CMP     #BytsPerSec+3,X         ; 2
145     JNZ     ReadSectorLoop          ; 2 14 cycles loop read byte
146 ; ----------------------------------;
147 ReadWriteHappyEnd                   ; <==== WriteSector
148 ; ----------------------------------;
149     BIC #3,S                        ; Clear read and write errors
150     BIS.B #CS_SD,&SD_CSOUT          ; Chip Select high
151     MOV @RSP+,PC                    ; W = 0
152 ; ----------------------------------;
153
154     .IFDEF SD_CARD_READ_WRITE
155
156         ASMWORD "WR_SECT"           ; WRite SECTor W=lo, X=Hi
157 ; ==================================;
158 WriteSectorWX                       ; write a logical sector
159 ; ==================================;
160     BIS     #2,S                    ; preset sd_write error
161     MOV.B   #058h,SD_CMD_FRM+5      ; CMD24 = WRITE_SINGLE_BLOCK
162     CALL    #RW_Sector_CMD          ; which performs logical sector to physical sector then little endian to big endian conversions
163     JNE     SD_CARD_ERROR           ; ReturnError = 2
164     MOV     #0FFFEh,W               ; PUT FFFEh as preamble requested for sector write
165     MOV     #2,X                    ; to put 16 bits value
166     CALL    #SPI_PUT                ; which performs little endian to big endian conversion
167 ; ----------------------------------;
168 WriteSectorLoop                     ; 11 cycles loop write, starts with X = 0
169 ; ----------------------------------;
170     MOV.B   SD_BUF(X),&SD_TXBUF     ; 5
171     NOP                             ; 1 NOPx adjusted to avoid write SD_error
172     ADD     #1,X                    ; 1
173     CMP     #BytsPerSec,X           ; 2
174     JNZ     WriteSectorLoop         ; 2
175 ; ----------------------------------;
176 WriteSkipCRC16                      ; CRC16 not used in SPI mode
177 ; ----------------------------------;
178     MOV     #3,X                    ; PUT 3 times to skip CRC16
179     CALL    #SPI_X_GET              ; and to get data token in W
180 ; ----------------------------------;
181 CheckWriteState                     ;
182 ; ----------------------------------;
183     BIC.B   #0E1h,W                 ; apply mask for Data response
184     SUB.B   #4,W                    ; data accepted
185     JZ      ReadWriteHappyEnd       ;
186 ; ----------------------------------;
187
188     .ENDIF ; SD_CARD_READ_WRITE
189
190 ; ----------------------------------;
191 ; SD ERRORS
192 ; ----------------------------------;
193 ; 0   = NO SD_CARD
194 ; ----------------------------------;
195
196 ; ----------------------------------;
197 ; High byte = 0 : FILE level error
198 ; ----------------------------------;
199 ;       low byte
200 ;       $1  = PathNameNotFound
201 ;       $2  = NoSuchFile      
202 ;       $4  = alreadyOpen     
203 ;       $8  = NomoreHandle    
204 ;       $10 = InvalidPathname
205 ;       $20 = DiskFull
206 ;       
207 ; ----------------------------------;
208 ; High byte <> 0 : SD_CARD level error 
209 ; ----------------------------------;
210 ; 1   = CMD17    read error
211 ; 2   = CMD24    write error
212 ; 4   = CMD0     time out (GO_IDLE_STATE)
213 ; 8   = ACMD41   time out (APP_SEND_OP_COND)
214 ; $10 = partition error, low byte = partition ID <> FAT32
215 ;
216 ;       low byte, if CMD R1 response:
217 ;       bit0 = In Idle state
218 ;       bit1 = Erase reset
219 ;       bit2 = Illegal command
220 ;       bit3 = Command CRC error
221 ;       bit4 = erase sequence error
222 ;       bit5 = address error
223 ;       bit6 = parameter error
224
225 ;       low byte if Data Response Token
226 ;       Every data block written to the card will be acknowledged by a data response token.
227 ;       It is one byte long and has the following format:
228 ;       %xxxx_sss0 with bits(3-1) = Status
229 ;       The meaning of the status bits is defined as follows:
230 ;       '010' - Data accepted.
231 ;       '101' - Data rejected due to a CRC error.
232 ;       '110' - Data Rejected due to a Write Error
233
234 ; ------------------------------;
235 SD_CARD_ERROR                   ; <=== SD_INIT errors 4,8,$10 from forthMSP430FR_SD_INIT.asm
236 ; ------------------------------;
237         SWPB S                  ; High Level error in High byte
238         BIS &SD_RXBUF,S         ; add SPI(GET) return value as low byte error
239 SD_CARD_INIT_ERROR              ; <=== from forthMSP430FR_SD_INIT.asm
240 SD_CARD_FILE_ERROR              ; <=== from forthMSP430FR_SD_LOAD.asm, forthMSP430FR_SD_RW.asm 
241 NO_SD_CARD                      ; from forthMSP430FR_SD_LOAD(Open_File)
242         MOV S,TOS               ;
243         CALL #ABORT_TERM+4      ;
244         CALL #INIT_FORTH        ;
245     .IFDEF BOOTLOADER           ;
246         .word   NOBOOT          ;
247     .ENDIF
248         .word   ECHO            ;
249         .word   XSQUOTE         ;
250         .byte   4,27,"[7m"      ;
251         .word   TYPE            ;
252         .word   XSQUOTE         ;
253         .byte   10,"SD_ERROR $" ;
254         .word   TYPE            ;
255         .word   LIT,10h         ;
256         .word   LIT,BASEADR,STORE;
257         .word   UDOT            ;
258         .word   LIT,10          ;
259         .word   LIT,BASEADR,STORE;
260         .word   BRAN,SDABORT_END;   to set normal video display then goto ABORT
261 ; ------------------------------;
262