4bit sound format converter

Other misc things
Post Reply
stefano
Well known member
Posts: 2137
Joined: Mon Jul 16, 2007 7:39 pm

4bit sound format converter

Post by stefano »

https://github.com/z88dk/z88dk/tree/mas ... port/sound

For what I could observe trying to deal with 4bit audio tracks put quite a few people in trouble.
Part of the confusion is because of the WAV format, which changes the data encoding style depending on the bit resolution.

By the way, in many cases this converter should make it.
There are two different use cases for the analog audio streams, the 1bit PWM conversion (tends to be crap, you must try by tuning the audio data and check the results) and the read analogue output via DAC or messing with the volume control of a sound chip (e.g. the Commodore's SID).

Currently it is possible to get analog output on the CBM128, the SpecDrum interface, the Camputers Lynx, the Bondwell 12/14 and very few others.

The 1bit support works slightly better on faster CPUs, e.g. it's not very good on a Spectrum, it could be better on the SAM Coupè.
cborn
Well known member
Posts: 267
Joined: Tue Oct 06, 2020 7:45 pm

Re: 4bit sound format converter

Post by cborn »

thank you, that is for me an understandable piece off code in C
for zx spectrum i rewrote the wav2ay player, which is mono only. is 'strereo' 0 or 1 as a default use? since if it mentions 1 or 2 then you dont have to recalculate it, i supose and in case of quadro-phony you could set it to 4, perhaps. But if this is a standard cq default true/fasle then you have to recalc ofcourse.

wav2ay puts the result per fetch as a low nudge and a high nudge using 1 byte for 2 samples.
in my own ASM routine i state it differs in handeling time if you start with the high part against to low part off the byte, since the high part have to be rotated to the low part and that takes atleast 4x4 tstate per double-sample

another thing is that wav2ay uses a sliding curve to cut the amplitudes, you use the cut off part as a result with out placing it on that curve.
Image

i am still 'experimenting' with this but did not work on this for a while.
wav2ay does not cut sample rate i think
and PCMENC from MSX does it totaly different.
http://www.cborn.nl/zxfiles/wav2ay/
stefano
Well known member
Posts: 2137
Joined: Mon Jul 16, 2007 7:39 pm

Re: 4bit sound format converter

Post by stefano »

My C program does roughly the same work you do with SOX and wav2ay: it decodes a WAV file into a RAW format, 4bit unsigned (left nibble in a byte first, then the lower one). If the original wav is stereo then only the first audio channel is used. Resampling happens by simply trashing the extra data.

The playzb4() routines are MONO players working at about 8khz (the exact frequecy depends on the way the target routine was implemented).

A routine able to do the 4bit magic on the AY PSG is very welcome !
cborn
Well known member
Posts: 267
Joined: Tue Oct 06, 2020 7:45 pm

Re: 4bit sound format converter

Post by cborn »

do you mean the player itself ?
gasman wrote an z80 player based on amplitude
i rewrote it to a better and smoother playing
and i ported the pcmenc VPLAYER to zx spectrum standard
and
i wrote a 3channel wav player in zx spectrum z80 source
those all use both nibbles giving 2 samples per byte
the pcmenc actauly is very complex with tuning towards best playtime instead off bending any wave in perse that 1 hz.
i did NOT do such at all, in an type off C. sorry.
a lot off zx wave are made with the original wav2ay, so i supase thats the correct player to start with
after that my rewrite of wav2ayplayer and my 3sample player might be intresting to add aswell

this is gasmans PLAYER asm from WAV2AY:

Code: Select all

; sample player
; need 317 tstates per sample

	org 32768
	
	ld hl,33000	; start address of sample data
	ld bc,20007	; length of sample data, in bytes
	push bc
	
	ld a,7			; set bits 0-5 of AY register 7 so that all channels are fixed at 'high'
	ld bc,0xfffd	; output - this way the AY is not generating waveforms of its own, and
	out (c),a		; varying the volume (channels 8/9/10) creates our own wave output instead
	ld a,63
	ld b,0xbf
	out (c),a

	pop bc
	di			; disable interrupts, so that they don't mess with our carefully planned timings

samplelp
	push bc		; 11

	; get low 4 bits to use as the first volume level
	ld a,(hl)	; 7
	and 0x0f	; 7

	; delay 117ish tstates
	ld b,8		; 7
zzz2	djnz zzz2
	
	; output that volume level to channels 8/9/10
	ld bc,0xfffd	; 10
	ld d,8		; 7
	out (c),d	; 12
	ld b,0xbf	; 7
	out (c),a	; 12
	inc d		; 4
	ld b,0xff	; 7
	out (c),d	; 12
	ld b,0xbf	; 7
	out (c),a	; 12
	inc d		; 4
	ld b,0xff	; 7
	out (c),d	; 12
	ld b,0xbf	; 7
	out (c),a	; 12
	
	; get the next volume level from the high 4 bits
	ld a,(hl)	; 7	; start tstate count here
	srl a		; 8
	srl a		; 8
	srl a		; 8
	srl a		; 8

	; delay 152ish tstates
	ld b,11		; 7
zzz1	djnz zzz1
				; 8

	; output that volume level to channels 8/9/10
	ld b,0xff	; 7
	ld d,8		; 7
	out (c),d	; 12
	ld b,0xbf	; 7
	out (c),a	; 12
	inc d		; 4
	ld b,0xff	; 7
	out (c),d	; 12
	ld b,0xbf	; 7
	out (c),a	; 12
	inc d		; 4
	ld b,0xff	; 7
	out (c),d	; 12
	ld b,0xbf	; 4
	out (c),a	; 12
	
	; move on to next byte
	inc hl		; 6
	
	; loop if we haven't reached the end of the sample
	pop bc		; 11
	dec bc		; 6
	ld a,b		; 4
	or c		; 4
	jr nz,samplelp	; 12

	ei
	ret
	

this is my own player which has SPEED possibility
www.cborn.nl/zxfiles/wav2ay/nwAY1ch065.zip

Code: Select all

;; WavPlayer... from wav2AY
;ALTERED player part by Chris Born, Rotterdam 2015/../2018

; wav2ay uses
;RUNWAIT("sox input.wav -r 11025 -b -u -c1 Output.raw",@ScriptDir,@SW_HIDE )
;now      sox input.wav -r 12489 -b 8 -e unsigned -c1 Output.raw ??

; this wavplayer is actualy a 1 channel player that uses all 3 AY music channels for ZX Spectrum
; this triples the sound volume. the samples are 4bit values giving 16 states of soundvolume settings.
; 3x16 is 48 states in steps off 3 becouse the 3 channels are used equaly, as said before, indeed, tree ;-)

