did some updates

this inlcude has a lot of bloat so comment it out if you not need the routines to reduce compile space
i have shown some examples of how to use the routines as i got a few MP's on it recently


remove comments as needed

Code:

'*  Date    : 24/04/2022                                                                 *
'*  Version : 2.0a                                                                        *
'*  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                  *
' ========================================================================================
' Ver 2.0a - change example - fix Bsy_chk loop error for when multi 64k errace used      *
'          - change to use flash_ce offset                                               *
'          - change include name as SPI_flash.bas                                        *
'          - make  Data_Length var a word cos of how the length input uses value of 256  *
'            for selection                                                               *
'*****************************************************************************************
'                                                                                        *
' 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                         *
' 
'----------------------------------------------------------------------------------------*
'SECTOR	PAGES REF          |   *** LATA.0 OFFSET VALUE CALCULATIONS FOR FLASH_CE ***     *
'  0	0-15               |       LATA.0[0]  - LATA.0[7]  = LATA Port pins 0-7          *
'  1	16-31              |       LATA.0[8]  - LATA.0[15] = LATB Port pins 0-7          *
'  2	32-47              |       LATA.0[16] - LATA.0[23] = LATC Port pins 0-7          *
'  3	48-63              |       LATA.0[24] - LATA.0[31] = LATD Port pins 0-7          *
'  4	64-79              |       LATA.0[32] - LATA.0[39] = LATE Port pins 0-7          *
'  5	80-95              |       LATA.0[40] - LATA.0[47] = LATF Port pins 0-7          *
'  6	96-111             |       LATA.0[48] - LATA.0[55] = LATG Port pins 0-7          *
'  7	112-127            |       LATA.0[56] - LATA.0[63] = LATH Port pins 0-7          *
'  8	128-143            |       LATA.0[64] - LATA.0[71] = LATI Port pins 0-7          *
'  9	144-159            |                                                             *
'  10	160-175            |                                                             *
'  11	176-191            |                                                             *
'  12	192 -207           |                                                             *
'  13	208-223            |                                                             *
'  14	224-239            |                                                             *
'  15	240-255            |                                                             *
'----------------------------------------------------------------------------------------*

'============== EXAMPLE OF HOW TO USE THIS INCLUDE ======================================* 
'
' a: SETUP I/O PINS FOR FLASH USE IN MAIN PROGRAM
'    SCK           VAR LATC.3       ' Clock pin (output to RF modual)
'    SO            Var PORTC.4      ' Master In   - flash chip Data out pin     
'    SI            Var LATC.5       ' Master Out  - flash chip Data in pin      
'    FLASH1_CE     con 22'= LATC.6  ' Chip select FLASH chip ( low) 
'   Note: i use an offset constant to select flash_ce, but normal var is fine 
'   offset methode used cos of multi flash chips on same spi pins and no need to change include to address them 

