7112
UTILITAIRE -> Outils pour disquettes et cassettes
© Arkos (2005)
 
 
 
Arkos Disk Writter V1.0
FDC Tools
cpc
 
 

NOTICE / MANUAL

TXT (3)

NOTICE TEXTE n° 1 (2.6 Ko)

Arkos Disk Writter V1.0 ----------------------- By Targhan/Arkos Ce disc contient un utilitaire et des sources pour charger des fichiers sans passer par l'AMSDOS, ce qui peut s'averera tres pratique pour les programmeurs de part le monde. Deux utilitaires : READAMSD.MXM/DAM et DISK. READSCTS.MXM/DAM READAMSD -------- Ce source, a assembler avec MAXAM ou DAMS, vous permet de charger n'importe quel fichier binaire AMSDOS (sauvegarde sous Basic, par exemple), sans utiliser le systeme ou quelque routine ROM que ce soit. Ce peut etre tres utile si vous travaillez sur un jeu ou une demo avec de multiples fichiers, mais ne voulez pas vous embarraser a gerer une FAT par vous meme. Pour resumer, c'est exactement comme utiliser les vecteurs #bc77/bc83, mais le rendu sera plus rapide, aucun buffer n'est utilise et vous aurez la memoire entiere pour vous. Elle est pas belle, la vie ? Toutes les fonctions sont expliquees en detail dans le source. DISK and READSCTS ----------------- Ces deux la sont pour les utilisateurs avances. Vous pourrez utiliser un format 210k (10 secteurs par piste, secteurs de taille 2, 42 pistes). Puisque l'AMSDOS n'est pas capable de gerer de tels formats, vous allez devoir noter par vous meme (sur papier) l'organisation de vos fichiers. DISK vous permet de formater une face en 210k. Ensuite, toujours avec DISK, vous pourrez copier un fichier AMSDOS normal (64k max) vers la piste et le secteur de votre choix sur la face de destination. Quand la copie est finie, DISK vous precise combien de secteurs prend le fichier, et sur quel secteur et piste il se termine. NOTEZ CES INFORMATIONS SUR PAPIER !!! C'est indispensable, puisque vous devez vous souvenir quand commence votre fichier, et ou il s'arrete. Utiliser le format 210k est facile. Vous avez 42 pistes (0-41), chacune composee de 10 secteurs, nommes de &C1-&CA. Quand vous voudrez charger un fichier que vous aurez sauve avec DISK, utilisez le source READSCTS, a assembler avec MAXAM ou DAMS. Toutes les fonctions sont expliquees dans le source. Donnez lui le secteur/la piste de debut, combien de secteurs a lire, ou charger en memoire, et le code chargera votre fichier. Puis, avec un simple CALL, vous pourrez lancer votre production. Si vous utilisez ces sources et DISK, merci de le preciser quelquepart dans vos productions ! Les commentaires, remarques et rapports de bug sont biensur les bienvenus ! Vous pouvez me contacter ici : targhan@cpcscene.com contact@julien-nevo.com www.arkos.cpcscene.com www.julien-nevo.com/arkos Targhan.
 

NOTICE TEXTE n° 2 (11.35 Ko)

