OSDN Git Service

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