'   '*** NOTE: FLASH1_CE use LATA.0[LATA offset]
'    LATA.0[FLASH1_CE] = 1          ' Active Low so set High to start  
'    SI = 1                         ' Set SI to idle high to start
'    SCK = 1                        ' Set SCK to idle high to start
'   Flash_EN = FLASH1_CE            ' Set Flash1_CE at start as the Flash1 to use in var of flash include   
' 
' b:   place include statement in main code 
'     INCLUDE "modedefs.bas"              ' Required for shiftout,shiftin commands as defined symbols
'     include "SPI_Flash.bas"            ' include support of 8mbit Flash chip W25Q series 
' 
' C: examples of use 
'    most commands require the assumed variables listed in each command
'   1. example 1 - Flash_Test:  routine to erase / write / read test data for scratchpad sector 0 - test of flash chip 
'   2. example 2 - erase lower 32k of block1 
'                  SDC_Block =1   
'                  Flash_32KB_Block_Sel = 0  ' select lower 32k of block 
'                  gosub Flash_Blk32_Erase    
'   3. example 3 - read block2 pages 0-2, 256 bytes of each page to serial monitor port 
'                - refer ' EXAMPLE 3  at end of page 

 ' ////////////////////////////////////////////////////////////////////////////////////////////////////////////////////
 ' NOTE: there is a lot of bloat in this included where if you not need / use the routines they should be commented out 
 '       this also should remove unused varables they use in routines you not need 
 ' ====================================================================================================================

 '---------- Winbond SPI FLASH (W25Q series) commands set --------------------------------
 ' NOTE: No support for DUAL/QUAD/ QPI instruction sets 
 ' 
 '             SDC_cmd, SDC_CmdCode
 ' command 1-14 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 15-22 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 word       ' table of data length ( made word cos data length can be 256 so 0-255 byte = 256 total bytes
 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_Chk_Fail var bit        ' Flag result status of flash_test routine - called at startup 
 
 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_SPI_Shared   var bit    ' Flag Set (1) when SPI is a shared bus between flash and RF module 
 
 Flash_EN        var byte      ' Flash_CE pin value offset from LATA - value set in main program - allows for multi Flash chip CE from same routine 
 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  - used in busy loop counter 
 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
    ' called by gate_config routine at start 
         
         
         LATA.0[Flash_EN] = 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 
         LATA.0[Flash_EN] = 1                          ' Bring the FLASH chip select line high  
          gosub buffer_clear                           ' clear varables area 
     '    gosub Flash_Reg_Setup                         ' setup req2 and reg3 for dephalts use of the flash 32Kb  ( not needed ) 
   
    
  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 
   
    LATA.0[Flash_EN] = 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  
    LATA.0[Flash_EN] = 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
 
'-------------------------------------------------
 'SECTOR	PAGES REF
'  0    	0-15
'  1	    16-31
'  2	    32-47
'  3	    48-63
'  4	    64-79
'  5	    80-95
'  6	    96-111
'  7	    112-127
'  8	    128-143
'  9	    144-159
'  10	    160-175
'  11	    176-191
'  12	    192 -207
'  13	    208-223
'  14	    224-239
'  15	    240-255

 Flash_Sec_Erase: 
  ' assumes Block address  0-63 
  ' assumes Sector value 0 -15 
  ' erases 1 Sector at a time  address (4KB)= 16 pages - page 0 - 15 = sector 0  
  ' 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 (15 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

'------------------------------------------------------------------
 ' command routine commented out as it was not used to save space - but works ok 
 ' >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
 'Flash_Byte_Modify:
 ' assumes Event_Get_Block_Page routine has given the event block and page  
 ' assumes event selected block, event page address , event start SDC_byte , data length ( upto 256bytes )
 ' asusmes bytes changed are in the same sector and no boundry cross
 ' assumes block/sector 0 is not protected , block 0 is scrachpad 
 ' assumes selected modifed block/sector is not protected
 ' assumes buffer[0]+ (length-1)  has bytes data that is to be modfifed 
  
 ' Flash_Addr_Copy_high.byte1 =  Data_Length ' number of bytes to change  - save length in temp location 
 ' Flash_Addr_Copy_high.byte0 =  SDC_Block   ' save event block address 
 ' Flash_Addr_Copy_low.byte1  =  SDC_Page    ' save page addrees
 ' Flash_Addr_Copy_low.byte0  =  SDC_Byte    ' save start byte 
 
 ' SDC_Sector = (SDC_Page & $F0) >> 4        ' get 4k sector from page number  
 ' SDC_Block = 0                             ' set block to 0 
 ' gosub Flash_Sec_Erase                     ' erase block 0 ,4k sector of page range 
 
 ' SDC_Block = 0                             ' use sector 0,instead of given sector , but use given page, byte length  
 ' SDC_Page =  Flash_Addr_Copy_low.byte1     ' restore orgin page addrees
   
 ' sDC_Byte =  Flash_Addr_Copy_low.byte0     ' restore orgin byte start address 
    
 ' gosub Flash_write                         ' Write the changed byte data from buffer to sector 0
  
 
 ' if Flash_Addr_Copy_low.byte0 = 0 then               ' find the byte to copy - copy all bytes above 0 for given sector  
       
       
 '       Flash_Page_Orgin =1                           ' start page of orgin
 '       Flash_Page_length = 255                       ' how many pages 
 '       Flash_Sec_Orgin =  Flash_Addr_Copy_high.byte0 ' sector  
 '       Flash_Sec_Dest = 0
 '       Flash_Page_Dest = 1        
 '       gosub Flash_Page_Copy
'   endif 

'  if Flash_Addr_Copy_low.byte1 = 255 then             ' find the pages to copy - copy all pages/ bytes  below given page/ byte of sector  
'        Flash_Page_Orgin =0                           ' start page of orgin
'        Flash_Page_length = 254                       ' how many pages 
'        Flash_Sec_Orgin =  Flash_Addr_Copy_high.byte0 ' sector  
'        Flash_Sec_Dest = 0
'        Flash_Page_Dest = 0        
'        gosub Flash_Page_Copy
'   endif

'  if Flash_Addr_Copy_low.byte1 >0 and Flash_Addr_Copy_Low.byte1 < 254 then       ' find the pages to copy - copy all pages/ bytes  below given page/ byte of sector  
'        Flash_Page_Orgin =0                               ' start page of orgin
'        Flash_Page_length = Flash_Addr_Copy_low.byte1 - 1 ' how many pages 
'        Flash_Sec_Orgin =  Flash_Addr_Copy_high.byte0     ' sector  
'        Flash_Sec_Dest = 0                                ' start at same page value as orgin
'        Flash_Page_Dest = 0         
'        gosub Flash_Page_Copy
    
'        Flash_Page_Orgin = Flash_Addr_Copy_Low.byte1 + 1  ' start page of orgin
'        Flash_Page_length = 255 - Flash_Page_Orgin        ' panges to copy  = 255 - start address +1  
'        Flash_Sec_Orgin =  Flash_Addr_Copy_high.byte0     ' sector  
'        Flash_Sec_Dest = 0
'        Flash_Page_Dest = Flash_Addr_Copy_low.byte1 + 1          
'        gosub Flash_Page_Copy
'   endif
    
'  if Flash_Addr_Copy_low.byte0 + Flash_Addr_Copy_high.byte1  < 255 then   ' if the start byte + data length of the data changed is < 255 bytes , 
           ' then copy  bytes  below the selected changed data 
'         SDC_Block  = Flash_Addr_Copy_high.byte0         ' read selected sector 
'         SDC_PAGE   =  Flash_Addr_Copy_low.byte1          ' of selected page 
'         SDC_byte = 0                                     ' start address bytes 0 to  
'         Data_Length = Flash_Addr_Copy_Low.byte0 - 1      ' selected byte - 1  ( length)
'         gosub Flash_Read                                 ' read  
'         SDC_Block  = 0                                  ' use sector 0 aselected sector 
'         SDC_PAGE   =  Flash_Addr_Copy_low.byte1          ' of selected page 
'         SDC_byte = 0                                     ' start address bytes 0 to  
'         Data_Length = Flash_Addr_Copy_low.byte0 - 1      ' selected byte - 1  ( length)
'         gosub Flash_Write                                ' write  
      
          ' then copy  bytes above the selected changed data 
'         SDC_Block  = Flash_Addr_Copy_high.byte0                          ' read selected sector 
'         SDC_PAGE    = Flash_Addr_Copy_low.byte1                          ' of selected page 
'         SDC_byte    = Flash_Addr_Copy_low.byte0 + Flash_Addr_Copy_high.byte1  ' start address bytes above given address and length  
'         Data_Length = 255 - SDC_byte                                 ' data above changed bytes ( length = 255 bytes  - given addrees + given length )
'         gosub Flash_Read                                             ' read the data  
'         SDC_Block  = 0                                              ' use sector 0 
'         SDC_PAGE   =  Flash_Addr_Copy_low.byte1                          ' of selected page 
'         SDC_byte    = Flash_Addr_Copy_low.byte0 + Flash_Addr_Copy_high.byte1  ' start address bytes above given address and length  
'         Data_Length = 255 - SDC_byte                                 ' data above changed bytes ( length = 255 bytes  - given addrees + given length )
'         gosub Flash_Write                                            ' write  the data 
     
' endif
 
    ' Block 0 should now have a complete copy of the data + changed data from the orginal selected sector 
'       Flash_Sec_Orgin = 0                          ' copy sector 0 
'       Flash_Sec_dest = Flash_Addr_Copy_high.byte0  ' erase destination  and copy data from flash orgin
'       Flash_clear = 1                              ' set flag erase orgin sector 0 after copy
'       gosub Flash_Block_Copy                      ' copy the sector 
 
   
 
' return
'----------------------------------------------------
 ' command routine commented out as it was not used to save space - but works ok 
 ' >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 

' 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
'----------------------------------------------------------------------------------     
' command routine commented out as it was not used to save space - but works ok 
 ' >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
' 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 
       LATA.0[Flash_EN] = 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 
       LATA.0[Flash_EN] = 1                               ' Bring the FLASH chip select line high  
   return
'----------------------------------------------------
' command routine commented out as it was not used to save space - but works ok 
 ' >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 

'  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
'        HSEROUT2 ["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   
'---------------------------------------------------------------------


' command routine commented out as it was not used to save space - but works ok 
 ' >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 

'  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
  '----------------------------------------------


' command routine commented out as it was not used to save space - but works ok 
 ' >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 

' 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 
    LATA.0[Flash_EN] = 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 
    LATA.0[Flash_EN] = 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 
    LATA.0[Flash_EN] = 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 
    LATA.0[Flash_EN] = 1                                ' Bring the FLASH chip select line high  
  return
 '-----------------------------

 ' command routine commented out as it was not used to save space - but works ok 
 ' >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 

' Flash_Reg_Setup:

 ' ========== Note - NOT REQUIRED IT SEEMS ============
 ' Routine to write setup of status registers 2,3
 ' 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_buffer[0] = %00000000 ' QE(bit1) is forced to 0 so that if FVIQ chip Fitted uses standard SPI bus , and not force pin Hold/ WP az data i/o
'      sdc_cmd = Flash_Wr_reg2   ' write Status register2
'      data_length = 1           ' set 1 byte  
'      gosub Flash_Comand 
 
 ' 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_buffer[0] = %01100000   ' this is the factory dephalt for chip
'      sdc_cmd = Flash_Wr_reg3     ' write Status register3 
'      data_length = 1             ' set 1 byte  
'      gosub Flash_Comand 
 
' 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 
  
'   if Flash_SPI_Shared = 0 then NO_disable_rbc     ' if flag = 0 then is not a shared SPI bus with Rf Module  - jump over disable command
'   #if __PROCESSOR__ = "18F27K40" or __PROCESSOR__ = "18F47K40"  
'@ INT_DISABLE IOC_INT                              ; Turn off IOC interupts (xxk40) for RX_mode   - done so shared SPI BUS ON RF-MODULE does not corrupt flash data
'   #else 
'@ INT_DISABLE RBC_INT                              ; Turn off IOC interupts (xxk80,k22) for RX_mode   - done so shared SPI BUS ON RF-MODULE does not corrupt flash data
'   #endif 
'  NO_disable_RBC:                                 ' label to jump over the INT_disable 
 
 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  
  
      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
        LATA.0[Flash_EN] = 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
   	    LATA.0[Flash_EN] = 1               ' Bring the FLASH chip select line high to complete the write command 
 	   
     endif
	
     LATA.0[Flash_EN] = 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
    
     LATA.0[Flash_EN] = 1                          ' Bring the FLASH chip select line high.

'    #if __PROCESSOR__ = "18F27K40" or __PROCESSOR__ = "18F47K40"  
'     IOCCF.7 =0                                    ' 18f27k40 do a manual clear of the IOC port pin flag interupt - not done by DT_18_k40 atm 30/7/18
'@ INT_ENABLE IOC_INT                              ; Turn on IOC interupts (xxk40) for RX_mode   - done so shared SPI BUS ON RF-MODULE does not corrupt flash data
'   #else 
'@ INT_ENABLE RBC_INT                              ; Turn on IOC interupts (xxk80,k22) for RX_mode   - done so shared SPI BUS ON RF-MODULE does not corrupt flash data
'   #endif 
  return
'----------------------------------------------------
 Bsy_chk:
        LATA.0[Flash_EN] = 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 
        gosub Flash_SPIR  	                        ' Read Byte SDC_data_in from SPI bus.  Returns SDC_data_in.
        Flash_tmp = 0                               ' ensure 0 - counter for busychk loop
        while SDC_data_in.0 = 1                     ' while busy flag =1        
            gosub Flash_SPIR  	                    ' Read Byte SDC_data_in from SPI bus.  Returns SDC_data_in.
            Flash_tmp = Flash_tmp + 1               ' tmp counter 
            if Flash_tmp>65000 then goto BSY_Exit   ' if fail safe counter >65000 then exit - normaly under 65000 unless bulk erase  
        wend                  
BSY_Exit:
       LATA.0[Flash_EN] = 1                                   ' Bring the FLASH chip select line high
     '  IF FLASH_Install = 1 then                          ' used only for info 
     '      HSEROUT2 [" Flash_tmp = ",dec Flash_tmp,13,10] 
     '      IF Flash_tmp >65000 THEN HSEROUT2 [" Flash_tmp value HIGH - IF NOT CHIP ERASE",13,10] ' debug 
     '  ENDIF 
 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
'------------------------
 ' routine to erase / write / read test data for scratchpad sector 0 - test of flash chip 
 '  
 Flash_Test:
    SDC_Block = 0          ' set block address 
    sdc_SECTOR = 0         ' set sector start address 
    gosub Flash_Sec_Erase  ' erase sector 0  ( block0, pages 0-15 ) 
 
    SDC_Page = 0           ' set page start address 0 to 255  
    SDC_byte = 0           ' set byte start address 0 to 255 
    Data_Length = 256      ' set address length of 256 bytes  (0- 255)
   
    For  SDC_index = 0 to Data_Length -1          ' fill the data buffer  with 0 - 255  values
           SDC_buffer[SDC_index] = SDC_index      
    next SDC_index
    
    pause 100                 ' seems buffer write error if no delay of 50ms or more from the prev erase command  
    gosub Flash_Write         ' write test data to sector 0  to datalength
    gosub Buffer_Clear        ' clear the buffer after write 
    Flash_RD_Fast = 1         ' set fast read 
    gosub flash_read          ' read flash to buffer to datalength
    Flash_Chk_Fail = 1        ' set flag prior to test  
   
    For  SDC_index = 0 to Data_Length-1                 ' check data  
         if  SDC_buffer[SDC_index] <> SDC_index then 
             Flash_Chk_Fail = 0  ' if not correct value clear  flag , flag status shown on terminal at startup 
           '  HSEROUT2 ["Fail - IDX = ",DEC SDC_index,"  Buffer Data = ", dec SDC_buffer[SDC_index],13,10]  ' DEBUG 
         ENDIF
    next SDC_index
    gosub Buffer_Clear        ' clear the buffer at end of routine 
  return  
'------------------------------------------------------------------

' EXAMPLE 3 
' READ BLOCK 2 PAGES 0-2 , BYTES 0-255 OF EACH PAGE OUT TO SERIAL PORT MONITOR

' SDC_Block = 2         ' SET BLOCK TO READ    0-15 range
' Flash_Page_Orgin =0   ' SET Page START LOCATION READ value  0-255 range 
' Flash_Page_Length = 2 ' SET number of pages TO READ VALUE  0-255 range
' Data_Length = 256     ' SET BYTES NUMBER TO READ -  0-256 range  note:  
' gosub Flash_Test_RD   ' PLACE THE DATA OUT SERIAL PORT 
'return

'----------------------------------------------------------------
 'Flash_Test_RD: 
 'assumes  SDC_Block, Flash_Page_Orgin,Flash_Page_Length,Data_Length
 'Places seleted read data location out to serial port1 
  
 ' FLASH_Install = 1 ' show status  info for ref 
 ' gosub Bsy_chk ' just get the status reg value for ref 
 
 ' for SDC_Page = Flash_Page_Orgin0 to Flash_Page_Length    ' set page range for read
 '   gosub Flash_Read                                        ' read page into buffers 
 '   HSEROUT [13,10,"Sector ",dec SDC_Block," PAGE ",dec SDC_Page, 13,10]
 '   For SDC_index = 0 To Data_Length-1
 '     	HSEROUT [",",hex SDC_buffer[SDC_index] ] 
 '   next SDC_index
 ' next SDC_Page 
 
'return
'------------------------------------------
'Flash_Test_copy:

 
  ' copys data from 1 sector to another 
  ' erases destination sector - optional clean of orginal sector 
  ' assumes Flash_Orgin,Flash_clear flag,SDC_Block for destination 
  ' erases 1 sector at a time  address 
  ' Erases wont work on sectors that are write protected 
  ' sector erase take 600ms per instruction 
 
'       Flash_Sec_Orgin =  0 ' sector  
'       Flash_Page_Orgin = 0                   ' start page of orgin
'       Flash_Page_length = 9 ' how many pages 
'       Flash_Sec_Dest = Flash_Sec_Orgin          ' start at same page value as orgin
'       Flash_Page_Dest = 20        
'       gosub Flash_Page_Copy
 
'---------- FLASH_MODIFY_BYTE TEST
    
 '   Data_Length = 10     ' changed data length
 '  For SDC_index = 0 to Data_Length  
 '      SDC_buffer[SDC_index] = SDC_index  ' fill the data buffer  with 0 - 255  values 
 '   next SDC_index 
    
 '   SDC_Block = 1  ' sector start 
 '   SDC_Page = 3    ' page start
 '   SDC_Byte = 16   ' byte star address   ($0f)
 '   gosub Flash_Byte_Modify
 
 ' Flash_Sec_Orgin = 0  ' copy sector 0 
 ' Flash_Sec_dest = 1   ' erase sector 1 destination  and copy data from flash orgin
 ' Flash_clear = 1  ' erase sector 0 after copy
  
 ' gosub Flash_Sec_Copy
 '  SDC_Block = 1 
 ' gosub  Flash_Test_RD
 ' pause 3000
'  SDC_Block = 1 
'  gosub  Flash_Test_RD
 
 ' return
'Flash_protect_test:
'  SDC_Block = 0
'  gosub Flash_WR_protect 
'  gosub Bsy_chk 
'  gosub Flash_Read_ID
'return













JumpOverSPIFLASH: