Hi Guys
had need to review the SPI flash routines to incorporate the 4kb/32kb/64kb erase support and other features offered by the WINBOND series of flash chips

this is a re- vamp of the code i did last year and i posted for the 8mb chip to support another flash chip manufacture

hope you find it of use and dont have to re do the code wheel - again
this should be as an include to your main code

regards

Sheldon

Code:
'*          : All Rights Reserved                                                        *
'*  Date    : 4/05/2015                                                                 *
'*  Version : 2.0                                                                        *
'*  Notes   : Rewriten for Winbond SPI W25Q series Serial NOR Flash chips ..             *
'*          :  W25Q32 - 32Mbit(4MB)                                                      *
'*          : --- Orginal code (V1.1) based on support for M25P80 8Mbit chip or simular  *
'*          :  no support of duel / quad SPI & QPI options                               *
'*          :  No support for Fast Write ( W25Q80 )                                      *
'*          :  NO support of Suspend write/read operations                               *
'*          : chips are 3.3v - NOT 5V input tollerant                                    *
'*          : Code supports .....                                                        *
'*          : 1  Software Protection of data , hardware WP and Hold pins high            *
'*          : 2. 4KB sectors , 32/64KB blocks, for protection / erasing, copy commnads   * 
'*          : 3. Manufacture ID /Chip size detection / selection for number of blocks    *  
'*          : 4. Copy commands reseved use of scratch pad area of Block 0                *
'*       : code does not need Longs to be enabled to save on code space                  *
'*****************************************************************************************
'                                                                                        *
' Operational Notes on Timing Max and Min times                                          *
' =============================================                                          *
'                                                                                        *
'   1. powerup delay to CE & WR = 5ms min                                                *
'   2. 256 bytes max per read / write                                                    *
'   3. spi bus (mode 3) (clock idle High) and flash CE configures in main program        *
'   4. avg is 20ma during write /25ma for erase, 15ma for read                           *
'   5. min 50ns  on CE deselect                                                          *
'   6. SPI chip interface timing has min of 5ns requirements , so no timing issues       *
'       for picbasic which has a min of 2us using shiftout cmd                           *
'   7. software reset via spi = min 30us - BUSY & SUS bits are checked before issue      *
'   8. sector erase (4KB)= min 45mS  max 400ms,                                          *
'   9. block Erace(32KB) = min 120ms max 1.6sec                                          *
'  10. Block Erase (64KB)= min 150ms max 2.0sec                                          *
'  11. Chip Erase(32Mbit)=min 10sec max 50sec                                            *
'  12. hold/reset pin - factory dephalt is hold                                          *
'  13. WP pin is not active - SRP1=0 , SRP0 =0 - FACTORY DEPHALT                         *
'  14. 25QxxIQ has QE bit in register 2 = 1 from factory and cannot be cleared           *  
'----------------------------------------------------------------------------------------*


 '---------- Winbond SPI FLASH (W25Q series) commands set --------------------------------
 ' NOTE: No support for DUAL/QUAD/ QPI instruction sets 
 ' 
 '             SDC_cmd, SDC_CmdCode
 ' command 1-13 use the Write enable command ---
 Flash_Wr_reg1        con 1  ' $01       'def write the Status Register 1(S7-S0)   - 1 byte data - write enable req prior
 Flash_Wr_reg2        con 2  ' $31       'def write the Status Register 2(S15-S8)  - 1 byte data - write enable req prior
 Flash_Wr_reg3        con 3  ' $11       'def write the Status Register 3(S23-S16) - 1 byte data - write enable req prior
 Flash_WR             con 4  ' $02       'def Page Program mode command        ( 24bit address req)+ (1 byte data)- write enable req prior
 Flash_Wr_Secreg      con 5  ' $42       'def Program Security Register write  ( 24bit address req)+ (1 byte data)- write enable req prior  - holds access upto 256byte data per register  
 Flash_Sec_Ers        con 6  ' $20       'def Sector Erase command (4KB)       ( 24bit address req)               - write enable req prior
 Flash_Blk32_Ers      con 7  ' $52       'def Block 32KB Erase Command (32KB)  ( 24bit address req)               - write enable req prior
 Flash_Blk64_Ers      con 8  ' $D8       'def Block 64KB Erase Command (64KB)  ( 24bit address req)               - write enable req prior
 Flash_Indv_Blk_LCK   CON 9  ' $36       'def Indervidual Block/Sector Lock    ( 24bit address req): WEP must be 1 to setup and use  - write enable req prior
 Flash_Indv_Blk_UNLCK CON 10 ' $39       'def Indervidual Block/Sector UNLock  ( 24bit address req): WEP must be 1 to setup and use  - write enable req prior
 Flash_Secreg_Ers     con 11 ' $44       'def Erase Program Security Register  ( 24bit address req) - write enable req prior
 Flash_Bulk_Ers       con 12 ' $C7       'def Bulk Erase command                 - write enable req prior
 Flash_Globe_LCK      con 13 ' $7E       'def Globel Block /Sector Lock      : WEP must be 1 to setup and use   - write enable req prior
 Flash_Globe_UNLCK    con 14 ' $98       'def Globle Block/Sector Unlock     : WEP must be 1 to setup and use   - write enable req prior
 

 ' commands 14-12 use the Read command --- 
 Flash_RD             con 15 ' $03       'def read data at normal speed        ( 24bit address req)+ (1 byte data)
 Flash_Rd_HS          con 16 ' $0B       'def read data at High speed (Fast Read) ( 24bit address req)+ (1dummy+1 byte data)
 Flash_Rd_Secreg      con 17 ' $48       'def Program Security Register read  ( 24bit address req)+ (1 dummy +1 data)( simular to fast read command )
 Flash_Rd_Sig         con 18 ' $4B       'def read Flash device Unique ID signature - cmd + 4 dummy bytes , returns 64bit ID MSB first
 Flash_Rd_Blk_LCK     con 19 ' $3D       'def Read Block/Sector Lock status  , returns 0= unlocked 1= Locked ( 24bit address req)+ (1 byte data)
 Flash_Rd_ID          con 20 ' $9F       'def Read manufacture 1byte/device/UID code 2 bytes ( JEDEC ID) - returns 3 bytes 
 Flash_Rd_reg2        con 21 ' $35       'def read the Status Register 2(S15-S8)  - returns 1 data byte 
 Flash_Rd_reg3        con 22 ' $15       'def read the Status Register 3(S23-S16) - returns 1 data byte 

 '---- not in command lookup table - used directly -----
 Flash_Wr_dis      CON $04        'def write disable command 
 Flash_Rd_reg1     con $05        'def read the Status Register 1(S7-S0)  - done by Bsy_chk routine
 Flash_Wr_en       con $06        'def write Enable command   
 Flash_Vol_Wr_EN   con $50        'def  Volatile SR Write Enable - used to change write_reg1 bits but wont set WEL flag - quick way of changeing register for protection bits ( no write enable 
 Flash_EN_Rst      con $66        'def Enable Software Reset  - reset takes min 30us 
 Flash_Rst         Con $99        'def Do a Reset  - Must be combined with Flash_EN_Rst
 Flash_PWR_Dwn     con $B9        'def Deep Power Down command   
 Flash_PWR_Up      con $AB        'def Release From Deep Power Down command  
 