delay equ 1   ; 0 to 255 assemble a DELAY routine which costs at least 15 tstate per samples >> 2+13*B_reg extra  2+13*1=15 to 2+13*256=3330
delay_B  equ 1
; key   equ 1   ; assemble a KEY check routine which will cost 40 tstate
; key NOW is part off the second delay trap

 	ORG 32768

MainLoop:
        exx             ; alt_reg
        push hl         ; save BASIC link
        CALL ORGZSND    ;; ORGANIZE PACKED DATA FROM ADDRTABLE
                        ;; (ASSUMES 'WAV'  has been poked with Sample TO PLAY)

        CALL DEPACKER   ;; UNZIP THE SAMPLE (ASSUMES HL & DE)

        CALL PLAYWAV   ;; Plays the WAV

        pop hl          ; restore BASIC link
        exx             ; norm_reg
        RET             ;; THATS IT FOLKS, THATS YOUR MAIN ROUTINE DONE!
        
ORGZSND:
        ;; ORGANIZE SOUND SAMPLE DATA ACCORDING TO ADDRTABLE OFFSETS
        ;; INPUT Poke 'WAV' with SAMPLE number first
        ;; OUTPUTS HL=ADDRESS OF SAMPLE, DE=DESTINATION OF WHERE TO DUMP IT
        ;; THEN ACTUALLY DUMPS THE PACK INTO THE UNPACKED AREA (ADDRESS DE)

        LD DE,WAV
        LD A,(DE)

        SLA     A               ; DOUBLE THE CONTENTS OF A (A*2)
        LD DE, ADDRTABLE-2      ; COS WE'RE STARTING COUNT AT 1 (*2), NOT AT ZERO
        ;ADDING A TO DE NOW     ; TO GET SND ADDRESS TABLE OFFSET
        ADD A,E
        LD E,A                  ; DE NOW POINTS TO CORRECT ADDRTABLE OFFSET

         LD A,(DE)              ; WE NEED TO PEEK TWO VALUES NOW FROM
         LD L,A                 ; ADDRESS DE, & ADDRESS DE+1
         INC DE                 ; VALUE IS DUMPED INTO HL
         LD A,(DE)
         LD H,A
                                ;HL NOW HOLDS THE CONTENTS OF THE ADDR OF ADDRTABLE OFFSET,
                                ; THE CONTENTS OF WHICH POINT NOW TO SAMPLE

        LD DE,UNPACKED          ; ACTUALLY OFFSET TO 2 BYTES PRIOR THE MAIN WAV BUFFER
        RET                     ; BUT FINE FOR ANY OTHER DEPACKED DATA
        
DEPACKER:
        ;; INSERT YOUR FAV DEPACKER HERE (EG: EXOZIP OR MEGALZ)..
        ;; INPUT HL=LOCATION OF PACKED DATA, DE=WHERE YOU WANT TO DUMP IT
        ;; OUTPUT: THIS WILL DEPACK YOUR DATA & DUMP IT WHERE TOLD...
        ;; USING EXOZIP HERE...

deexo:          ld      ixh,128

                ld      b,52
                ld      iy,exo_mapbasebits
                push    de
exo_initbits:   ld      a,b
                sub     4
                and     15
                jr      nz,exo_node1

                ld      de,1            ;DE=b2
