added i2c controller functions, added IDE interface functions, fiexd IDE schematics
This commit is contained in:
243
OperatingSystem/software/include/kdrv_ide8255.s
Normal file
243
OperatingSystem/software/include/kdrv_ide8255.s
Normal file
@@ -0,0 +1,243 @@
|
||||
;----------------------------------------------------------------
|
||||
;BIOS Driver for IDE Interface 82C55
|
||||
;by Dennis Gunia (01/2023)
|
||||
;----------------------------------------------------------------
|
||||
|
||||
;================================================================
|
||||
; I/O registers
|
||||
;================================================================
|
||||
CS_PIA_PA .EQU 0x30 ; D0-7
|
||||
CS_PIA_PB .EQU 0x31 ; D8-15
|
||||
CS_PIA_PC .EQU 0x32 ; Controll Lines
|
||||
CS_PIA_CR .EQU 0x33
|
||||
|
||||
;================================================================
|
||||
; I/O pins
|
||||
;================================================================
|
||||
IDE_WR .EQU 00100000b
|
||||
IDE_RD .EQU 01000000b
|
||||
IDE_RST .EQU 10000000b
|
||||
|
||||
;================================================================
|
||||
; IDE registers
|
||||
;================================================================
|
||||
IDE_REG_DATA .EQU 01000b ;data I/O register (16-bits)
|
||||
IDE_REG_ERROR .EQU 01001b ;error information register when read; write precompensation register when written.
|
||||
IDE_REG_SECTOR .EQU 01010b ;Sector counter register
|
||||
IDE_REG_SSECTOR .EQU 01011b ;Start sector register
|
||||
IDE_REG_LCYL .EQU 01100b ;Low byte of the cylinder number
|
||||
IDE_REG_HCYL .EQU 01101b ;High two bits of the cylinder number
|
||||
IDE_REG_HEAD .EQU 01110b ;Head and device select register
|
||||
IDE_REG_CMDSTS .EQU 01111b ;command/status register
|
||||
IDE_REG_ALTSTS .EQU 10110b ;Alternate Status/Digital Output
|
||||
IDE_REG_DRVADDR .EQU 10111b ;Drive Address
|
||||
|
||||
;================================================================
|
||||
; I/O access functions
|
||||
;================================================================
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; ide_reset
|
||||
;
|
||||
; resets drives on bus
|
||||
;------------------------------------------------------------------------------
|
||||
ide_reset:
|
||||
LD A, 10000000b ;CommandByte-A, Mode 0, PA Out, PC Out, PB Out
|
||||
OUT (CS_PIA_CR), A ;Set Data direction to out
|
||||
LD A, IDE_RST
|
||||
OUT (CS_PIA_PC), A ;Reset IDE Device
|
||||
NOP
|
||||
XOR A
|
||||
OUT (CS_PIA_PC), A ;end device reset
|
||||
RET
|
||||
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; ide_regwrite_8
|
||||
;
|
||||
; Sends data to the IDE device
|
||||
; A contains DATA
|
||||
; B contains register number
|
||||
;------------------------------------------------------------------------------
|
||||
ide_regwrite_8:
|
||||
PUSH AF ;store date to stack
|
||||
; Prepare PIA Data Direction
|
||||
LD A, 10000000b ;CommandByte-A, Mode 0, PA Out, PC Out, PB Out
|
||||
OUT (CS_PIA_CR), A ;Set Data direction to out
|
||||
; Write Data out
|
||||
POP AF
|
||||
OUT (CS_PIA_PA), A ;Write Data to bit 0-7
|
||||
;Prepare Address
|
||||
LD A, B ;Load register address
|
||||
AND 00011111b ;Mask unused bits
|
||||
OUT (CS_PIA_PC), A ;Write Data to bit controll lines
|
||||
OR IDE_WR ;Set Write bit
|
||||
OUT (CS_PIA_PC), A ;Set write signal
|
||||
NOP ;delay to wait for processing
|
||||
LD A, B ;Load register address
|
||||
AND 00011111b ;Mask unused bits
|
||||
OUT (CS_PIA_PC), A ;disable write signal
|
||||
NOP
|
||||
XOR A ;clear register A
|
||||
OUT (CS_PIA_PC), A ;clear controll lines
|
||||
RET
|
||||
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; ide_regread_8
|
||||
;
|
||||
; Sends data to the IDE device
|
||||
; B contains register number
|
||||
; A returns data
|
||||
;------------------------------------------------------------------------------
|
||||
ide_regread_8:
|
||||
LD A, 10010010b ;CommandByte-A, Mode 0, PA IN, PC Out, PB IN
|
||||
OUT (CS_PIA_CR), A ;Set Data direction to in
|
||||
;Prepare Address
|
||||
LD A, B ;Load register address
|
||||
AND 00011111b ;Mask unused bits
|
||||
OUT (CS_PIA_PC), A ;Write Data to bit controll lines
|
||||
OR IDE_RD ;Set Write bit
|
||||
OUT (CS_PIA_PC), A ;Write Data to bit controll lines
|
||||
NOP ;delay to wait for processing
|
||||
PUSH AF
|
||||
POP AF
|
||||
PUSH AF
|
||||
POP AF
|
||||
PUSH AF
|
||||
POP AF
|
||||
PUSH AF
|
||||
POP AF
|
||||
IN A,(CS_PIA_PA) ;read data from ide device to b (because a is used later)
|
||||
PUSH AF
|
||||
XOR A ;clear register A
|
||||
OUT (CS_PIA_PC), A ;clear controll lines
|
||||
POP AF ;put data in accumulator
|
||||
RET
|
||||
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; ide_readsector_256
|
||||
;
|
||||
; Reads IDE Data
|
||||
; HL contains destination address
|
||||
;------------------------------------------------------------------------------
|
||||
ide_readsector_256:
|
||||
LD C,255 ;Setup counter for 256 words
|
||||
|
||||
ide_readsector_256_waitloop:
|
||||
LD B, IDE_REG_CMDSTS
|
||||
CALL ide_regread_8
|
||||
BIT 0,a ;Error Bit set.
|
||||
JP NZ, ide_printerror
|
||||
BIT 3,a ;DRQ Bit set. If set, disk has data
|
||||
JR Z, ide_readsector_256_waitloop ;If not set, wait
|
||||
|
||||
LD A, 10010010b ;CommandByte-A, Mode 0, PA IN, PC Out, PB IN
|
||||
OUT (CS_PIA_CR), A ;Set Data direction to IN
|
||||
LD A, IDE_REG_DATA ;CS0 and A=0 -> I/O register
|
||||
OUT (CS_PIA_PC), A ;set register
|
||||
OR IDE_RD ;Set Read bit
|
||||
OUT (CS_PIA_PC), A ;Write Read to bit controll lines
|
||||
NOP
|
||||
NOP
|
||||
NOP
|
||||
IN A,(CS_PIA_PB) ;Load 16-Bit data to buffer
|
||||
LD (HL), A
|
||||
INC HL
|
||||
IN A,(CS_PIA_PA)
|
||||
LD (HL), A
|
||||
INC HL
|
||||
|
||||
LD A,C
|
||||
OR A
|
||||
JP Z,ide_readsector_256_done
|
||||
DEC C
|
||||
JR ide_readsector_256_waitloop
|
||||
|
||||
ide_readsector_256_done:
|
||||
RET
|
||||
|
||||
ide_readsector_256_inv:
|
||||
LD C,255 ;Setup counter for 256 words
|
||||
|
||||
ide_readsector_256_inv_waitloop:
|
||||
LD B, IDE_REG_CMDSTS
|
||||
CALL ide_regread_8
|
||||
BIT 0,a ;Error Bit set.
|
||||
JP NZ, ide_printerror
|
||||
BIT 3,a ;DRQ Bit set. If set, disk has data
|
||||
JR Z, ide_readsector_256_inv_waitloop ;If not set, wait
|
||||
|
||||
LD A, 10010010b ;CommandByte-A, Mode 0, PA IN, PC Out, PB IN
|
||||
OUT (CS_PIA_CR), A ;Set Data direction to IN
|
||||
LD A, IDE_REG_DATA ;CS0 and A=0 -> I/O register
|
||||
OUT (CS_PIA_PC), A ;set register
|
||||
OR IDE_RD ;Set Read bit
|
||||
OUT (CS_PIA_PC), A ;Write Read to bit controll lines
|
||||
NOP
|
||||
NOP
|
||||
NOP
|
||||
IN A,(CS_PIA_PA) ;Load 16-Bit data to buffer
|
||||
LD (HL), A
|
||||
INC HL
|
||||
IN A,(CS_PIA_PB)
|
||||
LD (HL), A
|
||||
INC HL
|
||||
|
||||
LD A,C
|
||||
OR A
|
||||
JP Z,ide_readsector_256_done
|
||||
DEC C
|
||||
JR ide_readsector_256_inv_waitloop
|
||||
|
||||
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; ide_writesector_256
|
||||
;
|
||||
; Writes 512 bytes (256 words) of IDE Data
|
||||
; HL contains data start address
|
||||
;------------------------------------------------------------------------------
|
||||
ide_writesector_256:
|
||||
RET ;NOT IMPLEMENTED
|
||||
|
||||
|
||||
;================================================================
|
||||
; utility functions
|
||||
;================================================================
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; ide_printerror
|
||||
;
|
||||
; prints IDE error to console
|
||||
;------------------------------------------------------------------------------
|
||||
ide_printerror:
|
||||
LD HL, [str_error_start]
|
||||
CALL print_str
|
||||
LD B, IDE_REG_CMDSTS
|
||||
CALL ide_regread_8
|
||||
CALL print_a_hex
|
||||
LD HL, [str_error_start1]
|
||||
CALL print_str
|
||||
LD A,(MEM_IDE_DEVICE)
|
||||
CALL print_a_hex
|
||||
LD HL, [str_error_start2]
|
||||
CALL print_str
|
||||
LD B, IDE_REG_ERROR
|
||||
CALL ide_regread_8
|
||||
CALL print_a_hex
|
||||
LD A,10
|
||||
CALL print_char
|
||||
LD A,13
|
||||
CALL print_char
|
||||
|
||||
RET
|
||||
|
||||
str_error_start:
|
||||
db 13,10,"Disk I/O error. Status: 0x",0
|
||||
str_error_start1:
|
||||
db " Dev: 0x",0
|
||||
str_error_start2:
|
||||
db " Err: 0x",0
|
||||
|
||||
93
OperatingSystem/software/include/kdrv_ideif.s
Normal file
93
OperatingSystem/software/include/kdrv_ideif.s
Normal file
@@ -0,0 +1,93 @@
|
||||
;----------------------------------------------------------------
|
||||
;BIOS Driver for IDE Access
|
||||
;by Dennis Gunia (01/2023)
|
||||
;----------------------------------------------------------------
|
||||
|
||||
;================================================================
|
||||
; IDE commands
|
||||
;================================================================
|
||||
IDE_CMD_IDENT .EQU 0xEC ;Identify drive.
|
||||
IDE_CMD_READSEC .EQU 0x20 ;Read sectors.
|
||||
|
||||
;================================================================
|
||||
; IDE Variables
|
||||
;================================================================
|
||||
MEM_IDE_BASE .EQU 0x5000
|
||||
MEM_IDE_DEVICE .EQU MEM_IDE_BASE ;1Byte: Device ID for IDE-Port, Controller and Master/Slave
|
||||
MEM_IDE_STATUS .EQU MEM_IDE_BASE + 1 ;1Byte: 0x00 if status is okay
|
||||
MEM_IDE_BUFFER .EQU MEM_IDE_BASE + 2 ;512Byte: buffer for read/write data
|
||||
|
||||
;================================================================
|
||||
; IDE funtions
|
||||
;================================================================
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; ideif_init_drive
|
||||
;
|
||||
; initializes drive
|
||||
;------------------------------------------------------------------------------
|
||||
ideif_init_drive:
|
||||
xor a
|
||||
ld (MEM_IDE_DEVICE),A ;Set device to 0
|
||||
ld (MEM_IDE_STATUS),A ;Set status to 0 (OK)
|
||||
di ;disable interrupt
|
||||
call ide_reset ;Reset drives on bus
|
||||
ld hl, [str_dev_waitready]
|
||||
call print_str ;print waiting message
|
||||
ld DE, 0x1FFF ;preload timeout counter
|
||||
ideif_init_drive_loop1:
|
||||
ld b, IDE_REG_CMDSTS
|
||||
call ide_regread_8 ;read drive status register
|
||||
OR A
|
||||
JR Z, ideif_init_drive_nodrv ;no drive found
|
||||
BIT 6,A ;Wait for device ready
|
||||
JR NZ, ideif_init_drive_detected
|
||||
DEC DE ; decrement timeout
|
||||
LD A,D
|
||||
OR E
|
||||
JR Z, ideif_init_drive_nodrv
|
||||
|
||||
JR ideif_init_drive_loop1
|
||||
|
||||
ideif_init_drive_nodrv:
|
||||
ld hl, [str_dev_notfound]
|
||||
call print_str
|
||||
RET
|
||||
|
||||
ideif_init_drive_detected:
|
||||
ld hl, [str_dev_ready]
|
||||
call print_str
|
||||
LD B, IDE_REG_CMDSTS ;Get drive identification
|
||||
LD A, IDE_CMD_IDENT
|
||||
call ide_regwrite_8 ;Write command to drive
|
||||
LD HL,MEM_IDE_BUFFER ;set read/write buffer start address
|
||||
call ide_readsector_256 ;read 256 words from device
|
||||
LD HL,MEM_IDE_BUFFER + 20 ;print device serial
|
||||
LD B, 20
|
||||
CALL print_str_fixed
|
||||
ld hl, [str_dev_ready2]
|
||||
call print_str
|
||||
LD HL,MEM_IDE_BUFFER + 54 ;print device name
|
||||
LD B, 40
|
||||
CALL print_str_fixed
|
||||
LD A,10 ;New line
|
||||
CALL print_char
|
||||
LD A,13
|
||||
CALL print_char
|
||||
RET
|
||||
|
||||
|
||||
;================================================================
|
||||
; IDE strings
|
||||
;===============================================================
|
||||
|
||||
str_dev_waitready:
|
||||
db 13,10,"Seek HDD ... ",0
|
||||
|
||||
str_dev_ready:
|
||||
db "Device Found!",13,10,"Serial: ",0
|
||||
str_dev_ready2:
|
||||
db " Name: ",0
|
||||
|
||||
str_dev_notfound:
|
||||
db "no drive detected",13,10,0
|
||||
90
OperatingSystem/software/include/prettydump.s
Normal file
90
OperatingSystem/software/include/prettydump.s
Normal file
@@ -0,0 +1,90 @@
|
||||
;----------------------------------------------------------------
|
||||
;HEX and ASCII dump function
|
||||
;by Dennis Gunia (01/2023)
|
||||
;----------------------------------------------------------------
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; dump_pretty
|
||||
;
|
||||
; Dumps memory content
|
||||
; B contains amount of rows
|
||||
; HL contains start address
|
||||
; Destroys BC, HL
|
||||
;------------------------------------------------------------------------------
|
||||
dump_pretty:
|
||||
PUSH HL
|
||||
LD HL,[STR_PD_HEADER] ;Print header
|
||||
CALL print_str
|
||||
POP HL
|
||||
dump_pretty_row:
|
||||
LD A,B ;Check row counter
|
||||
OR A
|
||||
JP Z, dump_pretty_end ;If counter is 0, exit
|
||||
DEC B ;Decrement row counter by 1
|
||||
LD C, 16 ;Load column counter
|
||||
LD A, H ;Print base address
|
||||
CALL print_a_hex
|
||||
LD A, L
|
||||
CALL print_a_hex
|
||||
LD A, ' '
|
||||
CALL print_char
|
||||
dump_pretty_col: ;Loop for column
|
||||
LD A,(HL) ;Load byte to disply
|
||||
CALL print_a_hex
|
||||
LD A, ' '
|
||||
CALL print_char
|
||||
INC HL
|
||||
DEC C ;Decrement column counter
|
||||
JR NZ, dump_pretty_col ;Loop if not 0
|
||||
dump_pretty_ascii:
|
||||
PUSH BC
|
||||
PUSH HL
|
||||
LD B,0
|
||||
LD C,16
|
||||
SBC HL,BC ;Reset HL by column count
|
||||
dump_pretty_ascii_loop:
|
||||
LD A,(HL)
|
||||
INC HL
|
||||
CP 32
|
||||
JP C, dump_pretty_ascii_none ;if less than 32, it is not a char
|
||||
CP 127
|
||||
JP NC, dump_pretty_ascii_none ;if greater or equal than 128, it is not a char
|
||||
call print_char
|
||||
jr dump_pretty_ascii_cont
|
||||
dump_pretty_ascii_none:
|
||||
LD A,'.'
|
||||
call print_char
|
||||
dump_pretty_ascii_cont:
|
||||
DEC C
|
||||
JP NZ, dump_pretty_ascii_loop
|
||||
|
||||
|
||||
POP HL
|
||||
POP BC
|
||||
dump_pretty_nextrow:
|
||||
LD A,10 ;New line
|
||||
CALL print_char
|
||||
LD A,13
|
||||
CALL print_char
|
||||
JR dump_pretty_row ;Else next line
|
||||
dump_pretty_end:
|
||||
RET
|
||||
|
||||
STR_PD_HEADER:
|
||||
db 13,10,'BASE 0 1 2 3 4 5 6 7 8 9 A B C D E F ASCII',13,10,0
|
||||
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; print_str_fixed
|
||||
;
|
||||
; Prints string with fixed length
|
||||
; B contains length
|
||||
; HL contains start address
|
||||
;------------------------------------------------------------------------------
|
||||
print_str_fixed:
|
||||
LD A,(HL)
|
||||
INC HL
|
||||
CALL print_char
|
||||
DJNZ print_str_fixed
|
||||
RET
|
||||
|
||||
@@ -1,327 +1,50 @@
|
||||
.include "extern_symbols.s" ;include monitor symbols.
|
||||
.include "extern_symbols.s" ;include monitor symbols.
|
||||
org 0xB000
|
||||
CS_PIO_BD .EQU 0xF5
|
||||
CS_PIO_BC .EQU 0xF7
|
||||
CS_PIO_AD .EQU 0xF4
|
||||
CS_PIO_AC .EQU 0xF6
|
||||
;Testing code
|
||||
call ideif_init_drive
|
||||
|
||||
CS_I2C_S1 .EQU 0xF3
|
||||
CS_I2C_SX .EQU 0xF2
|
||||
;testread sector
|
||||
LD A,1 ;read 1 sector
|
||||
LD B,IDE_REG_SECTOR
|
||||
CALL ide_regwrite_8
|
||||
|
||||
IIC_RTC equ 11010000b
|
||||
LD A,1 ;read sector 0
|
||||
LD B,IDE_REG_SSECTOR
|
||||
CALL ide_regwrite_8
|
||||
|
||||
IIC_INIT:
|
||||
LD A,0xCF
|
||||
OUT (CS_PIO_AC), A
|
||||
LD A,11110101b
|
||||
OUT (CS_PIO_AC), A
|
||||
LD A,0 ;read cylinder 0
|
||||
LD B,IDE_REG_LCYL
|
||||
CALL ide_regwrite_8
|
||||
LD A,0
|
||||
LD B,IDE_REG_HCYL
|
||||
CALL ide_regwrite_8
|
||||
|
||||
LD A,00000000b ; Reset PCF8584 minimum 30 clock cycles
|
||||
OUT (CS_PIO_AD), A
|
||||
LD BC,0x1000
|
||||
CALL PAUSE_LOOP
|
||||
LD A,0000010b
|
||||
OUT (CS_PIO_AD), A
|
||||
LD A,10100000b ;read head 0
|
||||
LD B,IDE_REG_HEAD
|
||||
CALL ide_regwrite_8
|
||||
|
||||
NOP
|
||||
NOP
|
||||
NOP
|
||||
|
||||
LD A, 0x80 ;S1 -> Select S0, PIN disabled, ESO = 0, Interrupt disabled, STA, STA, ACK = 0
|
||||
OUT (CS_I2C_S1),A
|
||||
CALL SlowAccess
|
||||
CALL SlowAccess
|
||||
|
||||
LD A,0x55 ;S0 -> Loads byte 55H into register S0'; effective own address becomes AAH
|
||||
OUT (CS_I2C_SX),A
|
||||
CALL SlowAccess
|
||||
|
||||
LD A, 0xA0 ;S1 -> Loads byte A0H into register S1, i.e. next byte will be loaded into the clock control register S2.
|
||||
OUT (CS_I2C_S1),A
|
||||
CALL SlowAccess
|
||||
|
||||
|
||||
LD A,0x00 ;Load 18H into S2 register (clock control - 8 MHz, 90 KHz)
|
||||
OUT (CS_I2C_SX),A
|
||||
CALL SlowAccess
|
||||
|
||||
LD A,0xC1 ;S1 -> loads byte C1H into register S1; register enable
|
||||
;serial interface, set I 2C-bus into idle mode;
|
||||
;SDA and SCL are HIGH. The next write or read
|
||||
;operation will be to/from data transfer register
|
||||
;S0 if A0 = LOW.;
|
||||
OUT (CS_I2C_S1),A
|
||||
CALL SlowAccess
|
||||
|
||||
|
||||
|
||||
;CALL force_stop
|
||||
JP PROMPT_BEGIN
|
||||
|
||||
LD BC,$0100
|
||||
CALL PAUSE_LOOP
|
||||
|
||||
|
||||
; Send test message to RTC
|
||||
|
||||
LD DE, 0xC000 ; Set I2C Buffer Location
|
||||
LD A,0x00
|
||||
LD (DE),A
|
||||
;call regdump
|
||||
|
||||
LD B, IIC_RTC ; Set I2C Address
|
||||
LD A, 1 ; Set I2C Buffer length
|
||||
call i2c_send
|
||||
|
||||
LD DE, 0xC010
|
||||
LD B, IIC_RTC
|
||||
LD A, 7
|
||||
call i2c_read
|
||||
LD A,IDE_CMD_READSEC ;send read command
|
||||
LD B,IDE_REG_CMDSTS
|
||||
CALL ide_regwrite_8
|
||||
|
||||
LD HL,MEM_IDE_BUFFER ;set read/write buffer start address
|
||||
call ide_readsector_256_inv ;read 256 words from device
|
||||
|
||||
LD HL,MEM_IDE_BUFFER
|
||||
LD B,32
|
||||
call dump_pretty
|
||||
|
||||
JP PROMPT_BEGIN
|
||||
|
||||
|
||||
;CLK_ENABLE:
|
||||
; LD DE, 0xC000 ; Set I2C Buffer Location
|
||||
; LD A,0x00
|
||||
; LD (0xC000),A
|
||||
; LD (0xC001),A
|
||||
; ;call regdump
|
||||
;
|
||||
; LD B, IIC_RTC ; Set I2C Address
|
||||
; LD A, 2 ; Set I2C Buffer length
|
||||
; call i2c_send
|
||||
; JP PROMPT_BEGIN
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; i2c_send
|
||||
;
|
||||
; Sends data over the i2c bus
|
||||
; A contains BYTE COUNTER
|
||||
; B contains ADDRESS
|
||||
; DE contains location of Data Buffer
|
||||
;------------------------------------------------------------------------------
|
||||
i2c_send:
|
||||
; CALL PRINTINLINE;
|
||||
; defb "SEND A",10,13,0
|
||||
PUSH BC
|
||||
PUSH AF
|
||||
CALL i2c_bus_rdy
|
||||
; CALL PRINTINLINE
|
||||
; defb "SEND START",10,13,0
|
||||
LD A,B ;Load 'slave address' into S0 register:
|
||||
OUT (CS_I2C_SX),A
|
||||
CALL SlowAccess
|
||||
.include "kdrv_ide8255.s" ;include ide interface driver.
|
||||
.include "kdrv_ideif.s" ;include ide driver.
|
||||
.include "prettydump.s" ;include monitor symbols.
|
||||
|
||||
LD A, 0xC5 ;Load C5H into S1. 'C5H' = PCF8584 generates
|
||||
;the 'START' condition and clocks out the slave
|
||||
;address and the clock pulse for slave acknowledgement.
|
||||
OUT (CS_I2C_S1),A
|
||||
POP AF
|
||||
LD C,A
|
||||
INC C
|
||||
i2c_send_1: ; LOOP 1 : Wait for bus ready
|
||||
IN A,(CS_I2C_S1) ; Read byte from S1 register
|
||||
BIT 7,A ; Is bus free? (S1 ~BB=1?)
|
||||
JR NZ,i2c_send_1 ; No - loop
|
||||
BIT 4,A ; slave acknowledged? (LRB = 0?)
|
||||
JR NZ, i2c_send_stop ; if not, cancel transmission
|
||||
LD A,(DE) ; Load next byte from buffer
|
||||
INC DE
|
||||
DEC C
|
||||
JR Z, i2c_send_stop ; if counter = 0, exit loop
|
||||
OUT (CS_I2C_SX),A ; Send byte
|
||||
JR i2c_send_1 ; if counter > 0, loop again
|
||||
i2c_send_stop:
|
||||
LD A, 0xC3 ;STOP
|
||||
OUT (CS_I2C_S1),A
|
||||
CALL SlowAccess
|
||||
POP BC
|
||||
RET
|
||||
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; i2c_read
|
||||
;
|
||||
; Sends data over the i2c bus
|
||||
; A contains BYTE COUNTER
|
||||
; B contains ADDRESS
|
||||
; DE contains location of Data Buffer
|
||||
;------------------------------------------------------------------------------
|
||||
i2c_read:
|
||||
PUSH DE
|
||||
PUSH BC
|
||||
PUSH AF
|
||||
LD A,B ;Load 'slave address' into S0 register:
|
||||
OR 0x01 ;Set RW Bit for read operation
|
||||
OUT (CS_I2C_SX),A
|
||||
CALL SlowAccess
|
||||
CALL i2c_bus_rdy ; Is bus ready
|
||||
LD A, 0xC5 ;Load C5H into S1. 'C5H' = PCF8584 generates
|
||||
;the 'START' condition and clocks out the slave
|
||||
;address and the clock pulse for slave acknowledgement.
|
||||
OUT (CS_I2C_S1),A
|
||||
;Setup counter
|
||||
POP AF
|
||||
LD C,A ; Load BYTE COUNTER into C
|
||||
INC C ; Offset C by 1
|
||||
i2c_read_1: ;Wait for PIN = 0
|
||||
IN A,(CS_I2C_S1) ; Read byte from S1 register
|
||||
BIT 7,A ; S1 PIN=1?
|
||||
JR NZ,i2c_read_1 ; No - loop
|
||||
BIT 3,A ; S1 LRB=0? slave ACK?
|
||||
JR NZ, i2c_read_error ; No ACK -> an error has occured
|
||||
DEC C
|
||||
LD A, C
|
||||
DEC A ;If n = m − 1?
|
||||
JR Z, i2c_read_last
|
||||
IN A,(CS_I2C_SX)
|
||||
LD (DE),A
|
||||
INC DE
|
||||
JR i2c_read_1
|
||||
i2c_read_last: ;read last byte
|
||||
LD A, 0x40
|
||||
OUT (CS_I2C_S1),A
|
||||
CALL SlowAccess
|
||||
IN A,(CS_I2C_SX) ;receives the final data byte. Neg. ACK is also sent.
|
||||
LD (DE),A
|
||||
INC DE
|
||||
i2c_read_last_1:
|
||||
IN A,(CS_I2C_S1) ; Read byte from S1 register
|
||||
BIT 7,A ; S1 PIN=1?
|
||||
JR NZ,i2c_read_last_1 ; No - loop
|
||||
|
||||
i2c_read_error:
|
||||
NOP
|
||||
i2c_read_stop:
|
||||
LD A, 0xC3
|
||||
OUT (CS_I2C_S1),A
|
||||
CALL SlowAccess
|
||||
IN A,(CS_I2C_SX) ;transfers the final data byte from the
|
||||
;data buffer to accumulator.
|
||||
CALL SlowAccess
|
||||
LD (DE),A
|
||||
POP BC
|
||||
POP DE
|
||||
RET
|
||||
|
||||
|
||||
i2c_stop_force:
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; i2c_rdy
|
||||
;
|
||||
; Waits until the PCF8584 signals a byte transmission/reception is complete.
|
||||
;------------------------------------------------------------------------------
|
||||
i2c_rdy:
|
||||
PUSH AF
|
||||
i2c_rlp:
|
||||
IN A,(CS_I2C_S1) ; Read byte from S1 register
|
||||
BIT 7,A ; Is Tx/Rx complete? (S1 PIN=0?)
|
||||
call print_a_hex
|
||||
JR NZ,i2c_rlp ; No - loop
|
||||
i2crlpex:
|
||||
POP AF
|
||||
RET
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; i2c_bus_rdy
|
||||
;
|
||||
; Waits until the I2C bus is free before RETurning
|
||||
;------------------------------------------------------------------------------
|
||||
i2c_bus_rdy:
|
||||
PUSH AF
|
||||
i2c_blp:
|
||||
IN A,(CS_I2C_S1) ; Read byte from S1 register
|
||||
PUSH AF
|
||||
call print_a_hex
|
||||
delay_small:
|
||||
PUSH AF
|
||||
POP AF
|
||||
BIT 0,A ; Is bus free? (S1 ~BB=1?)
|
||||
JR Z,i2c_blp ; No - loop
|
||||
i2cblpex:
|
||||
POP AF
|
||||
RET
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; PAUSE_LOOP
|
||||
;
|
||||
; Timer function
|
||||
;
|
||||
; 16-bit (BC) decrement counter, performing 4xNEG loop until BC
|
||||
; reaches zero.
|
||||
;
|
||||
; 61 T-states in loop = 15.25uS per loop @ 4 MHz - near enough
|
||||
; a second delay for 65,535 iterations.
|
||||
;
|
||||
; Set iteration count in BC before calling this function.
|
||||
; Destroys: BC
|
||||
;------------------------------------------------------------------------------
|
||||
PAUSE_LOOP:
|
||||
PUSH AF ; 11 T-states
|
||||
pau_lp:
|
||||
;NEG ; 8 T-states
|
||||
;NEG ; 8 T-states
|
||||
;NEG ; 8 T-states
|
||||
;NEG ; 8 T-states
|
||||
PUSH BC ; 11 T-states
|
||||
POP BC ; 10 T-states
|
||||
PUSH BC ; 11 T-states
|
||||
POP BC ; 10 T-states
|
||||
DEC BC ; 6 T-states
|
||||
LD A,C ; 9 T-states
|
||||
OR B ; 4 T-states
|
||||
JP NZ,pau_lp ; 10 T-states
|
||||
POP AF ; 10 T-states
|
||||
RET ; Pause complete, RETurn
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; PRINTINLINE
|
||||
;
|
||||
; String output function
|
||||
;
|
||||
; Prints in-line data (bytes immediately following the PRINTINLINE call)
|
||||
; until a string terminator is encountered (0 - null char).
|
||||
;------------------------------------------------------------------------------
|
||||
PRINTINLINE:
|
||||
EX (SP),HL ; PUSH HL and put RET ADDress into HL
|
||||
PUSH AF
|
||||
PUSH BC
|
||||
nxtILC:
|
||||
LD A,(HL)
|
||||
CP 0
|
||||
JR Z,endPrint
|
||||
CALL print_char
|
||||
INC HL
|
||||
JR nxtILC
|
||||
endPrint:
|
||||
INC HL ; Get past "null" terminator
|
||||
POP BC
|
||||
POP AF
|
||||
EX (SP),HL ; PUSH new RET ADDress on stack and restore HL
|
||||
RET
|
||||
|
||||
SlowAccess:
|
||||
NOP
|
||||
NOP
|
||||
NOP
|
||||
NOP
|
||||
NOP
|
||||
NOP
|
||||
NOP
|
||||
NOP
|
||||
RET
|
||||
|
||||
|
||||
;.include "regdump.s"
|
||||
|
||||
force_stop:
|
||||
IN A,(CS_I2C_S1)
|
||||
BIT 0, A
|
||||
RET NZ
|
||||
LD A, 11000011b
|
||||
OUT (CS_I2C_S1),A
|
||||
NOP
|
||||
NOP
|
||||
JR force_stop
|
||||
PUSH AF
|
||||
POP AF
|
||||
RET
|
||||
327
OperatingSystem/software/test_iic.asm
Normal file
327
OperatingSystem/software/test_iic.asm
Normal file
@@ -0,0 +1,327 @@
|
||||
.include "extern_symbols.s" ;include monitor symbols.
|
||||
org 0xB000
|
||||
CS_PIO_BD .EQU 0xF5
|
||||
CS_PIO_BC .EQU 0xF7
|
||||
CS_PIO_AD .EQU 0xF4
|
||||
CS_PIO_AC .EQU 0xF6
|
||||
|
||||
CS_I2C_S1 .EQU 0xF3
|
||||
CS_I2C_SX .EQU 0xF2
|
||||
|
||||
IIC_RTC equ 11010000b
|
||||
|
||||
IIC_INIT:
|
||||
LD A,0xCF
|
||||
OUT (CS_PIO_AC), A
|
||||
LD A,11110101b
|
||||
OUT (CS_PIO_AC), A
|
||||
|
||||
LD A,00000000b ; Reset PCF8584 minimum 30 clock cycles
|
||||
OUT (CS_PIO_AD), A
|
||||
LD BC,0x1000
|
||||
CALL PAUSE_LOOP
|
||||
LD A,0000010b
|
||||
OUT (CS_PIO_AD), A
|
||||
|
||||
NOP
|
||||
NOP
|
||||
NOP
|
||||
|
||||
LD A, 0x80 ;S1 -> Select S0, PIN disabled, ESO = 0, Interrupt disabled, STA, STA, ACK = 0
|
||||
OUT (CS_I2C_S1),A
|
||||
CALL SlowAccess
|
||||
CALL SlowAccess
|
||||
|
||||
LD A,0x55 ;S0 -> Loads byte 55H into register S0'; effective own address becomes AAH
|
||||
OUT (CS_I2C_SX),A
|
||||
CALL SlowAccess
|
||||
|
||||
LD A, 0xA0 ;S1 -> Loads byte A0H into register S1, i.e. next byte will be loaded into the clock control register S2.
|
||||
OUT (CS_I2C_S1),A
|
||||
CALL SlowAccess
|
||||
|
||||
|
||||
LD A,0x00 ;Load 18H into S2 register (clock control - 8 MHz, 90 KHz)
|
||||
OUT (CS_I2C_SX),A
|
||||
CALL SlowAccess
|
||||
|
||||
LD A,0xC1 ;S1 -> loads byte C1H into register S1; register enable
|
||||
;serial interface, set I 2C-bus into idle mode;
|
||||
;SDA and SCL are HIGH. The next write or read
|
||||
;operation will be to/from data transfer register
|
||||
;S0 if A0 = LOW.;
|
||||
OUT (CS_I2C_S1),A
|
||||
CALL SlowAccess
|
||||
|
||||
|
||||
|
||||
;CALL force_stop
|
||||
JP PROMPT_BEGIN
|
||||
|
||||
LD BC,$0100
|
||||
CALL PAUSE_LOOP
|
||||
|
||||
|
||||
; Send test message to RTC
|
||||
|
||||
LD DE, 0xC000 ; Set I2C Buffer Location
|
||||
LD A,0x00
|
||||
LD (DE),A
|
||||
;call regdump
|
||||
|
||||
LD B, IIC_RTC ; Set I2C Address
|
||||
LD A, 1 ; Set I2C Buffer length
|
||||
call i2c_send
|
||||
|
||||
LD DE, 0xC010
|
||||
LD B, IIC_RTC
|
||||
LD A, 7
|
||||
call i2c_read
|
||||
|
||||
|
||||
|
||||
JP PROMPT_BEGIN
|
||||
|
||||
|
||||
;CLK_ENABLE:
|
||||
; LD DE, 0xC000 ; Set I2C Buffer Location
|
||||
; LD A,0x00
|
||||
; LD (0xC000),A
|
||||
; LD (0xC001),A
|
||||
; ;call regdump
|
||||
;
|
||||
; LD B, IIC_RTC ; Set I2C Address
|
||||
; LD A, 2 ; Set I2C Buffer length
|
||||
; call i2c_send
|
||||
; JP PROMPT_BEGIN
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; i2c_send
|
||||
;
|
||||
; Sends data over the i2c bus
|
||||
; A contains BYTE COUNTER
|
||||
; B contains ADDRESS
|
||||
; DE contains location of Data Buffer
|
||||
;------------------------------------------------------------------------------
|
||||
i2c_send:
|
||||
; CALL PRINTINLINE;
|
||||
; defb "SEND A",10,13,0
|
||||
PUSH BC
|
||||
PUSH AF
|
||||
CALL i2c_bus_rdy
|
||||
; CALL PRINTINLINE
|
||||
; defb "SEND START",10,13,0
|
||||
LD A,B ;Load 'slave address' into S0 register:
|
||||
OUT (CS_I2C_SX),A
|
||||
CALL SlowAccess
|
||||
|
||||
LD A, 0xC5 ;Load C5H into S1. 'C5H' = PCF8584 generates
|
||||
;the 'START' condition and clocks out the slave
|
||||
;address and the clock pulse for slave acknowledgement.
|
||||
OUT (CS_I2C_S1),A
|
||||
POP AF
|
||||
LD C,A
|
||||
INC C
|
||||
i2c_send_1: ; LOOP 1 : Wait for bus ready
|
||||
IN A,(CS_I2C_S1) ; Read byte from S1 register
|
||||
BIT 7,A ; Is bus free? (S1 ~BB=1?)
|
||||
JR NZ,i2c_send_1 ; No - loop
|
||||
BIT 4,A ; slave acknowledged? (LRB = 0?)
|
||||
JR NZ, i2c_send_stop ; if not, cancel transmission
|
||||
LD A,(DE) ; Load next byte from buffer
|
||||
INC DE
|
||||
DEC C
|
||||
JR Z, i2c_send_stop ; if counter = 0, exit loop
|
||||
OUT (CS_I2C_SX),A ; Send byte
|
||||
JR i2c_send_1 ; if counter > 0, loop again
|
||||
i2c_send_stop:
|
||||
LD A, 0xC3 ;STOP
|
||||
OUT (CS_I2C_S1),A
|
||||
CALL SlowAccess
|
||||
POP BC
|
||||
RET
|
||||
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; i2c_read
|
||||
;
|
||||
; Sends data over the i2c bus
|
||||
; A contains BYTE COUNTER
|
||||
; B contains ADDRESS
|
||||
; DE contains location of Data Buffer
|
||||
;------------------------------------------------------------------------------
|
||||
i2c_read:
|
||||
PUSH DE
|
||||
PUSH BC
|
||||
PUSH AF
|
||||
LD A,B ;Load 'slave address' into S0 register:
|
||||
OR 0x01 ;Set RW Bit for read operation
|
||||
OUT (CS_I2C_SX),A
|
||||
CALL SlowAccess
|
||||
CALL i2c_bus_rdy ; Is bus ready
|
||||
LD A, 0xC5 ;Load C5H into S1. 'C5H' = PCF8584 generates
|
||||
;the 'START' condition and clocks out the slave
|
||||
;address and the clock pulse for slave acknowledgement.
|
||||
OUT (CS_I2C_S1),A
|
||||
;Setup counter
|
||||
POP AF
|
||||
LD C,A ; Load BYTE COUNTER into C
|
||||
INC C ; Offset C by 1
|
||||
i2c_read_1: ;Wait for PIN = 0
|
||||
IN A,(CS_I2C_S1) ; Read byte from S1 register
|
||||
BIT 7,A ; S1 PIN=1?
|
||||
JR NZ,i2c_read_1 ; No - loop
|
||||
BIT 3,A ; S1 LRB=0? slave ACK?
|
||||
JR NZ, i2c_read_error ; No ACK -> an error has occured
|
||||
DEC C
|
||||
LD A, C
|
||||
DEC A ;If n = m − 1?
|
||||
JR Z, i2c_read_last
|
||||
IN A,(CS_I2C_SX)
|
||||
LD (DE),A
|
||||
INC DE
|
||||
JR i2c_read_1
|
||||
i2c_read_last: ;read last byte
|
||||
LD A, 0x40
|
||||
OUT (CS_I2C_S1),A
|
||||
CALL SlowAccess
|
||||
IN A,(CS_I2C_SX) ;receives the final data byte. Neg. ACK is also sent.
|
||||
LD (DE),A
|
||||
INC DE
|
||||
i2c_read_last_1:
|
||||
IN A,(CS_I2C_S1) ; Read byte from S1 register
|
||||
BIT 7,A ; S1 PIN=1?
|
||||
JR NZ,i2c_read_last_1 ; No - loop
|
||||
|
||||
i2c_read_error:
|
||||
NOP
|
||||
i2c_read_stop:
|
||||
LD A, 0xC3
|
||||
OUT (CS_I2C_S1),A
|
||||
CALL SlowAccess
|
||||
IN A,(CS_I2C_SX) ;transfers the final data byte from the
|
||||
;data buffer to accumulator.
|
||||
CALL SlowAccess
|
||||
LD (DE),A
|
||||
POP BC
|
||||
POP DE
|
||||
RET
|
||||
|
||||
|
||||
i2c_stop_force:
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; i2c_rdy
|
||||
;
|
||||
; Waits until the PCF8584 signals a byte transmission/reception is complete.
|
||||
;------------------------------------------------------------------------------
|
||||
i2c_rdy:
|
||||
PUSH AF
|
||||
i2c_rlp:
|
||||
IN A,(CS_I2C_S1) ; Read byte from S1 register
|
||||
BIT 7,A ; Is Tx/Rx complete? (S1 PIN=0?)
|
||||
call print_a_hex
|
||||
JR NZ,i2c_rlp ; No - loop
|
||||
i2crlpex:
|
||||
POP AF
|
||||
RET
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; i2c_bus_rdy
|
||||
;
|
||||
; Waits until the I2C bus is free before RETurning
|
||||
;------------------------------------------------------------------------------
|
||||
i2c_bus_rdy:
|
||||
PUSH AF
|
||||
i2c_blp:
|
||||
IN A,(CS_I2C_S1) ; Read byte from S1 register
|
||||
PUSH AF
|
||||
call print_a_hex
|
||||
POP AF
|
||||
BIT 0,A ; Is bus free? (S1 ~BB=1?)
|
||||
JR Z,i2c_blp ; No - loop
|
||||
i2cblpex:
|
||||
POP AF
|
||||
RET
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; PAUSE_LOOP
|
||||
;
|
||||
; Timer function
|
||||
;
|
||||
; 16-bit (BC) decrement counter, performing 4xNEG loop until BC
|
||||
; reaches zero.
|
||||
;
|
||||
; 61 T-states in loop = 15.25uS per loop @ 4 MHz - near enough
|
||||
; a second delay for 65,535 iterations.
|
||||
;
|
||||
; Set iteration count in BC before calling this function.
|
||||
; Destroys: BC
|
||||
;------------------------------------------------------------------------------
|
||||
PAUSE_LOOP:
|
||||
PUSH AF ; 11 T-states
|
||||
pau_lp:
|
||||
;NEG ; 8 T-states
|
||||
;NEG ; 8 T-states
|
||||
;NEG ; 8 T-states
|
||||
;NEG ; 8 T-states
|
||||
PUSH BC ; 11 T-states
|
||||
POP BC ; 10 T-states
|
||||
PUSH BC ; 11 T-states
|
||||
POP BC ; 10 T-states
|
||||
DEC BC ; 6 T-states
|
||||
LD A,C ; 9 T-states
|
||||
OR B ; 4 T-states
|
||||
JP NZ,pau_lp ; 10 T-states
|
||||
POP AF ; 10 T-states
|
||||
RET ; Pause complete, RETurn
|
||||
|
||||
;------------------------------------------------------------------------------
|
||||
; PRINTINLINE
|
||||
;
|
||||
; String output function
|
||||
;
|
||||
; Prints in-line data (bytes immediately following the PRINTINLINE call)
|
||||
; until a string terminator is encountered (0 - null char).
|
||||
;------------------------------------------------------------------------------
|
||||
PRINTINLINE:
|
||||
EX (SP),HL ; PUSH HL and put RET ADDress into HL
|
||||
PUSH AF
|
||||
PUSH BC
|
||||
nxtILC:
|
||||
LD A,(HL)
|
||||
CP 0
|
||||
JR Z,endPrint
|
||||
CALL print_char
|
||||
INC HL
|
||||
JR nxtILC
|
||||
endPrint:
|
||||
INC HL ; Get past "null" terminator
|
||||
POP BC
|
||||
POP AF
|
||||
EX (SP),HL ; PUSH new RET ADDress on stack and restore HL
|
||||
RET
|
||||
|
||||
SlowAccess:
|
||||
NOP
|
||||
NOP
|
||||
NOP
|
||||
NOP
|
||||
NOP
|
||||
NOP
|
||||
NOP
|
||||
NOP
|
||||
RET
|
||||
|
||||
|
||||
;.include "regdump.s"
|
||||
|
||||
force_stop:
|
||||
IN A,(CS_I2C_S1)
|
||||
BIT 0, A
|
||||
RET NZ
|
||||
LD A, 11000011b
|
||||
OUT (CS_I2C_S1),A
|
||||
NOP
|
||||
NOP
|
||||
JR force_stop
|
||||
Binary file not shown.
@@ -1,20 +1,43 @@
|
||||
:10B000003ECFD3F63EF5D3F63E00D3F4010010CD8B
|
||||
:10B01000F6B03E02D3F40000003E80D3F3CD16B16B
|
||||
:10B02000CD16B13E55D3F2CD16B13EA0D3F3CD1619
|
||||
:10B03000B13E00D3F2CD16B13EC1D3F3CD16B1C3AC
|
||||
:10B040009900010001CDF6B01100C03E001206D0FB
|
||||
:10B050003E01CD62B01110C006D03E07CD90B0C306
|
||||
:10B060009900C5F5CDE8B078D3F2CD16B13EC5D381
|
||||
:10B07000F3F14F0CDBF3CB7F20FACB6720091A13D7
|
||||
:10B080000D2804D3F218ED3EC3D3F3CD16B1C1C9D8
|
||||
:10B09000D5C5F578F601D3F2CD16B1CDE8B03EC5F1
|
||||
:10B0A000D3F3F14F0CDBF3CB7F20FACB5F201C0DE9
|
||||
:10B0B000793D2806DBF2121318EB3E40D3F3CD1690
|
||||
:10B0C000B1DBF21213DBF3CB7F20FA003EC3D3F3E4
|
||||
:10B0D000CD16B1DBF2CD16B112C1D1C9F5DBF3CB80
|
||||
:10B0E0007FCDE70220F7F1C9F5DBF3F5CDE702F1FB
|
||||
:10B0F000CB4728F5F1C9F5C5C1C5C10B79B0C2F779
|
||||
:10B10000B0F1C9E3F5C57EFE002806CDB7022318CD
|
||||
:10B11000F523C1F1E3C90000000000000000C9DB15
|
||||
:0CB12000F3CB47C03EC3D3F3000018F38C
|
||||
:10B00000CD47B13E01060ACD4BB03E01060BCD4BFC
|
||||
:10B01000B03E00060CCD4BB03E00060DCD4BB03E11
|
||||
:10B02000A0060ECD4BB03E20060FCD4BB0210250F6
|
||||
:10B03000CDB5B02102500620CDEEB1C396003E80C2
|
||||
:10B04000D3333E80D33200AFD332C9F53E80D33301
|
||||
:10B05000F1D33078E61FD332F620D3320078E61FE2
|
||||
:10B06000D33200AFD332C93E92D33378E61FD33206
|
||||
:10B07000F640D33200F5F1F5F1F5F1F5F1DB30F5FD
|
||||
:10B08000AFD332F1C90EFF060FCD67B0CB47C2E593
|
||||
:10B09000B0CB5F28F23E92D3333E08D332F640D392
|
||||
:10B0A00032000000DB317723DB30772379B7CAB475
|
||||
:10B0B000B00D18D3C90EFF060FCD67B0CB47C2E560
|
||||
:10B0C000B0CB5F28F23E92D3333E08D332F640D362
|
||||
:10B0D00032000000DB307723DB31772379B7CAB445
|
||||
:10B0E000B00D18D3C92118B1CDBC02060FCD67B081
|
||||
:10B0F000CDE4022135B1CDBC023A0050CDE40221AD
|
||||
:10B100003EB1CDBC020609CD67B0CDE4023E0ACD0A
|
||||
:10B11000B4023E0DCDB402C90D0A4469736B2049D7
|
||||
:10B120002F4F206572726F722E2053746174757385
|
||||
:10B130003A20307800204465763A20307800204567
|
||||
:10B1400072723A20307800AF320050320150F3CDA5
|
||||
:10B150003EB021A9B1CDBC0211FF1F060FCD67B0D3
|
||||
:10B16000B7280BCB77200E1B7AB3280218ED21DA13
|
||||
:10B17000B1CDBC02C921B9B1CDBC02060F3EECCDA8
|
||||
:10B180004BB0210250CD85B02116500614CD88B2A7
|
||||
:10B1900021D1B1CDBC022138500628CD88B23E0A5B
|
||||
:10B1A000CDB4023E0DCDB402C90D0A5365656B20C6
|
||||
:10B1B000484444202E2E2E20004465766963652085
|
||||
:10B1C000466F756E64210D0A53657269616C3A2091
|
||||
:10B1D0000020204E616D653A20006E6F2064726918
|
||||
:10B1E00076652064657465637465640D0A00E52105
|
||||
:10B1F00049B2CDBC02E178B7CA48B2050E107CCD89
|
||||
:10B20000E4027DCDE4023E20CDB4027ECDE4023ED8
|
||||
:10B2100020CDB402230D20F3C5E506000E10ED424B
|
||||
:10B220007E23FE20DA31B2FE7FD231B2CDB40218D5
|
||||
:10B23000053E2ECDB4020DC220B2E1C13E0ACDB40E
|
||||
:10B24000023E0DCDB40218AEC90D0A42415345204D
|
||||
:10B25000302020312020322020332020342020357F
|
||||
:10B26000202036202037202038202039202041205F
|
||||
:10B27000204220204320204420204520204620201A
|
||||
:10B2800041534349490D0A007E23CDB40210F9C948
|
||||
:05B29000F5F1F5F1C924
|
||||
:00000001FF
|
||||
|
||||
File diff suppressed because it is too large
Load Diff
@@ -1,19 +1,42 @@
|
||||
!B000 3E CF D3 F6 3E F5 D3 F6 3E 00 D3 F4 01 00 10 CD
|
||||
!B010 F6 B0 3E 02 D3 F4 00 00 00 3E 80 D3 F3 CD 16 B1
|
||||
!B020 CD 16 B1 3E 55 D3 F2 CD 16 B1 3E A0 D3 F3 CD 16
|
||||
!B030 B1 3E 00 D3 F2 CD 16 B1 3E C1 D3 F3 CD 16 B1 C3
|
||||
!B040 99 00 01 00 01 CD F6 B0 11 00 C0 3E 00 12 06 D0
|
||||
!B050 3E 01 CD 62 B0 11 10 C0 06 D0 3E 07 CD 90 B0 C3
|
||||
!B060 99 00 C5 F5 CD E8 B0 78 D3 F2 CD 16 B1 3E C5 D3
|
||||
!B070 F3 F1 4F 0C DB F3 CB 7F 20 FA CB 67 20 09 1A 13
|
||||
!B080 0D 28 04 D3 F2 18 ED 3E C3 D3 F3 CD 16 B1 C1 C9
|
||||
!B090 D5 C5 F5 78 F6 01 D3 F2 CD 16 B1 CD E8 B0 3E C5
|
||||
!B0A0 D3 F3 F1 4F 0C DB F3 CB 7F 20 FA CB 5F 20 1C 0D
|
||||
!B0B0 79 3D 28 06 DB F2 12 13 18 EB 3E 40 D3 F3 CD 16
|
||||
!B0C0 B1 DB F2 12 13 DB F3 CB 7F 20 FA 00 3E C3 D3 F3
|
||||
!B0D0 CD 16 B1 DB F2 CD 16 B1 12 C1 D1 C9 F5 DB F3 CB
|
||||
!B0E0 7F CD E7 02 20 F7 F1 C9 F5 DB F3 F5 CD E7 02 F1
|
||||
!B0F0 CB 47 28 F5 F1 C9 F5 C5 C1 C5 C1 0B 79 B0 C2 F7
|
||||
!B100 B0 F1 C9 E3 F5 C5 7E FE 00 28 06 CD B7 02 23 18
|
||||
!B110 F5 23 C1 F1 E3 C9 00 00 00 00 00 00 00 00 C9 DB
|
||||
!B120 F3 CB 47 C0 3E C3 D3 F3 00 00 18 F3
|
||||
!B000 CD 47 B1 3E 01 06 0A CD 4B B0 3E 01 06 0B CD 4B
|
||||
!B010 B0 3E 00 06 0C CD 4B B0 3E 00 06 0D CD 4B B0 3E
|
||||
!B020 A0 06 0E CD 4B B0 3E 20 06 0F CD 4B B0 21 02 50
|
||||
!B030 CD B5 B0 21 02 50 06 20 CD EE B1 C3 96 00 3E 80
|
||||
!B040 D3 33 3E 80 D3 32 00 AF D3 32 C9 F5 3E 80 D3 33
|
||||
!B050 F1 D3 30 78 E6 1F D3 32 F6 20 D3 32 00 78 E6 1F
|
||||
!B060 D3 32 00 AF D3 32 C9 3E 92 D3 33 78 E6 1F D3 32
|
||||
!B070 F6 40 D3 32 00 F5 F1 F5 F1 F5 F1 F5 F1 DB 30 F5
|
||||
!B080 AF D3 32 F1 C9 0E FF 06 0F CD 67 B0 CB 47 C2 E5
|
||||
!B090 B0 CB 5F 28 F2 3E 92 D3 33 3E 08 D3 32 F6 40 D3
|
||||
!B0A0 32 00 00 00 DB 31 77 23 DB 30 77 23 79 B7 CA B4
|
||||
!B0B0 B0 0D 18 D3 C9 0E FF 06 0F CD 67 B0 CB 47 C2 E5
|
||||
!B0C0 B0 CB 5F 28 F2 3E 92 D3 33 3E 08 D3 32 F6 40 D3
|
||||
!B0D0 32 00 00 00 DB 30 77 23 DB 31 77 23 79 B7 CA B4
|
||||
!B0E0 B0 0D 18 D3 C9 21 18 B1 CD BC 02 06 0F CD 67 B0
|
||||
!B0F0 CD E4 02 21 35 B1 CD BC 02 3A 00 50 CD E4 02 21
|
||||
!B100 3E B1 CD BC 02 06 09 CD 67 B0 CD E4 02 3E 0A CD
|
||||
!B110 B4 02 3E 0D CD B4 02 C9 0D 0A 44 69 73 6B 20 49
|
||||
!B120 2F 4F 20 65 72 72 6F 72 2E 20 53 74 61 74 75 73
|
||||
!B130 3A 20 30 78 00 20 44 65 76 3A 20 30 78 00 20 45
|
||||
!B140 72 72 3A 20 30 78 00 AF 32 00 50 32 01 50 F3 CD
|
||||
!B150 3E B0 21 A9 B1 CD BC 02 11 FF 1F 06 0F CD 67 B0
|
||||
!B160 B7 28 0B CB 77 20 0E 1B 7A B3 28 02 18 ED 21 DA
|
||||
!B170 B1 CD BC 02 C9 21 B9 B1 CD BC 02 06 0F 3E EC CD
|
||||
!B180 4B B0 21 02 50 CD 85 B0 21 16 50 06 14 CD 88 B2
|
||||
!B190 21 D1 B1 CD BC 02 21 38 50 06 28 CD 88 B2 3E 0A
|
||||
!B1A0 CD B4 02 3E 0D CD B4 02 C9 0D 0A 53 65 65 6B 20
|
||||
!B1B0 48 44 44 20 2E 2E 2E 20 00 44 65 76 69 63 65 20
|
||||
!B1C0 46 6F 75 6E 64 21 0D 0A 53 65 72 69 61 6C 3A 20
|
||||
!B1D0 00 20 20 4E 61 6D 65 3A 20 00 6E 6F 20 64 72 69
|
||||
!B1E0 76 65 20 64 65 74 65 63 74 65 64 0D 0A 00 E5 21
|
||||
!B1F0 49 B2 CD BC 02 E1 78 B7 CA 48 B2 05 0E 10 7C CD
|
||||
!B200 E4 02 7D CD E4 02 3E 20 CD B4 02 7E CD E4 02 3E
|
||||
!B210 20 CD B4 02 23 0D 20 F3 C5 E5 06 00 0E 10 ED 42
|
||||
!B220 7E 23 FE 20 DA 31 B2 FE 7F D2 31 B2 CD B4 02 18
|
||||
!B230 05 3E 2E CD B4 02 0D C2 20 B2 E1 C1 3E 0A CD B4
|
||||
!B240 02 3E 0D CD B4 02 18 AE C9 0D 0A 42 41 53 45 20
|
||||
!B250 30 20 20 31 20 20 32 20 20 33 20 20 34 20 20 35
|
||||
!B260 20 20 36 20 20 37 20 20 38 20 20 39 20 20 41 20
|
||||
!B270 20 42 20 20 43 20 20 44 20 20 45 20 20 46 20 20
|
||||
!B280 41 53 43 49 49 0D 0A 00 7E 23 CD B4 02 10 F9 C9
|
||||
!B290 F5 F1 F5 F1 C9
|
||||
|
||||
Reference in New Issue
Block a user