' ----------  FLASH varables -------------------------

 Data_Length    var byte       ' table of data length
 SDC_buffer	    Var Byte[256]  ' indexed data - max 256 bytes - 8mb FLASH has a 256 Limit from page Writes - Note 512 used in SD routines 
 SDC_data_in    Var Byte       ' Data in byte from flash 
 SDC_data_out   Var Byte       ' Data out byte from Flash - 
 SDC_address_High   Var word   ' address higher word sent to FLASH 
 SDC_address_Low    Var word   ' address lower  word sent to FLASH 
 SDC_index	    Var Word       ' Loop index counter 
 SDC_CmdCode    Var Byte       ' used here as Sector protect value for the Write Status register 
 SDC_cmd	    Var Byte       ' command code for selected operation 
 SDC_Block      var Byte       ' 64K block Address   - uses SDC_address_High.low , each block 0-63(32Kbit) 0-127(64Kbit), addressing used both 
 SDC_Sector     var byte       ' 4K Sector address   - uses SDC_address_Low.highbyte , each sector = 16 pages , so sector 0 = page 0-15  - values = 0 -15
 SDC_Page       var byte       ' Page Address
 SDC_Byte       Var byte       ' Bytes Address
 Flash_RD_Fast  var bit        ' Flag for High speed read 1 = Highspeed read speed 0= normal read speed 
 Flash_Install  var bit        ' flag set when flash install program used  
 Flash_32KB_Block_Sel  var bit ' Sets StartPage address for 32KB Block erase - 0 = lower block - sets start page address - page 0 - 127, 1 = High block - page 128 - 256
 Flash_Protect  var bit        ' Set Protect =1 / Unprotect =0 of a block , used as a read of block status as well
 
 Flash_Blk_Orgin    var byte  ' Orgin sector value     - copy sector command 
 Flash_Blk_Dest     var byte  ' destination  sector value  - copy Sector Command   
 Flash_Sec_Orgin    var byte  ' Orgin sector value     - copy sector command 
 Flash_Sec_Dest     var byte  ' destination  sector value  - copy Sector Command  
 Flash_Page_Orgin   var byte  ' Orgin Page value
 Flash_Page_Dest    var Byte  ' Dest Page Value 
 Flash_Page_Length  var byte  ' number of pages 
 Flash_Clear         var bit  ' flag to clear orginal sector 1= clear  
 
 Flash_Manf_id   var byte    ' manufacture id code 
 Flash_Manf_type var byte    ' device type code 
 Flash_Manf_cap  var byte    ' device capacity code 
 Flash_tmp       var byte    ' used as a temp varable 
 Flash_tmp2      VAR BYTE    ' used as a temp varable  
 Flash_Reg_val   var byte    ' Flash register value 

 Flash_Addr_Copy_Low  var word  ' low word temp storage of input address and data length 
 Flash_Addr_Copy_High var word  ' high word temp storage of input address and data length