exo_node1:      ld      c,16
exo_get4bits:   call    exo_getbit
                rl      c
                jr      nc,exo_get4bits
                ld      (iy+0),c        ;bits(i)=b1

                push    hl
                inc     c
                ld      hl,0
                scf
exo_setbit:     adc     hl,hl
                dec     c
                jr      nz,exo_setbit
                ld      (iy+52),e
                ld      (iy+104),d      ;base(i)=b2
                add     hl,de
                ex      de,hl
                inc     iy

                pop     hl
                djnz    exo_initbits
                inc     c

exo_literalseq: pop     de
exo_literalcopy:ldir                    ;copy literal(s)
exo_mainloop:   ld      c,1
                call    exo_getbit      ;literal?
                jr      c,exo_literalcopy
                ld      c,255
exo_getindex:   inc     c
                call    exo_getbit
                jr      nc,exo_getindex
                ld      a,c             ;C=index
                cp      16
                ret     z
                jr      c,exo_continue
                push    de
                ld      d,16
                call    exo_getbits
                jr      exo_literalseq
exo_continue:   push    de
                call    exo_getpair
                push    bc
                pop     af
                ex      af,af'          ;lenght in AF'
                ld      de,512+48       ;1?
                dec     bc
                ld      a,b
                or      c
                jr      z,exo_goforit
                ld      de,1024+32
                dec     bc              ;2?
                ld      a,b
                or      c
                jr      z,exo_goforit
                ld      e,16
exo_goforit:    call    exo_getbits
                ld      a,e
                add     a,c
                ld      c,a
                call    exo_getpair     ;bc=offset
                pop     de              ;de=destination
                push    hl
                ld      h,d
                ld      l,e
                sbc     hl,bc           ;hl=origin
                ex      af,af'
                push    af
                pop     bc              ;bc=lenght
                ldir
                pop     hl              ;Keep HL, DE is updated
                jr      exo_mainloop    ;Next!

exo_getpair:    ld      iy,exo_mapbasebits
                ld      b,0
                add     iy,bc
                ld      d,(iy+0)
                call    exo_getbits
                ld      a,c
                add     a,(iy+52)
                ld      c,a
                ld      a,b
                adc     a,(iy+104)
                ld      b,a
                ret

exo_getbits:    ld      bc,0            ;get D bits in BC
exo_gettingbits:dec     d
                ret     m
                call    exo_getbit
                rl      c
                rl      b
                jr      exo_gettingbits

exo_getbit:     ld      a,ixh           ;get one bit
                add     a,a
                ld      ixh,a
                ret     nz
                ld      a,(hl)
                inc     hl
                rla
                ld      ixh,a
		ret

exo_mapbasebits:
                defs    156     ;tables for bits, baseL, baseH


; New Wave Player n_wAYv

;Based on wav2ay player
;my 64bits calculator has problems with decimal
;0xffffffffffffffff=1.844674407×10¹⁹. with a 'nine digit' max 9876543210.123456789
; sample player uses 317 tstates per sample =
; 1 tstate = 1/3,500,000 = 0.000,000,286 second on 48k spectrum, 1/3.500000=0.285714286 >>0.000000285714286
; 1 tstate = 1/3,546,900 = 0.000,000,282 second on 128k spectrum 1/3.546900=0.281936339 >>0.000000281936339

; 0.286 *  317 =  90.662 millisecond per sample on 48k spectrum
; 3500000/317 = 11041.009463722 = 11.041 khz 

; 0.282 *  317 =  89.394 millisecond per sample on 128k spectrum
; 3546900/317 = 11188.958990536 = 11.188 khz

; if 'bb2' is fully eliminated even shorter, 284 tstate seems possible
;but 'short samples need big data' is a zx problem...!!!
; on 128 , 3 channels
; 3546900/284 = 12489.084507042 = 12.489 khz
; on 128 , 1 channel, at 1/3 volume, which is soft sound indeed
; 3546900/195 = 18189.230769231 = 18.189 khz

; timing is a loop with 3 main parts:
; wavtime, 4bits being 'outed'
; worktime, prepare the music now called 'work'
; delaytime, fill the gabs until they are equal, now called 'long'
; 1 bytes holds 2 samples. we loop twice with 317 tstate
; 1st loop = wavtime + delaytime(big)
; 2nd loop = wavtime + worktime + delaytime(small)
; the more worktime, the smaller the delaytime as compensation


; OUT is contended, it takes 4+4+4=12 tstate OR 8+4+4=16 OR 8+8+4=20 OR 8+8+8=24
;                                               4+8+4    OR 8+4+8
;                                               4+4+8    OR 4+8+8
; ULA needs 6 from 8 tstates per ULA_step, it could take 6 tstate extra before OUT is executed anyway,would it

playex:  ; save start for direct use, HL alt needs to be saved for BASIC use.
        exx             ; alt_reg
        push hl         ; save BASIC link
        CALL PLAYWAV   ;; Plays the WAV

        pop hl          ; restore BASIC link
        exx             ; norm_reg
        RET             ;; THATS IT FOLKS, THATS YOUR MAIN ROUTINE DONE!

