; ****************************************************************************** ; SX MultiMedia Card (MMC) VIRTUAL PERIPHERAL AUDIO DEMO ; (C) Copyright 1997-2000 Scenix Semiconductor ; ; ; Length: 476 bytes (total) ; Authors: Craig Webb, Andrian Kouznetsov ; Written: 97/03/10 to 00/10/30 ; ; This program implements six virtual peripherals on Scenix's SX28/52 ; DEMO board for demonstrating MultiMedia Card (MMC) external memory ; storage playing its contents as a .WAV file through the audio plug-in PCB. ; The MMC is accessed through a high level command interpreter subroutine ; peripheral that controls the MMC by way of an SPI subroutine interface ; peripheral. Data coming in from the MMC is stored in a circular buffer ; as it awaits output through the audio harware. The program uses timer ; clock virtual peripheral in conjunction with a pulse width modulation ; (PWM) virtual peripheral for output of the stored MMC data as streamed ; audio samples, and also uses a sigma-delta A/D virtual peripheral to ; sample external signals that can then be written to the MMC. ; ; 1) MMC command interpreter interface ; 2) SPI interface subroutine(s) ; 3) Circular storage buffer ; 4) Timer routine ; 5) Pulse-Width Modulated (PWM) outputs (2) ; 6) Adjustable 8-15-bit Analog-to-Digital Converter (ADC) (1) ; ; These latter four of these virtual peripherals take advantage ; of the SX's internal RTCC-driven interrupt and operate ; in the background while the main program loop is executing. ; ;****************************************************************************** ; Program Notes: ; ; -Be careful that the SX SPI port pins are initialized when inserting or ; removing the MMC, oherwise peculiar card states can result (in which ; case the MMC should be completely removed and powered off, and then ; the SYNCHRONIZATION and INITIALIZATION routines must be run again). ; ; -if the program does encounter any MMC communication error, it is best ; to repeat the INITIALIZATION routine, and occasionally the ; SYNCHRONIZATION routine also. ; ;============================================================================== ; ;******************************* Program Variables *************************** ; ; ;****** Assembly Options ; pcb_revision = 0 ;0 or 1 ;PCB revision 1.x compiler = 0 ;0 or 1 ;0=SX-Key, 1=SXIDE stereo = 0 ;0 or 1 ;set =1 for stereo PCM data chip_type = 1 ;0 or 1 ;0=SX18/28, 1=SX52 include_adc = 0 ;0 or 1 ;0=adc routine not included ; ;****** Adjustable Paramaters ; sample_freq = 11025 ;6512-44100 ;sampling rate of .wav file MMC_size = 4 ;1-128 ;storage size of MMC card resolution = 8 ;8-15 ;adc resolution (8-15 bits) pwm0_init = 80h ;0-FFh ;initial pwm0 voltage pwm1_init = 80h ;0-FFh ;initial pwm1 voltage ; ;****** Program Variables ; int_period = 40+(include_adc*20)+6 ;minimum + main routine allowance sx_freq_factor = 1 ;this is a time delay scaling factor, ; for SX running at 50MHz(=1), 100MHz (=2) ; ;****** Program Constants & Dependent Variables ; ;sample_freq= $380 @ 11,025Hz mono, with xtal=50MHz, with adc on samp_freq = $380*int_period/66*sample_freq/11025 ;sets the audio PCM sample rate IF stereo=1 samp_freq = samp_freq*2 ;stereo needs twice the sample output rate ENDIF IF MMC_size<16 end_of_mem = MMC_size<<4-3 ;last bank of mmc memory blocks ELSE ; for MMC cards >16Meg end_of_mem = MMC_size>>4-3 ;last bank of mmc memory blocks ENDIF end_of_mem = $37 ; or end of audio sample (comment this if needed) IF compiler=0 ;assembler directive (for SX-Key) freq 50_000_000*sx_freq_factor ;default clock rate: 50 MHz ENDIF ; ;***SPIX timing delays: ;spix_rate = (1 + (3 * ( sx_freq_factor - 1))) spix_rate = sx_freq_factor ;rate factor for SPIX.MMC ; (may need to be trimmed for different SX clock rates) sync_duration = 10 ;?-255 ;MMC SYNCHRONIZATION function duration cmd1_resp_wait = $80 * sx_freq_factor ;?-128 ;initialization (CMD1) response wait duration cmd1_delay1 = $8 ;* sx_freq_factor ;?-128 ;initialization (CMD1) internal loop delay cmd1_delay2 = $10 ;* sx_freq_factor ;?-128 ;initialization (CMD1) internal loop delay cmd1_delay3 = $80 * sx_freq_factor ;?-128 ;initialization (CMD1) internal loop delay resp_r1_delay = 32 * sx_freq_factor ;2-255 ;delay for a RESPONSE from MMC blk_rd_delay1 = 1 * sx_freq_factor ;?-255 ;delay for MMC initial block read preparation " written blk_rd_wait = 20 * sx_freq_factor ;?-255 ;read wait time MMC incoming data bytes blk_wr_delay = 20 * sx_freq_factor ;?-255 ;delay for MMC initial block write preparation ; option_init = %10001000 ;bits: 1=RTCC@01h|0=int_en|0=RTCC_internal|x|psa(1=WDT)|ps(2-0) resolution = resolution-8 ;8-15 ;adc resolution (8-15 bits) ; mmc_blk_size = 512 ;block size for reading/writing MMC (in SPI mode) mmc_buffsize = 32 ;MMC read/write buffer size: must be =(2^n)*16, n=0,1,2(,3 for SX52) ; (only 16 and 32 have been tested) ;****** Assembler Directives ; ; DEVICE turbo ID 'MMCAudio' ;program ID label RESET reset_entry ;set reset/boot address ;******************* Configuration DATA and I/O pins ************************* ; ;****** Port definitions ; RA_IO = %0010 ;port A I/O directions RA_init = %1111 ;port A initial output states ;--------------- ;Pin assingment for SPI_X interface spix_clk_pin EQU RA.3 ;SPI clock output spix_out_pin EQU RA.2 ;SPI-Master-Out-Slave-In spix_in_pin EQU RA.1 ;SPI-Master-In-Slave-Out spix_cs_pin EQU RA.0 ;SPI device select ;=============== RB_IO EQU %10111111 ;port B I/O directions RB_init EQU %11111111 ;port B initial output states analog_port1 EQU RB ;--------------- LEDs EQU RB ;individual LED outputs ; await_button EQU LEDs.3 ;await button signal init_err EQU LEDs.2 ;signals initialize MMC error read_err EQU LEDs.1 ;signals read from MMC error write_err EQU LEDs.0 ;signals write to MMC error ;--------------- IF pcb_revision=0 ;--------------- RC_IO EQU %11110110 ;port C I/O directions RC_init EQU %11111111 ;port C initial output states analog_port2 EQU RC ;--------------- ;note: make duplicate changes in "analog_buff" pwm0_pin EQU RB.6 ;Pulse width mod. PWM0 output pwm1_pin EQU RC.3 ;Pulse width mod. PWM1 output adc0_in_pin EQU RC.2 ;ADC0 input pin adc0_out_pin EQU RC.0 ;ADC0 output/calibrate pin ;--------------- ELSE ;pcb_revision=1.1 ;--------------- RC_IO EQU %11111010 ;port C I/O directions RC_init EQU %11111111 ;port C initial output states analog_port2 EQU RC ;--------------- ;note: make duplicate changes in "analog_buff" pwm0_pin EQU RB.6 ;Pulse width mod. PWM0 output pwm1_pin EQU RC.2 ;Pulse width mod. PWM1 output adc0_in_pin EQU RC.1 ;ADC0 input pin adc0_out_pin EQU RC.0 ;ADC0 output/calibrate pin ;=============== ENDIF ;revision ; ;******************************** MMC_SPIX RAM **************************** ORG $0E ;global ram next_samp_ptr DS 1 ;points to next sample in buffer mmc_temp_data DS 1 ;temporary storage to move the data ; between the SX RAM banks ;=============== ;SPIX and MMC make use of the same RAM bank mmc_spix_ram ORG $10 ;MMC/SPI control register bank ; mmc_status ds 1 ;MMC driver status byte ;--------- spix_busy equ mmc_status.7 ;Busy bit set by SPIX VP to HIGH when byte ;transfer (SPI) is in progress mmc_busy equ mmc_status.6 ;set when the MMC is in BUSY state. Used in WRITE MODE mmc_read_write_data equ mmc_status.5 ;indicates that BLOCK READ/WRITE cycle is in progress mmc_error equ mmc_status.4 ;any error in data transfer ;MMC_R1 and MMC_R2 contain the error message mmc_no_response equ mmc_status.3 ;no response R1 was received ;within required time mmc_data_error equ mmc_status.2 ;data error token received ;during Block Read/Write command mmc_no_data equ mmc_status.1 ;no data block received from MMC mmc_wrong_command equ mmc_status.0 ;Set by the commnds decoder, indicates not supported command ;======== mmc_cmd ds 1 ;mmc command - 6 bytes mmc_addr_b3 ds 1 mmc_addr_b2 ds 1 mmc_addr_b1 ds 1 mmc_addr_b0 ds 1 mmc_cmd_crc ds 1 mmc_r1 ds 1 ;mmc response - 2bytes mmc_r2 ds 1 mmc_temp ds 1 ;temporary storage for MMC driver mmc_temp1 ds 1 mmc_temp2 ds 1 mmc_data_pointer ds 1 ;pointer to the current address ;of the SX data RAM ;SPIX data spix_data_io ds 1 ;one-byte I/O data buffer/shift register spix_temp ds 1 ;temporary storage spix_shift_counter ds 1 ;I/O shift counter ;------------------------ ; org 30h ;bank4 variables analog = $ ;pwm and ADC bank & timer ; analog_buff1 DS 1 ;analog output buffer analog_buff2 DS 1 ;analog output buffer IF pcb_revision=0 ;--------------- pwm0_out EQU analog_buff1.6 ;pwm0 buffer pwm1_out EQU analog_buff2.3 ;pwm1 buffer adc0_out EQU analog_buff2.0 ;adc0 out buffer ;--------------- ELSE ;--------------- pwm0_out EQU analog_buff1.6 ;pwm0 buffer pwm1_out EQU analog_buff2.2 ;pwm1 buffer adc0_out EQU analog_buff2.0 ;adc0 out buffer ;--------------- ENDIF pwm0 DS 1 ;pwm0 - value pwm0_acc DS 1 ; - accumulator pwm1 DS 1 ;pwm1 - value pwm1_acc DS 1 ; - accumulator ; adc0_lo DS 1 ;adc0 - value low byte adc0_hi DS 1 ; " high byte adc0_count_lo DS 1 ; - real-time count (lo) adc0_count_hi DS 1 ; - " " " (hi) adc0_acc_lo DS 1 ; - accumulator (lo) adc0_acc_hi DS 1 ; - " (hi) ; freq_low ds 1 ;frequency value low byte freq_high ds 1 ;frequency value high byte freq_accl ds 1 ;frequency accumulator low byte freq_acch ds 1 ;frequency accumulator high byte ;=============== mmc_data_ram ORG $70 ;MMC read/write data buffer(length of buffer=mmc_buffsize) ; (e.g. in the case of 32 bytes it will occupy banks $50 & $70) ;**************************** INTERRUPT CODE ******************************* ; ORG 0 ; ;****** Virtual Peripheral: TIMER/FREQUENCY OUTPUT ; ; This routine adds a programmable value to a 16-bit accumulator (a pair of ; two 8-bit registers) during each pass through the interrupt. It then ; copies the value from the high bit of the accumulator to the ; appropriate output port pin (LED, speaker, etc.) ; ; Input variable(s) : timer_low,timer_high,timer_accl,timer_acch ; freq_low,freq_high,freq_accl,freq_acch ; Output variable(s) : LED port pin, speaker port pin ; Variable(s) affected : timer_accl, timer_acch, freq_accl, freq_acch ; Flag(s) affected : none ; Size : 1 byte + 10 bytes (per timer) ; Timing (turbo) : 1 cycle + 10 cycles (per timer) ; :frequency bank analog ;switch to timer (& adc/pwm) bank ; clc ;only needed if CARRYX=ON add freq_accl,freq_low ;adjust freq's accumulator CLR W ;zero W reg. SNC ;did we get an overflow in low byte? MOV W,#1 ;if so, prepare to adjust high byte ADD W,freq_high ; (freq = 16 bits long) SZ ;if overflow for adjustment, skip ahead ADD freq_acch,W ;adjust high byte of accumulator SC ;skip ahead if timer triggered JMP :done ;if not, jump ahead to end :circ_buffer MOV W,next_samp_ptr ;load sample pointer MOV FSR,W ; for indirect addressing MOV W,ind ;load next sample BANK analog ;reset bank to analog CLRB FSR.7 ; and make sure we're in lower 128reg. block IF stereo=0 MOV pwm0,W ;convert it to audio MOV pwm1,W ; " ELSE SB next_samp_ptr.0 ;is this left channel? MOV pwm0,W ;yes, send out out left SNB next_samp_ptr.0 ;otherwise, if it's right channel MOV pwm1,W ; send it out right ENDIF INC next_samp_ptr ;advance pointer IF chip_type=0 ;SX18/28 MOV W,#buff_size*2+mmc_data_ram ;last address ELSE ;SX52 MOV W,#mmc_data_ram+mmc_buffsize ;last address ENDIF MOV W,next_samp_ptr-W ;test for end of buffer MOV W,#mmc_data_ram ;pre-load new offset in case SNZ ;if not at end, skip ahead MOV next_samp_ptr,W ;reset to start of buffer IF chip_type=0 MOV W,#$10 ;keep to odd banks for SX18/28 OR next_sample_ptr,W ; " ENDIF :done ; ;***** Virtual Peripheral: Pulse Width Modulators ; ; These routines create an 8-bit programmable duty cycle output at the ; respective pwm port output pins whose duty cycle is directly proportional ; to the value in the corresponding pwm register. This value is added to an ; accumulator on each interrupt pass interrupt. When the addition causes a ; carry overflow, the ouput is set to the high part of its duty cycle. ; These routines are timing critical and must be placed before any ; variable-execution-rate code (like the UART, for example). ; ; Input variable(s) : pwm0,pwm0_acc,pwm1,pwm1_acc ; Output variable(s) : pwm port pins ; Variable(s) affected : port_buff, pwm0_acc, pwm1_acc ; Flag(s) affected : none ; Size : 3 bytes + 4 bytes (per pwm) ; + 4 bytes shared with adc code (see below) ; Timing (turbo) : 3 cycles + 4 cycles (per pwm) ; + 4 cycles shared with adc code (see below) ; ;:set_analog bank analog ;switch to adc/pwm bank clr analog_buff1 ;zero pwm output buffer clr analog_buff2 ;zero pwm output buffer :pwm0 add pwm0_acc,pwm0 ;adjust pwm0 accumulator snc ;did it trigger? setb pwm0_out ;yes, toggle pwm0 high :pwm1 add pwm1_acc,pwm1 ;adjust pwm1 accumulator snc ;did it trigger? setb pwm1_out ;yes, toggle pwm1 high ;:update_analog MOV analog_port1,analog_buff1 ;update cap. charge/discharge pins ; MOV analog_port2,analog_buff2 ;update cap. charge/discharge pins :end_pwms ; IF include_adc=1 ;is this to be assembled in? ;***** Virtual Peripheral: Bitstream Analog to Digital Converters ; ; These routines allow an 8-bit value to be calculated which corresponds ; directly (within noise variation limits) with the voltage (0-5V) present ; at the respective adc port input pins. These routines are timing critical ; and must be placed before any variable-execution-rate code (like the UART, ; for example). The currently enabled routine (version A) has been optimized ; for size and speed, and RAM register usage, however a fixed execution rate, ; yet slightly larger/slower routine (version B) is provided in commented ; (disabled) form to simplify building other timing-critical virtual ; peripheral combinations (i.e. that require fixed rate preceeding code). ; Note: if version B is selected, version A must be disabled (commented) ; ; Input variable(s) : adc0_in_pin,adc0_acc_lo/hi,adc0_count_lo/hi ; Output variable(s) : analog_port1,analog_port2,analog_buff1,analog_buff2 ; Variable(s) affected : adc0_out,adc0_acc_lo/hi,adc0_count_lo/hi ; Flag(s) affected : none ; Size : 20 + 4 bytes shared with pwm code (see above) ; Timing : 5 cycle shared with pwm code (see above) + ; (a) [>99.5% of time] 15 cycles ; (b) [<0.5% of time] 20 cycles ; ;*** If the PWM routines are removed, the following 2 instructions must ;*** be enabled (uncommented) for the ADC routine to function properly: ; bank analog ;switch to adc/pwm bank :adc0 SB adc0_in_pin ;get current status of adc0 SETB adc0_out ;complement input to output SNB adc0_in_pin ; " CLRB adc0_out ; " SB adc0_in_pin ;check if adc0 triggered? INCSZ adc0_acc_lo ;if so, incr. 16-bit accumulator DEC adc0_acc_hi ; adjusting high byte as necessary INC adc0_acc_hi ; but making sure not to :adj_count INCSZ adc0_count_lo ;adjust 16-bit counter DEC adc0_count_hi ; by skipping this instr. INC adc0_count_hi ; when low byte overflows :check_trig SB adc0_count_hi.resolution ;sample ready? JMP :done_adcs ;if not, exit adc routine :adc_ready MOV adc0_lo,adc0_acc_lo ;yes, copy new value MOV adc0_hi,adc0_acc_hi ; into adc0 registers CLR adc0_count_hi ;clear count (low already=0) CLR adc0_acc_lo ;clear accumulator (low) CLR adc0_acc_hi ;clear accumulator (high) :done_adcs ENDIF ;whether to include adc or not :update_analog MOV analog_port1,analog_buff1 ;update cap. charge/discharge pins MOV analog_port2,analog_buff2 ;update cap. charge/discharge pins MOV W,#-int_period ;interrupt every 'int_period' clocks RETIW ;exit interrupt :end_int ; ;****** End of interrupt sequence ;=========================================================================== ; ;***************************** PROGRAM DATA ******************************** ; ;****************************** SUBROUTINES ******************************** ; Sine_Table JMP PC+W ;Lookup sine value (32 bytes) RETW 128,153,174,199,219,234,246,254,255,254,246,234,219,199,174,153 RETW 128,103,79,57,37,22,10,2,0,2,10,22,37,57,79,103 ;Sine_Table_16 RETW 0,9,37,79,128,176,218,246,255,246,218,176,128,79,37,9 ; ;****************************** ;*** 8-BIT SPI Master VP - SPIX ;****************************** ;SPIX DATA TRANSFER ;================== ; ;***Send the byte spix_send bank mmc_spix_ram ;select SPIX RAM bank setb spix_busy ;set the bit indicating that ;SPIX started data transfer mov spix_shift_counter,#$08 ;set number of shifts spix_send_loop ;CLK_HIGH clrb spix_clk_pin ;set CLK_LOW movb spix_out_pin,spix_data_io.7 ;shift data out. CLK_LOW rl spix_data_io ;CLK_LOW mov spix_temp,#spix_rate ;transfer rate delay spix_loop2 djnz spix_temp,spix_loop2 ;CLK_LOW setb spix_clk_pin ;set CLK - HIGH mov spix_temp,#spix_rate ;transfer rate delay spix_loop3 djnz spix_temp,spix_loop3 ;CLK- HIGH djnz spix_shift_counter,spix_send_loop ;check the bit counter clrb spix_busy ;exit if done setb spix_out_pin ret ;get the byte spix_get bank mmc_spix_ram ;select SPIX RAM bank setb spix_busy ;prepare to start mov spix_data_io,#$ff ;preset all bits high STC ;including carry bit mov spix_shift_counter,#$08 ;set number of shifts spix_get_loop ;CLK_High clrb spix_clk_pin ;set CLK_LOW rl spix_data_io ;CLK_LOW IF sx_freq_factor>1 ;100 MHZ? mov spix_temp,#spix_rate ;transfer rate delay spix_loop6 djnz spix_temp,spix_loop6 ; while CLK_LOW ENDIF SB spix_in_pin ;if new bit=1, then do nothing CLRB spix_data_io.0 ; otherwise, clear it accordingly setb spix_clk_pin ;set CLK_HIGH IF sx_freq_factor>1 ;100 MHZ? mov spix_temp,#spix_rate ;transfer rate delay spix_loop8 djnz spix_temp,spix_loop8 ;while CLK_High ENDIF djnz spix_shift_counter,spix_get_loop;check the bit counter setb spix_out_pin ;exit if done clrb spix_busy ret ;End of SPIX VP ;*********************** ; ;*** SPIX port initialization ; spix_init setb spix_clk_pin setb spix_out_pin setb spix_cs_pin RET ;*** Set MMC data address = 0 zero_MMC_addr CLR mmc_addr_b3 ;set the block address to read (hi byte first) CLR mmc_addr_b2 ; " CLR mmc_addr_b1 ; " CLR mmc_addr_b0 ; (lo byte last: always = 0 since 512 bytes/block) RET ;*********************** MMC COMMAND INTERPRETER ********************** ; ;FUNCTIONS are not MMC card commands, but sequences of the commands. ;The MMC VP currently implements four separate FUNCTIONS ; - synchronize ; - initialize ; - read the data block ; - write the data block mmc_synchronize equ $FF ;send 80 SPI_clk signals for initial synchronization mmc_initialize equ $FE ;card initialization procedure ; flow chart (exept for synchronization) mmc_block_read_command equ $FD ;Complete implementation of the block read flow chart ;Send the Read Block Command and set the ;mmc_read_write_data flag in the MMC_STATUS byte ;The MMC /CS line is left active (LOW) until the data ;are read. Get the data block from MMC and ;finishes the read block cycle by setting MMC /CS mmc_block_write_command equ $FA ;complete implementation of the block writing ; ;MMC COMMANDS. ;Implemented MMC commands are used as FUNCTION calls ;Other commands listed here (but currently unimplemented) are presented ; mainly for reference. These commands are described in detail in the MMC manual. mmc_go_idle_state equ $40 ;CMD0 ;these three command are used as a part mmc_send_op_cond equ $41 ;CMD1 ;of INITIALIZE function mmc_set_blocklen equ $50 ;CMD16 mmc_read_single_block equ $51 ;CMD17 mmc_write_block equ $58 ;CMD24 ;----------------------- ;MMC commands currently NOT implemented: ;mmc_send_status equ $4d ;CMD13 assuming that status data come in the ;R2 bytes ;mmc_send_csd equ $49 ;CMD9 ;mmc_send_cid equ $4a ;CMD10 ;mmc_program_csd equ $5b ;CMD27 ;mmc_set_write_prot equ $5c ;CMD28 ;mmc_clr_write_prot equ $5d ;CMD29 ;mmc_send_write_prot equ $5e ;CMD30 ;mmc_tag_sector_start equ $60 ;CMD32 ;mmc_tag_sector_end equ $61 ;CMD33 ;mmc_untag_sector equ $62 ;CMD34 ;mmc_tag_erase_group_start equ $63 ;CMD35 ;mmc_tag_erase_group_end equ $64 ;CMD36 ;mmc_untag_erase_group equ $65 ;CMD37 ;mmc_erase eque $66 ;CMD38 ;mmc_crc_on equ $67 ;CMD59 ;******************** MMC Subroutines ********************************* ; ;*** MMC Wait ;Sometimes a delay is needed for internal MMC processes mmc_long_wait MOV W,#$FF ;longest delay mmc_wait MOV mmc_temp1,W ;selectable delay (loaded in W prior to call) mloop49 mov mmc_temp,#$FF ;set wait cycles counter mloop69 djnz mmc_temp,mloop69 ;inner delay loop djnz mmc_temp1,mloop49 ;outer delay loop ret ;exit ;*** MMC Send "DUMMY" Bytes ;This subroutine generates a number of DUMMY byte transfer cycles on the SPI bus. ;The number of cycles should be specified in MMC_TEMP prior to the call. ;These dummy cycles are required by the MMC card data transfer protocol. ; mmc_delay bank mmc_spix_ram call spix_get djnz mmc_temp,mmc_delay ret ;*** MMC Send Command ;This Subroutine sends a 6 byte MMC command string starting with the MMC_CMD byte ;and finishing by CRC byte ; mmc_cmd_send bank mmc_spix_ram ;select SPIX RAM bank mov mmc_temp,#mmc_cmd mmc_loop2 mov fsr,mmc_temp mov w,ind ;load next COMMAND byte to ;the SPIX I/O buffer using index addressing mode mov spix_data_io,w call spix_send ;send the byte inc mmc_temp cjne mmc_temp,#(mmc_cmd + 6),mmc_loop2 setb spix_out_pin ;loop until all six bytes sent ret ;*** MMC Get Response R1 ;Get the response byte from the MMC. Wait for the response R1 for x=mmc_r1_wait_cycles ;byte cycles. If the R1 is not recieved or R1 is not $00, set the error flag. ;Number of wait cycles is recommended to be 2, but here we use 32 for safety. ;The routine can return two errors: (1) no response at all, (2) non zero response ; mmc_r1_get bank mmc_spix_ram ;select the RAM bank mov mmc_r1,#$ff ;initialize the byte to FF mov mmc_temp,#resp_r1_delay ;set delay counter mmc_loop3 call spix_get ;read the byte cjne spix_data_io,#$FF,mmc_loop4 ;if the byte is "FF" then repeate ;mmc_r1_wait_cycles times djnz mmc_temp,mmc_loop3 setb mmc_no_response ;no response ret mmc_loop4 test spix_data_io ;test if not zero sz setb mmc_error ;set an error flag mov mmc_r1,spix_data_io ret ;******************** MMC Command Function Interpreter ******************* ;This is the MMC command decoder subroutine. This is an optional structure ;The actual commands can be executed separately. The use of this structure ;is to reduce the number of subroutines (i.e. CALLs) and replace them by JMPs ; mmc_execute bank mmc_spix_ram cje mmc_cmd,#mmc_block_read_command,mmc_cmd_block_read cje mmc_cmd,#mmc_block_write_command,mmc_cmd_block_write cje mmc_cmd,#mmc_synchronize,mmc_cmd_synchronize cje mmc_cmd,#mmc_initialize,mmc_cmd_initialize setb mmc_wrong_command mmc_exit ret ;****************************** MMC Functions **************************** ;*** Read Data Block (Function $51) ;upon the reception of this command the MMC will start to access the data block. ;the data will be ready within 1.5 msec ; mmc_cmd_block_read bank mmc_spix_ram ;Select the RAM Bank clrb spix_cs_pin ;set MMC_CS active (LOW) ; mov mmc_temp,#blk_rd_delay1 ;do a DUMMY read cycle delay ; call mmc_delay ; clr mmc_status :do_read mov mmc_cmd,#$51 ;send the BLOCK READ Command call mmc_cmd_send call mmc_r1_get test mmc_r1 ;MMC response is not Zero, exit jnz mmc_read_exit ;******************* Continue Read Cycle, Read The Data ********************* ;Wait for the Start Byte. ;Wait time is set to (mmc_read_wait_cycles * $FF). Total wait time sould be 1.5ms+. mmc_read_data_block bank mmc_spix_ram ;select the RAM bank setb mmc_read_write_data ;await data start byte = $FE mov mmc_temp1,#blk_rd_wait ;load delay value mmc_label40 mov mmc_temp,#$FF ;set wait counter mmc_label41 call spix_get ;wait for data start byte = $FE cje spix_data_io,#$fe,mmc_label42 ;End waiting if Start Byte cjne spix_data_io,#$ff,mmc_label44 ;End waiting if Error Message djnz mmc_temp,mmc_label41 ;inner wait loop djnz mmc_temp1,mmc_label40 ;outer wait loop setb mmc_no_data ;waiting time expiered - error jmp mmc_read_exit ;exit mmc_label44 mov mmc_r2,spix_data_io ;Error message is in R2 setb mmc_data_error ;MMC sent the Data Error Token jmp mmc_read_exit ;the token will be placed in MMC_R2 ;Read MMC Data (if no errors occurred): ;This routine should be used as an example only. It transfers a block of data from MMC card ;placing the data bytes in the data storage buffer. Since the buffer is smaller than the MMC ;block size (i.e. data not being streamed), the 512 bytes coming from the MMC will ;repeatedly overwrite the buffer locations with the data steaming from MMC card. ;At the end of the cycle the last 16 (32) bytes of 512 MMC data block will be located ;in the SX data buffer mmc_label42 mov mmc_temp2,#mmc_blk_size/mmc_buffsize ;set number of cycles mmc_label43 mov mmc_temp,#mmc_buffsize ;set the byte counter and IF chip_type=0 ;SX18/28 MOV W,#buff_size*2+mmc_data_ram-1 ;last address ELSE ;SX52 MOV W,#mmc_data_ram+mmc_buffsize-1 ;last address ENDIF mov mmc_data_pointer,W ;data pointer for incoming data :mmc_read_byte call spix_get ;data read loop ;store incoming bytes into the data (circular) buffer INC mmc_data_pointer IF chip_type=0 ;SX18/28 MOV W,#buff_size*2+mmc_data_ram ;last address ELSE ;SX52 MOV W,#mmc_data_ram+mmc_buffsize ;last address ENDIF MOV W,mmc_data_pointer-W ;test for end of buffer MOV W,#mmc_data_ram ;pre-load new offset in case SNZ ;if not at end, skip ahead MOV mmc_data_pointer,W ;reset to start of buffer IF chip_type=0 MOV W,#$10 ;keep to odd banks for SX18/28 OR mmc_data_pointer,W ; " ENDIF :wait_buff_space MOV W,next_samp_ptr ;load output pointer MOV W,mmc_data_pointer-W ;and check if buffer full SNZ ;if not, skip ahead JMP :wait_buff_space ;wait till there's room mov mmc_temp_data,spix_data_io ;move data to global storage mov fsr,mmc_data_pointer ;use index register and W mov w,mmc_temp_data ;to move the date from SPIX temp data reg. mov ind,w ; to MMC data buffer BANK mmc_spix_ram ;reset to variables bank CLRB FSR.7 ; and make sure we're in lower 128reg. block djnz mmc_temp,:mmc_read_byte ;decrement byte counter djnz mmc_temp2,mmc_label43 ;decrement block counter call spix_get ;"read" two bytes CRC call spix_get ;the CRC is not implemented and thus the data are not used mmc_read_exit call spix_get ;DUMMY read cycle ; call spix_get ;DUMMY read cycle clrb mmc_read_write_data ;end the transfer and exit setb spix_cs_pin ;set MMC to inactive state jmp mmc_exit ;done ;******************* Send CMD24 ($58) (WRITE BLOCK) to MMC ********************* ;this is the first part of the BLOCK WRITE sequence - the command itself and the R1 ;response from the MMC mmc_cmd_block_write bank mmc_spix_ram ;select the RAM bank clr mmc_status ;clear the Status byte clrb spix_cs_pin ;set MMC_CS active (LOW) ;execute CMD16 :set_block_length mov mmc_temp,#$10 ;fixed delay call mmc_delay call spix_get ;"DUMMY" byte mov mmc_cmd,#$58 ;send the command call mmc_cmd_send call mmc_r1_get ;get the response call spix_get ;"DUMMY" byte test mmc_r1 ;if response was 00 then start jz mmc_write_data_block jmp mmc_write_exit ;end the transfer and exit ;*** WRITE CYCLE: Write the data block to MMC ;Send the Start Byte=$FE, wait for response (R1 type) ;Wait time= (mmc_write_wait_cycles * $FF). Total wait time should be =>1.5ms ; mmc_write_data_block call spix_get mov spix_data_io,#$fe ;send the start byte $FE call spix_send ;send the 512 data bytes the from the SX write data buffer. The buffer can be 16 or 32 bytes ;long. ;In a real wold when the buffer is empty, the program should wait untill the MAIN fills the buffer ;and returns to the black transfer again ;This program just sends the incrementing counter to the the MMC card ;It is intended to demonstrate the timing and the logic of the data transfer ;This part of the program heavily depends on the higher level program artichecture ; clr mmc_temp_data ;This is temp location for the Demo mov mmc_temp1,#mmc_blk_size/mmc_buffsize mmc_label38 mov mmc_temp,#mmc_buffsize ;set the byte counter and mov mmc_data_pointer,#mmc_data_ram ;data pointer for the data mmc_label39 ;this part of the program was tested and it works, but is not used for this demo ; mov fsr,mmc_data_pointer ;move the byte from MMC_DATA_RAM ; mov w,ind ;to MMC_SPIX_RAM using global ; mov mmc_temp_data,w ;location at $08 - MMC_TEMP_DATA ; bank mmc_spix_ram ; mov spix_data_io,mmc_temp_data ;this is just for the Demo - write incrementing values to MMC offset addresses bank mmc_spix_ram ;switch to spix control ram bank mov spix_data_io,mmc_temp_data ;Increment the counter and sent it to MMC card INC mmc_temp_data ;write increading values: DEMO only call spix_send ;send the byte inc mmc_data_pointer ;point to next data address or mmc_data_pointer,#$10 ;keep bank address in %xxx1000 range djnz mmc_temp,mmc_label39 ;decrement byte counter djnz mmc_temp1,mmc_label38 ;decrement SX RAM blocks counter call spix_get ;read the two byte "CRC" call spix_get ; " call mmc_r1_get ;get the response on the data block call spix_get ;the R1 in this case is not a typical one clrb mmc_error ;error detection in MMC_GET_R1 is not and mmc_r1,#$0f ;applicable cje mmc_r1,#$05,mmc_label37 jmp mmc_write_error ;error in the data - exit ;continue BLOCK WRITE dummy read cycles until MMC's BUSY signal is clear mmc_label37 setb mmc_busy ;set wait cycles counter mov mmc_temp1,#blk_wr_delay mmc_label36 mov mmc_temp,#$FF mmc_label35 call spix_get jb spix_in_pin,mmc_write_done ;wait for the BUSY signal to clear djnz mmc_temp,mmc_label35 djnz mmc_temp1,mmc_label36 jmp mmc_write_error ;error exit - time expired mmc_write_done clr mmc_status ;no-error exit jmp mmc_write_exit mmc_write_error setb mmc_error ;exit on error setb mmc_data_error mmc_write_exit call spix_get ;DUMMY read cycle clrb mmc_read_write_data setb spix_cs_pin jmp mmc_exit ;*** MMC Synchronization ;send $FF data to the MMC 10 times. Only called after power-up ; mmc_cmd_synchronize bank mmc_spix_ram ;select the RAM bank CALL spix_init ;initialize SPI I/O pins clr mmc_status ;initialize the MMC driver clr mmc_r1 clr mmc_r2 mov mmc_temp,#sync_duration ;get n bytes as a delay mmc_lable1 setb spix_out_pin ;in case of non-zero response from MMC call spix_get cjne spix_data_io,#$ff,mmc_lable2 djnz mmc_temp,mmc_lable1 mmc_lable2 mov mmc_r1,spix_data_io call spix_get ;DUMMY read cycle jmp mmc_exit ;*** MMC Initialization ;This function executes CMD0 and CMD1 with corresponding R1 MMC response detection ; mmc_cmd_initialize clrb spix_cs_pin ;set MCC_CS active (low) bank mmc_spix_ram ;init all the variables clr mmc_status ;clear the status byte CALL zero_MMC_addr ;set MMC data address to 0 mov mmc_cmd_crc,#$FF ;execute the CMDO command, exit if R1 is not equal to $01 mov mmc_temp,#$08 call mmc_delay ;execute 8 DUMMY cycles mov mmc_cmd,#$40 ;execute CMD0 call mmc_cmd_send call mmc_r1_get ;get a response byte back mov mmc_temp,#$10 call mmc_delay ;execute 16 DUMMY cycles cjne mmc_r1,#$01,mmc_label14 ;correct R1 is equal to #$01 ;The above code segment seems to go against MMC specs. The MMC isn't supposed to give ; a $00 response on this command but it seems to if we try to repeat it. ;The correct (from the manual point of view) sequence should look like following, ; (but it does not work): ; cje mmc_r1,#$01,mmc_label15 ;correct R1 is equal to #$01 ; setb mmc_error ;if not - set the error flag ; jmp mmc_label14 ;and exit ;execute the CMD1 command until R1==00 or MMC_CMD1_WAIT times mmc_label15 mov mmc_temp2,#cmd1_resp_wait ;load wait duration for response mmc_label13 clr mmc_status ;reset error status mov mmc_temp,#cmd1_delay1 ;send n (=8?) DUMMY bytes call mmc_delay mov mmc_cmd,#$41 ;send CMD1 code call mmc_cmd_send call mmc_r1_get ;get the response mov mmc_temp,#cmd1_delay2 ;load delay call mmc_delay ;send n (=16?) DUMMY bytes MOV W,#cmd1_delay3 ;load delay value call mmc_wait ;wait for some time test mmc_r1 ;check for response jz mmc_label14 ;correct R1 is equal to #$00 djnz mmc_temp2,mmc_label13 ;if not - repeat mmc_cmd1_wait times mmc_label14 setb spix_cs_pin ;set MMC_CS to inactive (HIGH) jmp mmc_exit ;exit ;=========================================================================== ; ;*************************** Main Program Code ***************************** ; ;******** ;* Main * ;******** ; ; ORG 100h ; Reset_entry IF chip_type=1 ;SX52 MOV FSR,#$0A ;load first offset ELSE ;SX52 CLR FSR ;point to beginning of RAM ENDIF :zero_ram IF chip_type=0 SB FSR.4 ;are we on low half of bank? SETB FSR.3 ;If so, don't touch regs 0-7 ENDIF CLR IND ;clear using indirect addressing IJNZ FSR,:zero_ram ;repeat until done :setup_regs MOV RA,#RA_init ;initialize port RA MOV !RA,#RA_IO ;Set RA in/out directions MOV RB,#RB_init ;initialize port RB MOV !RB,#RB_io ;Set RB in/out directions MOV RC,#RC_init ;initialize port RC MOV !RC,#RC_io ;Set RC in/out directions MOV !OPTION,#option_init ;initialize OPTION reg. :initialize BANK analog ;switch to adc/pwm/timer bank MOV W,#pwm0_init ;get initial pwm0 voltage MOV pwm0,W ; and store it MOV W,#pwm1_init ;get initial pwm0 voltage MOV pwm1,W ; and store it MOV W,#samp_freq&$FF ;keep low byte of sample rate MOV freq_low,W ;store it MOV W,#samp_freq>>8 ;keep high byte of sample rate MOV freq_high,W ;store it IF chip_type=0 ;SX18/28 MOV W,#buff_size*2+mmc_data_ram-2 ;last address (-2 to keep stereo syncing) ELSE ;SX52 MOV W,#mmc_data_ram+mmc_buffsize-2 ;last address (-2 to keep stereo syncing) ENDIF MOV next_samp_ptr,W ;set sample pointer to start CALL spix_init ;SPIX port pin default states CALL zero_MMC_addr ;reset MMC data address pointers ; ;************** Main program loop Mainloop :sync bank mmc_spix_ram mov mmc_cmd,#$ff ;execute the SYNCHRONIZE function call mmc_execute :init mov mmc_cmd,#$fe ;execute the INITIALIZE function call mmc_execute test mmc_status jnz :sync ;repeat in case of syncronization/initialization error :write mov mmc_cmd,#$FA ;execute the 512 byte block write command ; call mmc_execute ;uncomment this to write the block test mmc_status ;check how write procedure went sz JMP :error ;exit if we got an error writing data block :read_init CALL zero_MMC_addr ;reset MMC data address pointer => 0 :read_loop mov mmc_cmd,#$FD ;execute the block read command call mmc_execute test mmc_status ;check how read procedure went SZ ; JMP :error ;exit if we got an error reading data block INC mmc_addr_b1 ;count through multiple blocks INCSZ mmc_addr_b1 ; (b1=b1+2 => advance 512 bytes at a time) JMP :read_loop ;keep reading IF MMC_size<16 INC mmc_addr_b2 ;continue through multiple blocks MOV W,#end_of_mem ;load end of storage memory (or sample size) MOV W,mmc_addr_b2-W ; and see if we're there yet ELSE ; for MMC cards >16Meg INCSZ mmc_addr_b2 ;continue through multiple blocks JMP :read_loop ;keep reading INC mmc_addr_b3 ;continue through multiple blocks MOV W,#end_of_mem ;load end of storage memory (or sample size) MOV W,mmc_addr_b3-W ; and see if we're there yet ENDIF SZ ;if so, skip ahead JMP :read_loop ;otherwise, keep looping :done_read JMP :read_init ;run through the whole read again :error JMP MainLoop ;in case of read/write error, re-synchronize ; ;*********************************************** END
file: /Techref/SCENIX/contest/mmc/sx52mmc.src, 38KB, , updated: 2000/11/10 15:24, local time: 2024/11/12 11:45,
3.133.137.53:LOG IN ©2024 PLEASE DON'T RIP! THIS SITE CLOSES OCT 28, 2024 SO LONG AND THANKS FOR ALL THE FISH!
|
©2024 These pages are served without commercial sponsorship. (No popup ads, etc...).Bandwidth abuse increases hosting cost forcing sponsorship or shutdown. This server aggressively defends against automated copying for any reason including offline viewing, duplication, etc... Please respect this requirement and DO NOT RIP THIS SITE. Questions? <A HREF="http://sxlist.com/TECHREF/SCENIX/contest/mmc/sx52mmc.src"> SCENIX contest mmc sx52mmc</A> |
Did you find what you needed? |
Welcome to sxlist.com!sales, advertizing, & kind contributors just like you! Please don't rip/copy (here's why Copies of the site on CD are available at minimal cost. |
Welcome to sxlist.com! |
.