'----------- Varable settings at startup ---------------------------------------------

   Flash_RD_Fast = 0        ' Set to normal read at start
   Flash_Install = 0        ' set to 0 when flash  install not being used  
   Flash_Clear = 0          ' set not to clear 
   Flash_32KB_Block_Sel = 0 ' set to use low address 
  
'---------------- Routines  ------------------ 
goto JumpOverSPIFLASH     ' Jump to end of this include file  for Correct compile  
 
  Flash_Init:
    ' do a read register command to clear the Flash register after power up
  
         FLASH_CE = 0                                  ' Bring the FLASH chip select line low  
          SDC_data_out = Flash_Rd_reg1                 ' Send the read status register command byte
 	      Gosub Flash_spiw	                           ' Write Byte SDC_data_out. , subroutine writes a byte on the SPI bus 
         FLASH_CE = 1                                  ' Bring the FLASH chip select line high  
         gosub buffer_clear                            ' clear varables area 
      
  return                                                        
' -----------------------------
  Buffer_Clear:
 
      For SDC_index = 0 To 255
          SDC_buffer[SDC_index] = 0
      next SDC_index
  return

'--------------------------------------- 
  Flash_Reset:
  ' routine to software reset the flash 
  ' enable reset and reset must be consecutive 
   
    FLASH_CE = 0                                  ' Bring the FLASH chip select line low  
      SDC_data_out = Flash_EN_Rst                 ' Send Enable Reset command 
      gosub Flash_spiw	                          ' Write Byte SDC_data_out. , subroutine writes a byte on the SPI bus 
      SDC_data_out = Flash_Rst                    ' Send Reset command 
   	  Gosub Flash_spiw	                          ' Write Byte SDC_data_out. , subroutine writes a byte on the SPI bus  
    FLASH_CE = 1                                  ' Bring the FLASH chip select line high  
     
  return

'-----------------------------------------

 Flash_Format:
 'Note wont work if any sectors are protected 
  ' can take upto 50sec on 32mbit chip 
   sdc_cmd = Flash_Bulk_ers  ' excutes as it sounds
   gosub Flash_Comand 
 return
 
'-------------------------------------------------
 
 Flash_Sec_Erase: 
  ' assumes Block address  0-63 
  ' assumes Sector value 0 -15 
  ' erases 1 Sector at a time  address (4KB)= 15 pages 
  ' Erases wont work on sectors that are write protected 
  ' sector erase take 400ms per instruction 
   SDC_pAGE = 0                          ' ensure 0 
   SDC_pAGE = sdc_SECTOR << 4            ' shift given sector 0-15 to upper page value   
  
   sdc_cmd = Flash_Sec_Ers               ' Erases  sector ( 256 pages x 256 bytes ) 
   SDC_address_high.byte0 = SDC_Block    ' set sector Address 0 to 15 for chip
   SDC_address_low.byte1  = SDC_Page     ' set page start address 0 to 255  
   SDC_address_low.byte0  = 0            ' set byte start address 0 to 255
   gosub Flash_Comand                    ' Do the command 
 return

'----------------------------------------------------

 Flash_Blk32_Erase: 
  ' assumes Block address   
  ' assumes flag 32KB_Block_Sel 0 = bottom 32Kb start address page, 1= 128page address
  ' erases 1/2 a 64KB Block at a time  address (32KB)= 128 pages 
  ' Erases wont work on sectors that are write protected 
  ' sector erase take min 120ms max 1.6Sec per instruction 
   IF Flash_32KB_Block_Sel = 0 THEN           ' select offset page for 32 byte sector 
       SDC_PAGE = 0
   ELSE
       SDC_PAGE = 128
   ENDIF    
   sdc_cmd = Flash_blk32_Ers             ' Erases 32kB block ( 128 pages of 256 bytes ) 
   SDC_address_high.byte0 = SDC_Block    ' set block Address for chip
   SDC_address_low.byte1  = SDC_PAGE     ' set page start address 0 to 255  
   SDC_address_low.byte0  = 0            ' set byte start address 0 to 255
   gosub Flash_Comand                    ' Do the command 
 return
'-------------------------------------------------------------
 
 Flash_Blk64_Erase: 
  ' assumes Block address  
  ' erases a 64KB Block at a time  address (64KB)= 256 pages 
  ' Erases wont work on sectors that are write protected 
  ' sector erase take min 160ms max 2.0Sec per instruction 
  
   sdc_cmd = Flash_blk64_Ers             ' Erases 64kB block ( 256 pages of 256 bytes ) 
   SDC_address_high.byte0 = SDC_Block    ' set Block Address for chip
   SDC_address_low.byte1  = 0            ' set page start address 0 to 255  
   SDC_address_low.byte0  = 0            ' set byte start address 0 to 255
   gosub Flash_Comand                    ' Do the command 
 return

'------------------------------------------------------------------
 
 Flash_Block_Copy:
  ' copys data from 1 block to another 
  ' erases destination block - optional clean of orginal block 
  ' assumes Flash_Sect_Orgin,Flash_Sect_Dest ,Flash_clear
  ' Erases wont work on blocks that are write protected 
  ' block erase take 400ms per instruction 
      SDC_Block  = Flash_Blk_Dest            ' clear destination block 
      gosub Flash_blk64_Erase                ' use SDC_blk64_erase info to erase destination sector 
       for SDC_PAGE = 0 to 255               ' copy pages to selected block ( 256bytes at a time) 
           SDC_Block  = Flash_blk_Orgin      ' block to copy 
           SDC_byte    = 0
           Data_Length = 255
           gosub Flash_Read                  ' read the data to buffer 
           SDC_Block  = Flash_Blk_Dest       ' block to copy to
           SDC_byte    = 0                   ' use block details for destination
           Data_Length = 255
           gosub Flash_Write                 ' write the data
       next SDC_PAGE
     if Flash_clear = 1 then 
        SDC_Block = Flash_Blk_Orgin         ' clean up orgin Block 
        gosub Flash_Blk64_Erase               
     endif
 return
     
 Flash_Page_Copy:
  ' copys data from pages 0 -255 from orgin or destination block 
  ' assumes destination block pages are Erased 
  ' assumes pages orgin and pages destination do not cross block boundrys 
  ' assumes Flash_Page_Orgin,Flash_Page_dest ,Flash_Page_length, Flash_blk_orgin ,Flash_blk_dest  
  ' writes wont work on blocks that are write protected 
      
     for  Flash_tmp2 =  Flash_Page_Orgin to Flash_Page_length    '  copy sector 0 pages to selected sector 0 ( 256bytes at a time) 
           SDC_Block  = Flash_blk_Orgin                     ' sector to copy 
           SDC_PAGE =  Flash_tmp2
           SDC_byte    = 0
           Data_Length = 255
           gosub Flash_Read                                  ' read the data to buffer 
         
           SDC_Block  = Flash_blk_Dest                       ' sector to copy to
           SDC_PAGE = Flash_Page_Dest                        ' page to copy to 
           SDC_byte    = 0                
           Data_Length = 255
           gosub Flash_Write                                 ' write the data
           Flash_Page_Dest = Flash_Page_Dest + 1              ' increment destination page 
     next Flash_tmp2
 
 
 return 