org #100 nolist ; ; ; FDC Code reading AMSDOS file ; Without system. ; V1.0 ; ; By Targhan/Arkos ; ; AMSDOS limitations still present. ; 9 2-sized sectors per track (c1-c9), one side. ; However, can read sectors up to 41 tracks ; (used by files copied with Disc'o'Magic, for example). ; ; Can't read ASCII files (who cares ?) ; ; ; Filename entered follow the format = ; AAAAAAAABBB ; Use upper case only. Do not put the '.'. ; ; ; ; Proper use = ; call FDCON to turn the drive ON ; ; ld a,drive (0-3) ; ld b,head (0-1) ; call FDCVARS to tell which drive to use, head to read. ; ; ld hl,FILENAME ; ld de,destination ; ld bc,buffer read below about it. ; call LOADFILE to load the file. ; Return = ; A=state. 0=ok 1=disc missing 2=read fail ; 3=file not found ; ; When you've loaded all the files you wanted = ; call FDCOFF ; ; You shouldn't need it, but... ; call RECALIBR ; to recalibrate the current drive (use FDCON ; and FDCVARS first !). AMSDOS does it when you turn ; the CPC on. You can also do it when an error disc ; happened, before trying loading the file again. ; ; That's it ! ; ; ; Notes ; - The 'buffer' of LOADFILE CAN be equal to DE. It is used ; to load one sector of the Directory. In the case you want ; to load a screen in #c000, you might want to set BC to ; another address, so that you don't see garbage at the ; beginning of the loading. ; - By changing the Head, you can read the file on the second ; side of a 3"5 disc. ; - Automatically skips the AMSDOS header. ; - Even if the file is not found, 512 bytes will be use ; from the 'destination' address. ; - The User of a file is ignored (who cares ?), except for deleted files. ; - No buffer is needed. ; - The interruptions are CUT by the loading code. ; - Interruptions are turned on when turning on the FDC, so ; put #c9fb in #38 before if you don't want your ; interruptions code to be run at this moment. ; - Some little tables are defined at the end. You can relocate ; them where you want if needed. ; ; ; ;Maximum number of direction entry of a file. *16 to get the maximum size ;loadable in KB. 4 should be more than enough (=64k). NBMAXENT equ 4 ; ;Track where the directory is. Some AMSDOS tweakings allow to use another one. DIRTRACK equ 0 ; ;First sector of the directory. DIRFSECT equ #c1 ; ; ; ; ; ;Some testing program ;Removing this when included this code to your own. ;---------------------------- di ld hl,#c9fb ld (#38),hl ; call FDCON ; xor a ld b,0 call FDCVARS ; ld hl,MYFILE ld de,#c000 ld bc,#c000 call LOADFILE jr nc,ERROR ; call FDCOFF ; ENDLESS jr ENDLESS MYFILE defb "IMG SCR" ; ERROR ld bc,#7f10 ;error out (c),c ld c,#4c out (c),c jr ENDLESS ;---------------------------- ; ; ; ; ;Tell which drive to use, head to read. ;A=drive (0-3) ;B=head (0-1) FDCVARS ld (FDCDRIVE),a ld c,a ld a,b ld (FDCHEAD),a rla rla and %100 or c ld (FDCIDDR),a ret ; ; ; ; ;Turn FDC on and wait a bit. FDCON LD A,(FDCMOTOR) OR A RET NZ INC A LD (FDCMOTOR),A LD BC,#FA7E LD A,1 OUT (C),A EI ;Wait for motor to get full speed LD B,6*30 WAIT HALT DJNZ WAIT DI RET ; ; ; ; ;Turn FDC off. FDCOFF XOR A LD (FDCMOTOR),A LD BC,#FA7E XOR A OUT (C),A RET ; ; ; ;Recalibrate current drive. RECALIBR call RECALIB2 call RECALIB2 ret RECALIB2 LD A,%00000111 CALL PUTFDC ld a,(FDCIDDR) CALL PUTFDC CALL WAITEND RET ; ; ; ; ; ;Load a file ;HL=Filename ;DE=Where to load it ;BC=#200 buffer ;RET=A=state. 0=ok 1=disc missing 2=read fail ;3=file not found LOADFILE ld (PTFILENM),hl LD (LOADWHER),DE ld (ADBUFFER),bc ; ; CALL BUILDTAB ret nc ; ld a,128 ld (SKIPBYTE+1),a ; ; ;Reading the file LD IX,TABSECTS LOADLP LD A,(IX+0) cp #ff jr z,LOADFOK cp #fe jr z,LOADNEXT LD B,(IX+1) push ix CALL READSECT pop ix ret nc ld (LOADWHER),hl ; ld hl,(TOREAD) ld a,l or h jr z,LOADFOK ; xor a ld (SKIPBYTE+1),a ; LOADNEXT inc ix inc ix jr LOADLP ; LOADFOK xor a scf ret ; ; ; ; ; ; ; ; ; ;Wait for the end of the current instruction (using ST0). WAITEND LD A,%00001000 CALL PUTFDC CALL GETFDC ;Get ST0 LD (ST0),A CALL GETFDC XOR A LD (ST1),A ;Reset ST1 and ST2 LD (ST2),A ; LD A,(ST0) BIT 5,A ;Instruction over ? JR Z,WAITEND RET ; ;Send data to FDC ;A=data PUTFDC ex af,af' LD BC,#FB7E PUTFD2 IN A,(C) JP P,PUTFD2 ex af,af' inc c OUT (C),A RET ; ;Get data from FDC ;Ret = A=FDC data GETFDC LD BC,#FB7E GETFD2 IN A,(C) JP P,GETFD2 inc c IN A,(C) RET ; ; ;Track change ;a=nb piste GOTOPIST PUSH AF LD A,%00001111 CALL PUTFDC LD A,(FDCIDDR) CALL PUTFDC POP AF CALL PUTFDC ; CALL WAITEND ; RET ; ; ;Read sector. ;A=track ;B=ID sector ;RET=A=state.Carry=1=ok A=0=ok 1=disc missing 2=read fail ;3=file not found ;HL=Where new data should be loaded (LOADWHER) READSECT LD (RSPIST+1),A PUSH BC CALL GOTOPIST ; LD A,%01000110 CALL PUTFDC LD A,(FDCIDDR) ;ID drive CALL PUTFDC RSPIST LD A,0 ;track CALL PUTFDC XOR A ;head CALL PUTFDC POP BC ;ID sect LD A,B PUSH AF CALL PUTFDC LD A,2 ;size CALL PUTFDC POP AF ;last sect to read CALL PUTFDC LD A,#52 ;GAP CALL PUTFDC LD A,#FF CALL PUTFDC ; LD BC,#FB7E ; SKIPBYTE ld a,0 ;If header, skip it or a jr z,RSAVLOOP ld e,a ; ld hl,BUFHEAD ;Read bytes to the header buffer. RSSKIPLP IN A,(C) ;FDC ready for transf ? JP P,RSSKIPLP AND %00100000 ;FDC performing ? JR Z,RSFIN ; INC C IN A,(C) ld (hl),a inc hl DEC C dec e jr nz,RSSKIPLP ; ld hl,(BUFHEAD+64) ;get filesize ld (TOREAD),hl ; ;Normal reading code. RSAVLOOP LD HL,(LOADWHER) ld de,(TOREAD) RSLOOP IN A,(C) ;FDC ready for transf ? JP P,RSLOOP AND %00100000 ;FDC performing ? JR Z,RSFIN ; INC C IN A,(C) LD (HL),A INC HL ; DEC C dec de ld a,e or d JR nz,RSLOOP ; ;Reading with saving. Done if end of file but sectors left. RSWASTE IN A,(C) ;FDC ready for transf ? JP P,RSWASTE AND %00100000 ;FDC performing ? JR Z,RSFIN ; INC C IN A,(C) DEC C JR RSWASTE ; ;Reading instr result RSFIN ld (TOREAD),de ; CALL GETFDC LD (ST0),A CALL GETFDC LD (ST1),A CALL GETFDC LD (ST2),A CALL GETFDC CALL GETFDC CALL GETFDC CALL GETFDC ; ; ;Test errors. ;ret= Carry=1=ok a=0=ok a=1=disc missing 2=read fail ;ute ST0, ST1, ST2 LD A,(ST0) BIT 7,A JR NZ,TESTEJEC ;no disc BIT 3,A JR NZ,TESTEJEC ;no disc BIT 4,A JR NZ,TESTFAIL ;Read fail ; LD A,(ST1) AND %00110111 JR NZ,TESTFAIL ; LD A,(ST2) AND %00110000 JR NZ,TESTFAIL ; TESTNOE XOR A scf ret TESTEJEC LD A,1 or a ret TESTFAIL LD A,2 or a ret ERRFNF LD A,3 or a ret ; ; ; ; ; ; ;Search a file in the AMSDOS directory, and ;build the sector table. ;RET=A=state. 0=ok 1=disc missing 2=read fail ;3=file not found .BUILDTAB ld a,DIRFSECT ld (BTSECT+1),a add a,4 ld (BTESECT+1),a xor a ld (FILFOUND),a ld (SKIPBYTE+1),a ; ld hl,#ffff ld (TOREAD),hl ; ; ld hl,TABSECTS ld de,TABSECTS+1 ld bc,TABSECTF-TABSECTS-1 ld (hl),#fe ldir ; ; BTLOOP ld a,DIRTRACK BTSECT ld b,#c1 call READSECT ret nc ; ld hl,(ADBUFFER) ld (BTBUFF+1),hl ; ;Search in the loaded sector the right entry(ies) ld b,16 BTENTLP push bc LD HL,(PTFILENM) BTBUFF ld de,0 ld a,(de) cp #e5 ;ignore deleted files jr z,BTNEXT inc de CALL CMP call C,BTFOUND ; BTNEXT ld hl,(BTBUFF+1) ld de,32 add hl,de ld (BTBUFF+1),hl ; pop bc djnz BTENTLP ;Next sector ld a,(BTSECT+1) inc a ld (BTSECT+1),a BTESECT cp #c5 jr nz,BTLOOP ; ld a,(FILFOUND) or a jr z,BTNOFND xor a scf ret ; BTNOFND ld a,3 ;File not found ret ; ; ; ;Right entry found. BTFOUND ld a,1 ld (FILFOUND),a ; ld ix,(BTBUFF+1) ld a,(ix+12) ;Get block number ld l,a ;Calcule where to code the track+sect ld h,0 ;in the tabsects add hl,hl add hl,hl add hl,hl add hl,hl add hl,hl add hl,hl ld de,TABSECTS add hl,de ex de,hl defb #fd : ld l,e defb #fd : ld h,d ; ld de,16 add ix,de ; ;ix=source ;iy=dest call CONV ; ret ; ; ; ; ; ;Compare two strings. 7th bit to 0. ;DE= buffer HL=filename ;RET= Carry=OK CMP LD B,11 ; CM2 LD A,(DE) RES 7,A CP (HL) JR NZ,CMPNOT INC HL INC DE DJNZ CM2 SCF RET CMPNOT OR A RET ; ; ;Convert block table to table of tracks+sects ;IX=src IY=dest CONV ld b,16 ;Reading 16 blocks max CVNEXT ld a,(ix+0) ;read block number or a ret z inc ix ; push bc ; LD L,A LD H,0 ADD HL,HL CALL DIV9 LD (iy+0),c ;get track ; ; sect1 ; LD HL,(RESTE) LD A,L add a,DIRFSECT LD (iy+1),A ; ; sect2 ; INC A CP #CA JR NZ,CVP2 LD A,#C1 INC C CVP2 LD (iy+2),C LD (iy+3),A ld de,4 add iy,de ; pop bc djnz CVNEXT ret ; ; ; DIV9 LD DE,9 ;Not optimised. Who cares ? LD C,0 DIV91 OR A SBC HL,DE JR C,DIV92 INC C JR DIV91 DIV92 ADD HL,DE LD (RESTE),HL RET ; ; FDCMOTOR defb 0 ;Drive motor (0-1) FDCDRIVE defb 0 ;Drive used (0-3) FDCHEAD defb 0 ;Head used (0-1) FDCIDDR defb 0 ;Drive ID. ST0 DEFB 0 ST1 DEFB 0 ST2 defb 0 FILFOUND defb 0 RESTE DEFW 0 ; LOADWHER defw 0 ;Where to load the file ADBUFFER defw 0 ;#200 buffer PTFILENM defw 0 ;Point on the filename TOREAD defw 0 ;Size (decrease) ; ; ;Table where is build the sector table. ;One directory entry can contain 16 blocks, hence '16' ;One block=2 sectors, each one defined by a track+sect ID. Hence the '*4'. TABSECTS DEFS 16*4*NBMAXENT,#fe TABSECTF DEFW #FFFF ; BUFHEAD defs 128,0 ;Header put here ; list ;*** End FDC code nolist
 

NOTICE TEXTE n° 3 (7.02 Ko)

org #100 nolist ; ; ; FDC Code reading a load of sectors ; and files written with Arkos Disk Writter. ; Without system. ; V1.0 ; ; By Targhan/Arkos ; ; Format used by 'Arkos Disk Writter' ; 10 2-sized sectors per track (c1-ca), 42 tracks (0-41) ; ; ; ; ; Proper use = ; call FDCON to turn the drive ON ; ; ld a,drive (0-3) ; ld b,head (0-1) ; call FDCVARS to tell which drive to use, head to read. ; ; ld a,nb sectors to read ; ld b,beginning track (0-41) ; ld c,beginning sector (#c1-#ca) ; ld hl,where to load ; call LOADSCTS to load the sectors ; Return = ; A=state. 0=ok 1=disc missing 2=read fail ; ; When you've loaded all the files you wanted = ; call FDCOFF ; ; ; ; You shouldn't need it, but... ; call RECALIBR ; to recalibrate the current drive (use FDCON ; and FDCVARS first !). AMSDOS does it when you turn ; the CPC on. You can also do it when an error disc ; happened, before trying loading the file again. ; ; That's it ! ; ; ; Notes ; - By changing the Head, you can read the file on the second ; side of a 3"5 disc. ; - No buffer is needed. ; - The interruptions are CUT by the loading code. ; - Interruptions are turned on when turning on the FDC, so ; put #c9fb in #38 before if you don't want your ; interruptions code to be run at this moment. ; ; ; ;Maximum number of direction entry of a file. *16 to get the maximum size ;loadable in KB. 4 should be more than enough (=64k). NBMAXENT equ 4 ; ;Track where the directory is. Some AMSDOS tweakings allow to use another one. DIRTRACK equ 0 ; ;First sector of the directory. DIRFSECT equ #c1 ; ; ; ; ; ;Some testing program ;Removing this when included this code to your own. ;---------------------------- di ld hl,#c9fb ld (#38),hl ; call FDCON ; xor a ld b,0 call FDCVARS ; ld a,32 ;nb sectors to read ld b,0 ;beginning track (0-41) ld c,#c1 ;beginning sector (#c1-#ca) ld hl,#c000 ;where to load call LOADSCTS jr nc,ERROR call FDCOFF ; ENDLESS jr ENDLESS ; ERROR ld bc,#7f10 ;error out (c),c ld c,#4c out (c),c jr ENDLESS ;---------------------------- ; ; ; ; ; ; ;Tell which drive to use, head to read. ;A=drive (0-3) ;B=head (0-1) FDCVARS ld (FDCDRIVE),a ld c,a ld a,b ld (FDCHEAD),a rla rla and %100 or c ld (FDCIDDR),a ret ; ; ; ; ;Turn FDC on and wait a bit. FDCON LD A,(FDCMOTOR) OR A RET NZ INC A LD (FDCMOTOR),A LD BC,#FA7E LD A,1 OUT (C),A EI ;Wait for motor to get full speed LD B,6*30 WAIT HALT DJNZ WAIT DI RET ; ; ; ; ;Turn FDC off. FDCOFF XOR A LD (FDCMOTOR),A LD BC,#FA7E XOR A OUT (C),A RET ; ; ; ;Recalibrate current drive. RECALIBR call RECALIB2 call RECALIB2 ret RECALIB2 LD A,%00000111 CALL PUTFDC ld a,(FDCIDDR) CALL PUTFDC CALL WAITEND RET ; ; ; ; ;Load sectors in memory. ;ld a,nb sectors to read ;ld b,beginning track (0-41) ;ld c,beginning sector (#c1-#ca) ;ld hl,where to load ;Return = ;A=state. 0=ok 1=disc missing 2=read fail LOADSCTS ld (LOADWHER),hl ; ld (LSNBS+1),a ld a,b ld (LSTRACK+1),a ld a,c ld (LSSECT+1),a ; ; ;Reading the sectors LOADLP ; LSTRACK ld a,0 LSSECT ld b,0 ld hl,(LOADWHER) CALL READSECT ret nc ; LSNBS ld a,0 ;Nb sectors to read yet. dec a jr z,LOADFOK ld (LSNBS+1),a ; ld hl,(LOADWHER) ld de,#200 add hl,de ld (LOADWHER),hl ; ld a,(LSSECT+1) ;Go to next sector inc a cp #cb jr nz,LPNSF ld hl,LSTRACK+1 inc (hl) ld a,#c1 LPNSF ld (LSSECT+1),a ; jr LOADLP ; LOADFOK scf ret ; ; ; ; ; ; ;Wait for the end of the current instruction (using ST0). WAITEND LD A,%00001000 CALL PUTFDC CALL GETFDC ;Get ST0 LD (ST0),A CALL GETFDC XOR A LD (ST1),A ;Reset ST1 and ST2 LD (ST2),A ; LD A,(ST0) BIT 5,A ;Instruction over ? JR Z,WAITEND RET ; ;Send data to FDC ;A=data PUTFDC ex af,af' LD BC,#FB7E PUTFD2 IN A,(C) JP P,PUTFD2 ex af,af' inc c OUT (C),A RET ; ;Get data from FDC ;Ret = A=FDC data GETFDC LD BC,#FB7E GETFD2 IN A,(C) JP P,GETFD2 inc c IN A,(C) RET ; ; ;Track change ;a=nb piste GOTOPIST PUSH AF LD A,%00001111 CALL PUTFDC LD A,(FDCIDDR) CALL PUTFDC POP AF CALL PUTFDC ; CALL WAITEND ; RET ; ; ;Read sector. ;A=track ;B=ID sector ;RET=A=state.Carry=1=ok A=0=ok 1=disc missing 2=read fail ;3=file not found ;HL=Where new data should be loaded (LOADWHER) READSECT LD (RSPIST+1),A PUSH BC CALL GOTOPIST ; LD A,%01000110 CALL PUTFDC LD A,(FDCIDDR) ;ID drive CALL PUTFDC RSPIST LD A,0 ;track CALL PUTFDC XOR A ;head CALL PUTFDC POP BC ;ID sect LD A,B PUSH AF CALL PUTFDC LD A,2 ;size CALL PUTFDC POP AF ;last sect to read CALL PUTFDC LD A,#2A ;GAP CALL PUTFDC LD A,#FF CALL PUTFDC ; LD BC,#FB7E LD HL,(LOADWHER) ; RSLOOP IN A,(C) ;FDC ready for transf ? JP P,RSLOOP AND %00100000 ;FDC performing ? JR Z,RSFIN ; INC C IN A,(C) LD (HL),A INC HL ; DEC C jr RSLOOP ; ;Reading instr result RSFIN CALL GETFDC LD (ST0),A CALL GETFDC LD (ST1),A CALL GETFDC LD (ST2),A CALL GETFDC CALL GETFDC CALL GETFDC CALL GETFDC ; ; ;Test errors ;retour= Carry=1=ok a=0=ok a=1=disc missing 2=read fail ;use ST0, ST1, ST2 LD A,(ST0) BIT 7,A JR NZ,TESTEJEC ;no disc BIT 3,A JR NZ,TESTEJEC ;no disc BIT 4,A JR NZ,TESTFAIL ;Read fail ; LD A,(ST1) AND %00110111 JR NZ,TESTFAIL ; LD A,(ST2) AND %00110000 JR NZ,TESTFAIL ; TESTNOE XOR A scf ret TESTEJEC LD A,1 or a ret TESTFAIL LD A,2 or a ret ERRFNF LD A,3 or a ret ; ; ; ; FDCMOTOR defb 0 ;Drive motor (0-1) FDCDRIVE defb 0 ;Drive used (0-3) FDCHEAD defb 0 ;Head used (0-1) FDCIDDR defb 0 ;Drive ID. ST0 DEFB 0 ST1 DEFB 0 ST2 defb 0 LOADWHER defw 0 ;Where to load the file ; ; list ;*** End FDC code nolist
 



Goto Top
CPC-POWER/CPCSOFTS, programmation par Kukulcan © 2007-2024 tous droits réservés.
Reproduction sans autorisation interdite. Tous les titres utilisés appartiennent à leurs propriétaires respectifs.
Hébergement Web, Mail et serveurs de jeux haute performance