; 'AYreg' is the adres for the 14 byte AY register settings
PLAYWAV:
	  di                ; disable interrupts, so that they don't mess with our carefully planned timings
	  ld hl,AYreg
          call vox          ; set 'formant' or other preset sound

        ;; ACTUALLY PLAYS THE DATA
        ;; INPUT HL=START OF SAMPLE & BC=LENGTH OF SAMPLE PRIOR CALLING WPLAYER...

	  LD HL,UNPACKED+2   ;; NOTE YOUR SAM_LEN IS ONLY 2 BYTES
	  LD BC,(UNPACKED)   ;; PRIOR THE SAM_BUFFER WHERE ITS PLAYED..

          exx             ; 4t norm_reg , although thats relative. its just 'the other set'
          ld e,8          ; 7t
	  ld c,$fd        ; 7t
          ld hl,$ffbf     ; 10t
          exx             ; 4t alt_reg


; memorywise it would be good to have the PLAYER start at 32768
; meaning the next part should have an org off 32768 and all code BEFORE still should be in LOWER memory...decrunsh will be slower, true!!!
; but memory will have bigger uncontended DATABUFFER available..

WPLAYER: ;; EXTRA ENTRY POINT, IN CASE YOU WISH TO ASSUME OTHER HL/BC VALUES...
; time between 1st call and 2nd call MUST be 317 and full loop is entered here, but the TIMING ZERO PIONT comes later
samplelp:
          push bc         ;11t
	  ld e,2          ; 7t e counts down to loops for 2 nibbles
          xor a           ; 4t wipe high nibble since it will set SOME TONE in AY
work_1 equ 11+7+7+4 ; = 29
; YOU CAN NOT(!) USE  reg A   ANY FURTHER WHILE PLAYING !!!!!! use AF'; thats becouse 'RRD' is an destructive opcode !!!!; get 4 bits/1 nibble from (HL) to use as the first volume level
; timing starts HERE !, starting with the 'wavtime' part
c1	  rrd             ; 18  1st rotate A(HL) to LAH and  2nd rotate LAH to HLA; output that volume level to channels 8/9/10
; 1 channel=18+4+36+4+4+7= 73 tstate, 2 chan=62+36=109 and 3 chan=62+36+36=145t tstate wavtime

          exx             ; 4t norm_reg

ch_a	  ld d,e          ; 4
	  ld b,h          ; 4
	  out (c),d       ; 12 (or 24tC)
	  ld b,l          ; 4
	  out (c),a       ; 12 (or 24tC)  = 4+4+12+4+12 = 36

ch_b	  inc d           ; 4
	  ld b,h          ; 4
	  out (c),d       ; 12 (or 24tC)
	  ld b,l          ; 4
	  out (c),a       ; 12 (or 24tC)  =36

ch_c	  inc d           ; 4
	  ld b,h          ; 4
	  out (c),d       ; 12 (or 24tC)
	  ld b,l          ; 4
	  out (c),a       ; 12 (or 24tC)  =36

          exx             ; 4t alt_reg


IF (delay = 1 )
         bb2 equ $+1
          ld b,delay_B    ; 7t   default 1
loop      djnz loop       ; 1*13-5=8 t  minimum delayloop=15 tstate making 267 tstate 3546900/267=13284.269662921 =13.284khz
         delaytime equ 2+(13*delay_B)
ELSE
         delaytime equ 0
ENDIF
	  dec e           ; 4t loop 2 times for 2 RRD's, bin 10 to 01 and second to 00
	  jr z,work       ; 7t (+5 on jump)
wavtime  equ 18 +4 +36 +36 +36 +4 +delaytime +4 +7; =160

;delay to reach equal timing for both runs of loop 'e=2'
;IF (key = 1 )             ; keycheck build inside balance wait loop.
keytest   ex af,af'       ; 4t
          in    a,($fe)   ;11t port $00fe read keyboard CONTENDED !!!! 11 or 24 tstate!!
          cpl             ; 4t
          and   $1F       ; 7t filter ANY key touch with bin 11111
          jr   nz,rstore  ; 7t+5t jumping stops routine and thus timing ;-)
          ex af,af'       ; 4t
keytime equ 4+11+4+7+7+4
;ENDIF

;101-37=64 tstate delay, 6 bytes, exx=4t x2=8> '56 free tstate' left in 4bytes ??? 
          nop             ; 4t
          ld b,(hl)       ; 7t
          ld b,3          ; 7t
lop       djnz lop        ; (3*13)-5
;end delay
          jr c1           ; 12 t  2nd run of the play_loop, jump to timer start
        
long equ keytime+4+7+7+(3*13)-5+12  ;=  needed 101

;166+101=267 tstate 3546900/267=13284.269662921 =13.284khz


;keytouch gives early retreat from the loop, restore values, so wave stays intact.
rstore     ex af,af'       ; 4t
           rrd             ; 2nd rotate 
           rrd             ; 3rd rotate,A(HL), wav byte restored
           pop bc          ; stack balanced
           jr eisil        ; jump to end off routine

;work time is delaytime aswell
                          ;+12 t from jump (INSTEAD of 7t counted in 'keytest')
work:	   rrd             ;18t 3rd rotate (HL)A to A(HL); now reg A is 'FREE' again, until next RRD in the next loop
	   inc hl          ; 6t move on to next byte, 2 nibbles
           pop bc          ;10t pop down counter
	   dec bc          ; 6t
	   ld a,b          ; 4t
	   or c            ; 4t ;loop if we haven't reached the end of the sample
	   jr nz,samplelp  ;12t  =>
work_2     equ 12+18+6+10+6+4+4+12 ;= 72t  calculate work time delay
worktime   equ work_1 + work_2     ; = 29 + 72 = 101

loop_1 equ wavtime+worktime
loop_2 equ wavtime+long

eisil	   ei
silence    ld hl,silen  ; set Ay registers all to 0 for real silence
;hl points to 14 byte buffer at the BEGIN of the last compressed data block

vox	   ld c,$fd
	   ld d,0
xov                       ; set AY channels to preset Formant voice 
	   ld a,(hl)
	   ld b,$ff
	   out (c),d       ;
	   ld b,$bf
	   out (c),a       
	   inc hl
	   inc d           ; 13,12,..,2,1,0
           ld a,d
           cp 14
	   jr nz,xov       ; z/nz from dec d
           ret             ; return to basic or not

silen      defb 0,0,0,0,0,0,0,0,0,0,0,0,0,0  ; set all AY channels to zero 'silence'

;preset AY with a Formant voice chord, or any other full sized  AYregister group
; reg 7 should be/is usualy set to 63 !!!!
AYreg	   defb 0,0,0,0,0,0,0,63,0,0,0,0,0,0


WAV:				; WAV 
	   DEFB 1			; Set to =1 for 128k version, Else
				; change for the 48k version...

ADDRTABLE:

           DEFW SAMPLE1

include    fink_11025.asm


;; CALLED SUBROUTINES NOW FOLLOW...
UNPACKED:
SAM_LEN:
        ;; WHEN UNZIPPED, THE 2 BYTE ENCODING SAMPLE LENGTH GETS DUMPED HERE

           DEFW 0

SAM_BUFFER:
        ;; SAMPLES GET DUMPED HERE PRIOR PLAYING... (VAR LENGTH)


           END ;32768



;rrd=18t , 18x 3 = 54 t
;other methode?
;ld a,(hl)     ; 7t
;and %11110000 ; 7t
;rlca          ; 4t
;rlca          ; 4t
;rlca          ; 4t
;rlca          ; 4t  =7+7+4+4+4+4=30t

;ld a,(hl)     ; 7t
;and %00001111 ; 7t
;nop           ; 4t
;nop           ; 4t
;nop           ; 4t
;nop           ; 4t  =7+7+4+4+4+4=30t
;30+30=60
i use a lot off remark blabla
if you have questions please do so.
cborn
Well known member
Posts: 267
Joined: Tue Oct 06, 2020 7:45 pm

Re: 4bit sound format converter

Post by cborn »

could you possibly add an option to choose between 1 sample or 2 samples per byte?
that would be a nice feature
cborn
Well known member
Posts: 267
Joined: Tue Oct 06, 2020 7:45 pm

Re: 4bit sound format converter

Post by cborn »

if i find the sounds themself i put them here aswell

www.cborn.nl/zxfiles/nwAYrle80.7z

actualy i am at build 92/96 but got stuck somewhere
cborn
Well known member
Posts: 267
Joined: Tue Oct 06, 2020 7:45 pm

Re: 4bit sound format converter

Post by cborn »

Hi,
perhaps Bulba knows some C routines, here are loads off sources, but probably in asm
http://bulba.untergrund.net/progr_e.htm
cborn
Well known member
Posts: 267
Joined: Tue Oct 06, 2020 7:45 pm

Re: 4bit sound format converter

Post by cborn »

does any other AY related computer knows the PLAY command like on zx128?
https://worldofspectrum.org/ZXSpectrum1 ... 28p10.html

btw
the 1st example has a TYPO its A$ spelling, a zero were it should be an Oh, so it has to be
W 5 O 7
stefano
Well known member
Posts: 2137
Joined: Mon Jul 16, 2007 7:39 pm

Re: 4bit sound format converter

Post by stefano »

z88dk has a bit_play and a synth_play command, but it is not for the AY.
Microsoft BASIC, e.g. on the MSX had a play command, based on an internal macro language interpreter (called MCL) which was later ported to GWBASIC.
Were you suggesting to add something to z88dk?
cborn
Well known member
Posts: 267
Joined: Tue Oct 06, 2020 7:45 pm

Re: 4bit sound format converter

Post by cborn »

stefano wrote: Mon Nov 21, 2022 9:14 pm (..)
Were you suggesting to add something to z88dk?
i am not against it =D

i am not going to say that i should do that
i can TRY to start with the interpreter. its a string and that needs a reader and a big switch statement.
i know by now that i should NOT use apointer but wait until thats needed and
an array is already a kind off pointer!

so, i can try to start with a switch command
not a promise at all!
stefano
Well known member
Posts: 2137
Joined: Mon Jul 16, 2007 7:39 pm

Re: 4bit sound format converter

Post by stefano »

..something like this, you mean?
https://github.com/z88dk/techdocs/blob/ ... asm#L17533

That was used for both DRAW and PLAY.
In theory a spectrum and an MSX are closer than an MSX and a PC compatible, but this macro language ran on both.

The entry used by PLAY:
https://github.com/z88dk/techdocs/blob/ ... asm#L24373

EDIT:
Probably it should be interesting to first try adding it to this:
https://github.com/z88dk/techdocs/blob/ ... ic.asm#L17

It's a restoration project of MBASIC.COM for CP/M, still valid to produce a byte identical program.
I merged few optional code branches in it to enable some of the graphics instructions on the Spectrum +3, including portions of the MSX BASIC, which fit perfectly. :cool:
cborn
Well known member
Posts: 267
Joined: Tue Oct 06, 2020 7:45 pm

Re: 4bit sound format converter

Post by cborn »

stefano wrote: Thu Nov 24, 2022 9:58 pm ..something like this, you mean?
https://github.com/z88dk/techdocs/blob/ ... asm#L17533

That was used for both DRAW and PLAY.
In theory a spectrum and an MSX are closer than an MSX and a PC compatible, but this macro language ran on both.
thats in practice already and not just by the z80 cpu but eg in the AY adressing routine... despite the 16b zx ports against the 8bit ports off msx the actual active sound command is equal in byte size and perfect interchangeble, afaik.
i have to check that again, but i think eg 'vortexplayer' showed that. i have to find that piece of code back so i can show it.

The entry used by PLAY:
https://github.com/z88dk/techdocs/blob/ ... asm#L24373

EDIT:
Probably it should be interesting to first try adding it to this:
https://github.com/z88dk/techdocs/blob/ ... ic.asm#L17

It's a restoration project of MBASIC.COM for CP/M, still valid to produce a byte identical program.
I merged few optional code branches in it to enable some of the graphics instructions on the Spectrum +3, including portions of the MSX BASIC, which fit perfectly. :cool:
thats a lot to read and i see its like the original microsoft macro ported to MSX ?
a ready to use string procesing routine only waiting for some nice input.
my asm is much much better then my C, so i have to read a lot first.
with the future switch command, the list it self is easy but how to create the result like the repeating of the whole string by a braket. thats a lot of adressing with a single chr$.
cborn
Well known member
Posts: 267
Joined: Tue Oct 06, 2020 7:45 pm

Re: 4bit sound format converter

Post by cborn »

LOADFP = file pointer and not floating point... ok
stefano
Well known member
Posts: 2137
Joined: Mon Jul 16, 2007 7:39 pm

Re: 4bit sound format converter

Post by stefano »

well, it is floating point instead

and.. it IS the Microsoft macro interpreter used in the original MSX BASIC.
If adapted to the CP/M BASIC it will probably work on a Spectrum.. or on an CPC or ..on a MSX 🤣

An intermediate backport could help in familiarizing with the code and insulating the necessary code portions. a later step would involve a study to replace the string and maths and timer calls, I don't think they are many.
cborn
Well known member
Posts: 267
Joined: Tue Oct 06, 2020 7:45 pm

Re: 4bit sound format converter

Post by cborn »

hmm , it assembled addresses i think, probably i am wrong or read a different spot.

the zx play command is determint in ROM0
https://github.com/ZXSpectrumVault/rom- ... 8_ROM0.asm

it gives:

Code: Select all

; =====================
; PLAY COMMAND ROUTINES
; =====================
; Up to 3 channels of music/noise are supported by the AY-3-8912 sound generator.
; Up to 8 channels of music can be sent to support synthesisers, drum machines or sequencers via the MIDI interface,
; with the first 3 channels also played by the AY-3-8912 sound generator. For each channel of music, a MIDI channel
; can be assigned to it using the 'Y' command.
;
; The PLAY command reserves and initialises space for the PLAY command. This comprises a block of $003C bytes
; used to manage the PLAY command (IY points to this command data block) and a block of $0037 bytes for each
; channel string (IX is used to point to the channel data block for the current channel). [Note that the command
; data block is $04 bytes larger than it needs to be, and each channel data block is $11 bytes larger than it
; needs to be]
;
; Entry: B=The number of strings in the PLAY command (1..8).

; -------------------------
; Command Data Block Format
; -------------------------
; IY+$00 / IY+$01 = Channel 0 data block pointer. Points to the data for channel 0 (string 1).
; IY+$02 / IY+$03 = Channel 1 data block pointer. Points to the data for channel 1 (string 2).
; IY+$04 / IY+$05 = Channel 2 data block pointer. Points to the data for channel 2 (string 3).
; IY+$06 / IY+$07 = Channel 3 data block pointer. Points to the data for channel 3 (string 4).
; IY+$08 / IY+$09 = Channel 4 data block pointer. Points to the data for channel 4 (string 5).
; IY+$0A / IY+$0B = Channel 5 data block pointer. Points to the data for channel 5 (string 6).
; IY+$0C / IY+$0D = Channel 6 data block pointer. Points to the data for channel 6 (string 7).
; IY+$0E / IY+$0F = Channel 7 data block pointer. Points to the data for channel 7 (string 8).
; IY+$10          = Channel bitmap. Initialised to $FF and a 0 rotated in to the left for each string parameters
;                   of the PLAY command, thereby indicating the channels in use.
; IY+$11 / IY+$12 = Channel data block duration pointer. Points to duration length store in channel 0 data block (string 1).
; IY+$13 / IY+$14 = Channel data block duration pointer. Points to duration length store in channel 1 data block (string 2).
; IY+$15 / IY+$16 = Channel data block duration pointer. Points to duration length store in channel 2 data block (string 3).
; IY+$17 / IY+$18 = Channel data block duration pointer. Points to duration length store in channel 3 data block (string 4).
; IY+$19 / IY+$1A = Channel data block duration pointer. Points to duration length store in channel 4 data block (string 5).
; IY+$1B / IY+$1C = Channel data block duration pointer. Points to duration length store in channel 5 data block (string 6).
; IY+$1D / IY+$1E = Channel data block duration pointer. Points to duration length store in channel 6 data block (string 7).
; IY+$1F / IY+$20 = Channel data block duration pointer. Points to duration length store in channel 7 data block (string 8).
; IY+$21          = Channel selector. It is used as a shift register with bit 0 initially set and then shift to the left
;                   until a carry occurs, thereby indicating all 8 possible channels have been processed.
; IY+$22          = Temporary channel bitmap, used to hold a working copy of the channel bitmap at IY+$10.
; IY+$23 / IY+$24 = Address of the channel data block pointers, or address of the channel data block duration pointers
;                   (allows the routine at $0A6E (ROM 0) to be used with both set of pointers).
; IY+$25 / IY+$26 = Stores the smallest duration length of all currently playing channel notes.
; IY+$27 / IY+$28 = The current tempo timing value (derived from the tempo parameter 60..240 beats per second).
; IY+$29          = The current effect waveform value.
; IY+$2A          = Temporary string counter selector.
; IY+$2B..IY+$37  = Holds a floating point calculator routine.
; IY+$38..IY+$3B  = Not used.

; -------------------------
; Channel Data Block Format
; -------------------------
; IX+$00          = The note number being played on this channel (equivalent to index offset into the note table).
; IX+$01          = MIDI channel assigned to this string (range 0 to 15).
; IX+$02          = Channel number (range 0 to 7), i.e. index position of the string within the PLAY command.
; IX+$03          = 12*Octave number (0, 12, 24, 36, 48, 60, 72, 84 or 96).
; IX+$04          = Current volume (range 0 to 15, or if bit 4 set then using envelope).
; IX+$05          = Last note duration value as specified in the string (range 1 to 9).
; IX+$06 / IX+$07 = Address of current position in the string.
; IX+$08 / IX+$09 = Address of byte after the end of the string.
; IX+$0A          = Flags:
;                     Bit 0   : 1=Single closing bracket found (repeat string indefinitely).
;                     Bits 1-7: Not used (always 0).
; IX+$0B          = Open bracket nesting level (range $00 to $04).
; IX+$0C / IX+$0D = Return address for opening bracket nesting level 0 (points to character after the bracket).
; IX+$0E / IX+$0F = Return address for opening bracket nesting level 1 (points to character after the bracket).
; IX+$10 / IX+$11 = Return address for opening bracket nesting level 2 (points to character after the bracket).
; IX+$12 / IX+$13 = Return address for opening bracket nesting level 3 (points to character after the bracket).
; IX+$14 / IX+$15 = Return address for opening bracket nesting level 4 (points to character after the bracket).
; IX+$16          = Closing bracket nesting level (range $FF to $04).
; IX+$17...IX+$18 = Return address for closing bracket nesting level 0 (points to character after the bracket).
; IX+$19...IX+$1A = Return address for closing bracket nesting level 1 (points to character after the bracket).
; IX+$1B...IX+$1C = Return address for closing bracket nesting level 2 (points to character after the bracket).
; IX+$1D...IX+$1E = Return address for closing bracket nesting level 3 (points to character after the bracket).
; IX+$1F...IX+$20 = Return address for closing bracket nesting level 4 (points to character after the bracket).
; IX+$21          = Tied notes counter (for a single note the value is 1).
; IX+$22 / IX+$23 = Duration length, specified in 96ths of a note.
; IX+$24...IX+$25 = Subsequent note duration length (used only with triplets), specified in 96ths of a note.
; IX+$26...IX+$36 = Not used.

L0985:  DI                ; Disable interrupts to ensure accurate timing.
,,,
the BASIC from zx spectrum allows 3 channels of PLAY command while MIDI accepts 8 channels. thats a different approach form me.
my own idear is not much more then a string muncher whith a coorect case on it.
my C is still very simple. i will have to use snippest of ASM and thats still a new chapter.
i am not against it.

this is a bunch off PSEUDO code like stuff. i have to start somewhere
default should be silence since if its going wrong you want to be quite about it (stupid pun indeed)
well, how to stop a disturpt sound? with silence, so if thats the next step, better make it default.
the 'vox' might be a player aka port-dump-loop if its split apart from 'silence' but there are many others possible.
and no, i dont know what i do now.

Code: Select all

//https://worldofspectrum.org/ZXSpectrum128Manual/sp128p10.html

#include <stdio.h>
#include <stdlib.h>
#include <string.h>

// PSEUDO CODE
/*
silence   ld hl,0xffbf      ; 10t
          ld c,0xfd         ;  7t
          ld e,7           ;  7t
          ld b,h           ;  4t
          out (c),e        ; 12t
          in a,(c)         ; 12t
          or %00111111     ;  7t
          ld b,l           ;  4t
          out (c),a        ; 12t %xx111111
          xor a            ;  4t
          
xv1       dec e            ;  4t
          ld b,h           ;  4t
	  out (c),e        ; 12t
	  ld b,l           ;  4t
          out (c),a        ; 12t
          jr nz,xv1        ; 12-5t
          ret              ; 10t
                           ;t= 10+7+7+4+12+12+7+4+12+4 + 6*(4+4+12+4+12+12)-5+10 = 372t
*/


void play_silence(){

inline asm // ZX SPECTRUM

vox         ld a,6          ; last  reg PORT
	    ld d,255        ; first reg PORT-1
            ld e,0          ; VALUE to set
            call xov

            inc a           ; a=7
          ld b,0xff        ;  7t
          out (c),a        ; 12t
          in a,(c)         ; 12t
          or %00111111     ;  7t
            ld e,a         ; %00111111 > bit 6+7 are set to READ keyboard instead of OUTing TO
            call xov        ; d=6

            ld a,13         ; very last AYreg
            ld e,0          ; e=0 d=7


xov         inc d           ; 4t start with 255 for 0
xov1	    ld bc,$fffd     ;10t
	    out (c),d       ;12t
	    ld b,$bf        ; 7t
	    out (c),e       ;12t
            cp d            ; 4t d=6 is used and then checked on reg_a
	    jp nz,xov       ;10t if a <> d then next AY_register
            ret             ;10t return to basic or not
end_asm
return 0 ;
}

void play_ay( char file )
{

switch ( char note )

case '!':               //  Enclose a comment
         break;         // just increase adres until NEXT '!' found, then +1 for next CASE


case 'b':               //  Gives pitch of note within current octave range
case 'B':

case 'c':               //  Gives pitch of note within current octave range
case 'C':
         break;

case '$':	       //  Flattens note following it
         break;

case '#':	       //  Sharpens note following it
         break;

case 'O':	       //  Followed by number 0 to 8 sets current octave range
         fetch_octave(char note++);
         set_octave();
         break;

case '1':       //  Sets length of notes
case '2':
case '3':
case '4':
case '5':
case '6':
case '7':
case '8':
case '9':
case '10':      // TWO chars to fetch! 
case '11':      // TWO chars to fetch! 
case '12':      // TWO chars to fetch!
         break;

case '&':	       //  Denotes a rest
         break;

case 'N':	       //  Separates two numbers
         break;

case 'V':               //  Followed by a number 0 to 15 sets volume of notes
         break;

case 'W':               //  Followed by a number 0 to 7 sets volume effect
         break;

case 'U':               //  Turns on volume effect in any string
         break;

case 'X':               //  Followed by a number 0 to 65535 sets duration of volume effect
         break;

case 'T':               //  Followed by a number from 60 to 240 sets tempo of music
         break;

case '(':               // Enclose repeated phrase, which can be repeated!! nonsence (U2(U3(ABO2AD))X)H
case ')':               // fetch a SUBSTRING and return after playing it in the upper-level(susb)string
         break;


case 'H':               //  Stops a PLAY command
         play_silence();
         break;

case 'M':               //  Followed by a number from 1 to 63 selects channels
         break;

case 'Y':               //  Followed by a number from 1 to 16 turns on a MIDI channel
         break;

case 'Z':               //  Followed by a number sends that number as a MIDI programming code
         break;         //  SENDING involves rs232 or other PORTS to OTHER devices !!!


default :               // the default action is silence, without string or empty string it does nothing.
         play_silence();
}
cborn
Well known member
Posts: 267
Joined: Tue Oct 06, 2020 7:45 pm

Re: 4bit sound format converter

Post by cborn »

its not 4bit at all
and this is pseudo aswell

Code: Select all

case '!':               //  Enclose a comment
         while(note!="!")note++;
         break;         // just increase adres until NEXT '!' found, then +1 for next CASE
maybe a separate tread for that ay_player is a bit better??
Post Reply