'---------------------------------------- 
 
       
 Flash_Write: 
  ' assumes data length , address and upto 256 bytes in  SDC_buffer[] to send 
  ' writes bytes from SDC_buffer[] into flash , block/page/byte loction must be "FF" at start
  ' write wont work on sectors that are write protected 
 
   sdc_cmd = Flash_WR               ' excutes as it sounds - max of 256 bytes
   SDC_address_high.byte0 = SDC_Block   ' set block Address for  chip
   SDC_address_low.byte1  = SDC_Page     ' set page start address 0 to 255  
   SDC_address_low.byte0  = SDC_byte     ' set byte start address 0 to 255
   gosub Flash_Comand 
  
  return
 
'--------------------------------------

 Flash_Read: 
  ' assumes Block, page, bytes , data length input 
  ' gets upto bytes data into SDC_buffer[] from flash 
  ' uses normal read speed if no Flash_RD_Fast flag set
   if Flash_RD_Fast = 1 then
     sdc_cmd = Flash_Rd_HS          ' excutes fast read  - max of 256 bytes 
   else
     sdc_cmd = Flash_RD             ' excutes normal read - max of 256 bytes cos of buffers size/ page size 
   endif
   SDC_address_high.byte0 = SDC_Block   ' set block Address  for chip
   SDC_address_low.byte1  = SDC_Page     ' set page start address 0 to 255  
   SDC_address_low.byte0  = SDC_byte     ' set byte start address 0 to 255
   gosub Flash_Comand
  return

 
 Flash_WR_protect:
 ' routine to protect/ unprotect a set block of 60-63 in 32kbit chip ( block 60-63 used by K9 system stored settings )
 ' Assumes Flash_Protect - 0 = unprotect 1 = Protect a sector 
 ' SETUP FOR 32kB CHIP 
 '  Bit7 = SRP0 - Set to 0 - software protect (SRP1= 0 DEPHALT(stat_reg2(bit0), not WP pin 
 ' bits6(SEC) = 0 = 64KB Block 1= 4Kb SECTOR , Bit5(TB) 0= Top, 1 = Bottom , Bit4-2 = BP2-BP0. bits 1-0 (wel, busy )
   
   
     if Flash_Protect = 0 then 
        SDC_buffer[0] = $00 ' clear all blocks
     else
        SDC_buffer[0] = $0C ' set blocks 60-63 protected for K9 project 
     endif 
  
      sdc_cmd = Flash_Wr_reg1  ' write register 
      data_length = 1          ' set 1 byte  
      gosub Flash_Comand 
   return

'-----------------------------------------------------------
   Flash_WR_Disable:
   ' reset the write enable latch 
      FLASH_CE = 0                                ' Bring the FLASH chip select line low  
        SDC_data_out = Flash_Rd_reg1                 ' Send the read status register command byte
 	    Gosub Flash_spiw	                        ' Write Byte SDC_data_out. , subroutine writes a byte on the SPI bus 
       FLASH_CE = 1                               ' Bring the FLASH chip select line high  
   return
'----------------------------------------------------
  Flash_Read_ID:
  ' returns JEDEC ID-  returns Manufacture ID byte($EF), mem type - (ID15-ID8)1byte ,capacity(ID7-ID0)1byte)   
      
    sdc_cmd =  Flash_Rd_ID              ' Flash Read ID 
    data_length = 3                     ' 3 bytes  
    gosub Flash_Comand
    Flash_Manf_id =  SDC_buffer[0]
    Flash_Manf_type = SDC_buffer[1] 
    Flash_Manf_cap  = SDC_buffer[2]
    IF FLASH_Install = 1 then
       HSEROUT ["Flash Manf ID = ",hex Flash_Manf_id,"  Flash Device ID = ",hex Flash_Manf_type,"  Device Capacity ID = ",hex Flash_Manf_cap,13,10]  
     endif
  return   
'---------------------------------------------------------------------
  Flash_Read_Sig:
  ' returns the flash chips Unique ID number ( 64Bit)
    sdc_cmd = Flash_Rd_Sig               ' Flash Read Unique ID signature 
    data_length = 4                      ' 4 bytes                ' Flash Read Unique ID signature 
    gosub Flash_Comand
  return
  '----------------------------------------------
 Flash_Read_BLK_Lock:
 'routine to read block or sector locks ( WPS=1 to work )
   sdc_cmd =  Flash_Rd_Blk_LCK                          ' Flash Read block lock  
   data_length = 1                                     ' 1 bytes   
   gosub Flash_Comand
   Flash_Protect = SDC_buffer[0] & $01                  ' get bit0 value - 1 = locked .0 = unlocked  
  return
 '--------------------------------------------- 
 
  Flash_Power_Down:
 ' sEt Flash chip to low power mode from standby mode - no command other tha powerup will wake the device 
    FLASH_CE = 0                                ' Bring the FLASH chip select line low  
      SDC_data_out = Flash_PWR_Dwn              ' command to pwr down
 	  Gosub Flash_spiw	                        ' Write Byte SDC_data_out. , subroutine writes a byte on the SPI bus 
    FLASH_CE = 1                                ' Bring the FLASH chip select line high  
  return
'----------------------------  
  Flash_Power_Up:
 ' sEt Flash chip to standby mode - no command other tha powerup will wake the device 
' sEt Flash chip to low power mode from standby mode - no command other tha powerup will wake the device 
    FLASH_CE = 0                                ' Bring the FLASH chip select line low  
      SDC_data_out =  Flash_PWR_Up              ' command to pwr up
 	  Gosub Flash_spiw	                        ' Write Byte SDC_data_out. , subroutine writes a byte on the SPI bus 
    FLASH_CE = 1                                ' Bring the FLASH chip select line high  
  return
 '-----------------------------


' -----------------------------
 Flash_Read_reg2:
 ' reads write register 2 -  
 ' Register 2 controls ..... 
 ' bit7(S15)- Suspend Status 
 ' bit6(S14)CMP -Compliment Protect - dephalt CMP =0 
 ' bit5-3(S13-11)- Security Register(One time programable) dephalt = 000
 ' bit1(S9) - QE - Quad SPI Mode Enable ( default =0 when chips NOT FVIQ type)
 ' bit0(S8) - SRP1-  Protect bit1 _ dephalt =0 
 '  
   sdc_cmd =  Flash_Rd_reg2                          ' Flash Read register 2   
   data_length = 1                                   ' 1 bytes returned     
   gosub Flash_Comand
 return
 
 '---------------------------------------
 
 Flash_Read_reg3:
 ' Register 3 controls ..... 
 ' bit7(S23) - Hold(0- dephalt)/Reset(1) pin fuction  
 ' bit6,5(S22,S21)(0,0=100%),(0,1=75%),(1,0=50%),(1,1=25%- dephalt) read driver strength- used to overcome cpacitive loading ,trace impendace issues with signal at high speed reads 
 ' bits4,3 - reserved (writen as 0)
 ' Bit2(S18) WPS - selects Protection methode - Indervidual block/sectors(WPS=1) or by grouping range(WPS=0) ( WPS dephalt is 0 ) 
 ' Bits1,0-reserved(writen as 0)  
   sdc_cmd =  Flash_Rd_reg3                          ' Flash Read register 3   
   data_length = 1                                   ' 1 bytes returned     
   gosub Flash_Comand
  return
  
  '-----------------------------------
   
  Flash_Comand:
  ' assumes SDC_address long
  ' assumbe data_Length = Lookup table to fill 
  ' max 256 bytes per write 
  ' erase of the sector by byte  / bulk is needed prior to write , as a write only changes a 1 to 0 , and the erase chanse the 0 to 1 
   if  SDC_cmd = 0 then return           ' invalid command if value =0 


 
 Lookup SDC_cmd,[$00,$01,$31,$11,$02,$42,$20,$52,$D8,$36,$39,$44,$C7,$7E,$98,$03,$0B,$48,$4B,$3D,$9F,$35,$15],SDC_CmdCode ' asignes command code to flash chip  
  
      Flash_tmp = 0                        ' ensure 0 - counter for busychk loop
      gosub BSY_chk                        ' do for all commands 
         
     if SDC_cmd <=14 then                  ' do for writes, sector erase,bulk erase , write reg protect - commands 1-14 use writen enable first
        FLASH_CE = 0                       ' Bring the FLASH chip select line low.
 	    SDC_data_out = Flash_Wr_en         ' Send  command byte that requires a write 
        Gosub Flash_spiw	               ' Write Byte SDC_data_out. , subroutine writes a byte on the SPI bus
   	    FLASH_CE = 1                       ' Bring the FLASH chip select line high to complete the write command 
 	    pauseus 1                          ' pause between prev command  - may not need 
     endif
	
     FLASH_CE = 0                          ' Bring the FLASH chip select line low 
     SDC_data_out =  SDC_CmdCode           ' Send the  command byte,
   	 Gosub Flash_spiw	                   ' Write Byte SDC_data_out. , subroutine writes a byte on the SPI bus
    
     if SDC_cmd =>4 and SDC_cmd <=11 or _           ' if write commands 4-11 then use 24bit address assigned 
        SDC_cmd =>15 and SDC_cmd <=19 then          ' or read commands 15-19 then use 24bit address assigned , command 18 uses 24bit address as 3 dummy bytes 
          SDC_data_out = SDC_address_high.Byte0     ' set block Address for chip
 	      Gosub Flash_spiw		                    ' Write Byte SDC_data_out.
 	      SDC_data_out = SDC_address_low.Byte1      ' set page address 0 to 255  
 	      Gosub Flash_spiw	                        ' Write Byte SDC_data_out.
 	      SDC_data_out = SDC_address_low.Byte0      ' set byte address 0 to 255
          Gosub Flash_spiw		                    ' Write Byte SDC_data_out.
          if SDC_cmd => 16 and SDC_cmd <= 18 then   ' if read High speed mode ,Program security read , Read Unique ID(add 4th dummy byte) 
             SDC_data_out = $00                     ' add a dummy byte to command  
             Gosub Flash_spiw		                ' Write Byte SDC_data_out.
          endif
      endif
    
      if SDC_cmd <=5 or _                                ' if write commands require data bytes sent 
         SDC_cmd >=15 and SDC_cmd <= 22 then             ' or read commands require data bytes returned     
                 
          For SDC_index = 0 To Data_Length-1             ' DATA LENGTH -1  so byte 0 is counted when setting data length  
              if SDC_cmd <= 5 then                       ' if write ,Write register,write Security register then 
                 SDC_data_out = SDC_buffer[SDC_index]    ' send contents of indexed SDC_buffer 
                 gosub  Flash_SPIw  	                 ' write byte SDC_data_in from SPI bus.  Returns SDC_data_in.
              endif
            
              if SDC_cmd =>15 and SDC_cmd <=22 then      ' if read scommand returns data 
                 gosub  Flash_SPIR  	                 ' Read Byte SDC_data_in from SPI bus.  Returns SDC_data_in.
 	             SDC_buffer[SDC_index] = SDC_data_in
              endif
          Next SDC_index
      endif
      pauseus 1 
     FLASH_CE = 1                          ' Bring the FLASH chip select line high.

  return
'----------------------------------------------------
 Bsy_chk:
        FLASH_CE = 0                                ' Bring the FLASH chip select line low  
        SDC_data_out = Flash_Rd_reg1                ' Send the read status register1 command byte
 	    Gosub Flash_spiw	                        ' Write Byte SDC_data_out. , subroutine writes a byte on the SPI bus 
        Flash_tmp = 0                               ' clear counter                  
       while  Flash_tmp <150                        '  loop test read for busy ( counter may need to be increased depending on size of chip and time for block erase command to complete       
         gosub Flash_SPIR  	                        ' Read Byte SDC_data_in from SPI bus.  Returns SDC_data_in.
         IF FLASH_Install = 1 then 
           Flash_Reg_val  = SDC_data_in               ' get value of read status reg value for use in flash install program checks for protection 
           HSEROUT ["STATUS REG = ",hex Flash_Reg_val,13,10]  ' show on terminal when doing flash install 
           HSEROUT ["Flash_tmp = ",dec2 Flash_tmp,13,10]     
         endif 
         Flash_tmp = Flash_tmp + 1 
         SDC_data_in =  SDC_data_in & $01          ' mask bit 0 ( busy flag)
        if SDC_data_in = 0 then Flash_tmp = 151    ' Test bit 0 if write not busy,force exit of loop
       wend                  
       FLASH_CE = 1                                    ' Bring the FLASH chip select line high
 return  
'------------------------------- 
  Flash_SPIR:
    SO = 1			                    ' Shift out high bits while shifing in data.
 	Shiftin SO, SCK, 6,[SDC_data_in]	' MSb first, clock idle high.
  
  Return
'-------------------------------

  Flash_SPIW: 
      shiftout SI,SCK,5,[SDC_data_out]	    ' MSb first, clock idle high.
                       
  return
'------------------------





JumpOverSPIFLASH: