VOGONS


First post, by Lassar

User metadata
Rank Newbie
Rank
Newbie

😳
I was messing around with a PowerBasic Version of DmaPlay.bas

I finally got it to work. Then I decided to get rid of a bunch of subroutines I was not using.

It stopped working in DosBox. It was still working very good under XP. I started to compare the differences between this version to a previous version that worked in DosBox.

I finally narrowed down the diffence that caused it to stopped working
under DosBox.

All I had done was to take out routines I was not using. Nothing else.

Talk about a unusual bug.

If you doubt me here is the code.

'---------------------------------------------------------------------------
' DMA Play 6.0 Beta Build 11.10.98: released for beta testing ONLY!
' a versatile DMA-based sound (.WAV) file player in QBasic and QB45.
' by Mike Huff (v1), Martin Rampersad (v2), Toshi Horie (v3,4,5,6)
' Realtime 16-bit to 8-bit stereo/mono conversions added up to 44Khz
' Realtime 16-bit and 8-bit mixing possible on Pentium 120Mhz+.
' Program downloaded from http://www.ocf.berkeley.edu/~horie/project.html
' ------------- programming notes ----------------
' Thanks: * Ethan Brodsky, who made DMAPLAY4+ possible.
' * Angelo Mottola for his support and testing on SB16.
' * Michael Sorensen for his brilliant ideas and feedback.
' Features: * 8-bit and 16-bit 2 channel mixing.
' * Tested with an SB Pro and SB AWE32.
' * simplified calling scheme: PlayWave Filename$
' * new 8-bit 'generic DMA' handler for SB16.
' * bugfix: Now all files tested finish playing.
' Future Plans* complete 8 channel mixer routine
' * EMS sound buffer swapping support
' * interrupt and autoinit mode support (thanks to Michael)
' Legal: * Toshihiro Horie will not be liable for any damages
' resulting from the use or misuse of this program.
'---------------------------------------------------------------------------
OPTION BINARY BASE 1
DEFINT A-Z
$STATIC
TYPE WaveInfoType
StereoWav AS INTEGER
Freq AS LONG
Length AS LONG
playtime AS DOUBLE
sixteenbit AS INTEGER
END TYPE

TYPE WaveHeaderType
RiffID AS STRING * 4 'should be 'RIFF'
RiffLength AS LONG
'rept. chunk id and size then chunk data
WavID AS STRING * 4 'should be 'WAVE'
FmtID AS STRING * 4
FmtLength AS LONG
'FMT ' chunk - common fields
wavformattag AS INTEGER ' word - format category e.g. 0x0001=PCM
Channels AS INTEGER ' word - number of Channels 1=mono 2=stereo
SamplesPerSec AS LONG 'dword - sampling rate e.g. 44100Hz
avgBytesPerSec AS LONG 'dword - to estimate buffer size
blockalign AS INTEGER ' word - buffer size must be int. multiple of this
FmtSpecific AS INTEGER ' word
DataID AS STRING * 4
DataLength AS LONG
END TYPE

DECLARE SUB PlayWave (Filename$)
DECLARE SUB getWaveInfo ()
DECLARE FUNCTION DMADone% (DMA16%, L??)
DECLARE FUNCTION ResetDSP% ()
DECLARE FUNCTION ReadDSP% ()
DECLARE FUNCTION ReadDAC% ()
DECLARE SUB VocVolume (Right1%, Left1%, Getvol%)
DECLARE SUB MasterVolume (Right1%, Left1%, Getvol%)
DECLARE SUB WriteDSP (Byte2%)
Show last 429 lines
DECLARE SUB SpeakerState (OnOff%)
DECLARE SUB DMAState (StopGo%)
DECLARE SUB DMAPlay (Segment??, offset??, Length??, Freq&, StereoWav%)
DECLARE SUB GetBLASTER ()
DECLARE FUNCTION DSPVersion! ()

SHARED Baseport%, LenPort%, DMA%, DMA16%, IRQ%, cardversion%, SoundLen??

Playerversion$ = "DMAPlay 6.0b"


DIM Wave AS WaveHeaderType
DIM WaveInfo AS WaveInfoType

SHARED Wave
SHARED WaveInfo


SCREEN 0: CLS
'WIDTH 80, 50
PRINT Playerversion$
PRINT "By Mike Huff (SB, SBPro) and Toshi Horie (SB16, SBPro realtime conv/mixing)"
PRINT "Modified By Martin Rampersad (To play entire file instead of first 32k)"
PRINT "Comments, etc. can be sent to MHuff@gnn.com or to Martin_Rampersad@juno.com"

Baseport% = &H220: IRQ% = 5: DMA% = 1: 'default
GetBLASTER ' Parses BLASTER environment

PRINT STRING$(80, 196)
Left1% = 12: Right1% = 12
ResetDSP%

SpeakerState 1
MasterVolume 20, 20, 0
VocVolume 20, 20, 0

'MasterVolume Right1%, Left1%, 1
PRINT "Master volume is set at: Right-"; Right1%; " Left-"; Left1%
'WavBuffer size MUST be divisible by 4 for stereo files
SoundLen?? = 65528

DIM STATIC WavBuffer&(16382)
SHARED WavBuffer&()


%HeaderSize = 45 'assume .WAV file (use 45 because 1st byte
PlayWave COMMAND$

DMAState 0: 'stop sound
Quit% = ResetDSP%

CLOSE
END

FUNCTION DMADone% (DMA16%, L??)
countlo% = INP( LenPort%)
counthi% = INP(LenPort%)
IF counthi% = 255 AND countlo% = 255 THEN
IF DMA16% THEN
ack16% = INP(Baseport% + &HF) 'ack to SB
'OUT &HA0, &H20 'acknowledge SB interrupt 8-15
'OUT &H20, &H20 'acknowledge SB interrupt 1-15
ELSE
ack% = INP(Baseport% + &HE)
'OUT &H20, &H20 'acknowledge SB interrupt 1-15
END IF
DMADone% = -1
'SOUND 300, .4
END IF
END FUNCTION

$SEGMENT
SUB DMAPlay (Segment??, offset??, Length??, Freq&, StereoWav%)
Length?? = Length?? - 1
page% = 0
Addr& = Segment?? * 16 + OffSet??

SELECT CASE DMA%
CASE 0
PgPort% = &H87
AddPort% = &H0
LenPort% = &H1
ModeReg% = &H48
CASE 1
PgPort% = &H83
AddPort% = &H2
LenPort% = &H3
ModeReg% = &H49
CASE 2
PgPort% = &H81
AddPort% = &H4
LenPort% = &H5
ModeReg% = &H4A
CASE 3
PgPort% = &H82
AddPort% = &H6
LenPort% = &H7
ModeReg% = &H4B
CASE ELSE
PRINT "8-bit DMA channels 0-3 only!": END
EXIT SUB
END SELECT
Lengthlo% = Length?? AND &HFF
Lengthhi% = (Length?? AND &HFF00&) \ &H100
OUT &HA, &H4 + DMA%: 'DMA channel to use (DRQ#)
OUT &HC, &H0
OUT &HB, ModeReg%
OUT AddPort%, Addr& AND &HFF: 'buffer address of sound data low byte
OUT AddPort%, (Addr& AND &HFF00&) \ &H100: 'high byte
IF (Addr& AND 65536) THEN page% = page% + 1: '64K pages for 8-bit DMA
IF (Addr& AND 131072) THEN page% = page% + 2
IF (Addr& AND 262144) THEN page% = page% + 4
IF (Addr& AND 524288) THEN page% = page% + 8
OUT PgPort%, page%: 'output page of phys. addr of sample block
OUT LenPort%, Lengthlo%: 'size of block to DMA controller -Low
OUT LenPort%, Lengthhi%: 'high byte
OUT &HA, DMA%: 'release DMA channel

LOCATE 21, 1: PRINT "seg:"; DEC2HEX$(Segment??),
PRINT "offset:"; DEC2HEX$(OffSet??), "addr:"; DEC2HEX$(addr&)

TimeConst% = 256 - 1000000 \ Freq&

IF Freq& < 22728 THEN
WriteDSP &H40
WriteDSP TimeConst%
WriteDSP &H14: '8 bit output over DMA
WriteDSP (Length?? AND &HFF)
WriteDSP ((Length?? AND &HFFFF&) \ &H100)
ELSE 'SBPro (DSP version 3.x) can play 8-bit mono/stereo wave files
IF cardversion% > 2 THEN
'high speed 8 bit output up to 44kHz mono or 22Khz stereo
WriteDSP &H40: 'output sampling rate const
WriteDSP TimeConst%
WriteDSP &H48
WriteDSP Lengthlo%
WriteDSP Lengthhi%
WriteDSP &H91
ELSE
PRINT "Current Freq&="; Freq&
PRINT "You need a Sound Blaster Pro to play at 8 bit high speed.": END
END IF
END IF
END SUB

SUB DMAState (StopGo%)
' Stops or continues DMA play.
IF StopGo% THEN WriteDSP &HD4 ELSE WriteDSP &HD0
END SUB

FUNCTION DSPVersion!
' Gets the DSP version.
WriteDSP &HE1
Temp% = ReadDSP%
temp2% = ReadDSP%
Temp$ = TRIM$(STR$(Temp%))
Temp2$ = TRIM$(STR$(Temp2%))

IF temp2% < 10 THEN
DSPVersion! = VAL(Temp$ + ".0" + Temp2$)
ELSE
DSPVersion! = VAL(Temp$ + "." + Temp2$)
END IF

'MODEL VERSION
'SB 1.0 1.?? (1.05???, err=2.00)
'SB 1.5 1.?? (1.05???)
'SB 2.0 2.xx (2.01)
'SB Pro 3.00 (???)
'SB Pro 2 3.01+ (3.01, 3.02)
'SB 16 4.0x (4.04, 4.05)
'SB 16 SCSI-2 4.11 (4.11)
'SB AWE 32 4.12+ (4.12)
END FUNCTION

SUB GetBLASTER
' This subroutine parses the BLASTER environment string
' and returns the sound card settings
' implicitly using COMMON variables Baseport%, DMA%, DMA16%

blaster$ = ENVIRON$("BLASTER")
IF LEN(blaster$) = 0 THEN
PRINT "BLASTER environment variable not set."
INPUT "Would you like to try the defaults? <y/n>"; ck$
IF ck$ = "Y" OR ck$ = "y" THEN
blaster$ = "A220 I5 D1 H5"
ELSE
PRINT "Goodbye."
END
END IF
ELSE
FOR index% = 1 TO LEN(blaster$)
SELECT CASE MID$(UCASE$(blaster$), index%, 1)
CASE "A"
Baseport% = VAL("&H" + MID$(blaster$, index% + 1, 3))
CASE "I"
IRQ% = VAL(MID$(blaster$, index% + 1, 1))
CASE "D"
DMA% = VAL(MID$(blaster$, index% + 1, 1))
CASE "H"
DMA16% = VAL(MID$(blaster$, index% + 1, 1))
END SELECT
NEXT
END IF
IF ResetDSP% = 0 THEN 'resets DSP (returns true if sucessful)

PRINT "Sound card NOT found at " + HEX$(Baseport%) + "H."
PRINT "Either your card is not SB-compatible or it is set up wrong."
END
END IF
PRINT "Sound Card DSP version:"; DSPVersion!
cardversion% = INT(DSPVersion!)
END SUB

SUB getWaveInfo
WaveInfo.Freq = Wave.SamplesPerSec
PRINT "SamplesPerSec:"; WaveInfo.Freq&
'assume no weird sampling rate like 9bit/sec
'PRINT "should equal blockalign:"; (Wave.avgBytesPerSec / Freq&)
PRINT "BlockAlign:"; Wave.blockalign
IF (SoundLen?? MOD Wave.blockalign) <> 0 THEN PRINT "Internal error: make SoundLen??=32752": END
PRINT "FmtSpecific:"; Wave.FmtSpecific; "bits/sample"
IF Wave.FmtSpecific = 16 THEN WaveInfo.sixteenbit = 1
'PRINT "DataID:"; Wave(0).DataID
IF UCASE$(Wave.DataID) <> "DATA" THEN PRINT "Not Data chunk": END
PRINT "DataLength:"; Wave.DataLength; "bytes"
WaveInfo.Length = Wave.DataLength
WaveInfo.playtime# = WaveInfo.Length / WaveInfo.Freq& / Wave.blockalign
pmin = INT(WaveInfo.playtime#) \ 60
psec = INT(WaveInfo.playtime#) MOD 60
IF pmin > 0 THEN
PRINT USING "Play Length: ##:"; pmin;
PRINT USING "##"; psec
ELSE
PRINT USING "Play Length ##.##s"; WaveInfo.playtime#
END IF
'PRINT "start of actual data:"; SEEK(1)
END SUB

SUB MasterVolume (Right1%, Left1%, Getvol%)
OUT Baseport% + 4, &H22
IF Getvol% THEN
Left1% = INP(Baseport% + 5) \ 16
Right1% = INP(Baseport% + 5) AND &HF
EXIT SUB
ELSE
OUT Baseport% + 5, (Right1% + Left1% * 16) AND &HFF
END IF
END SUB

$SEGMENT
SUB PlayWave (Filename$)
FileNum% = FREEFILE
LOCATE 7, 1
OPEN Filename$ FOR BINARY AS FileNum%
IF LOF(FileNum%) = 0 THEN
PRINT "**"; Filename$; " doesn't exist.**"
CLOSE : KILL Filename$: END
END IF

SoundLen& = LOF(FileNum%)-44

IF SoundLen& < 65528 THEN
SoundLen?? = SoundLen&
END IF

L?? = SoundLen??

PRINT : PRINT "Playing " + Filename$
GET #FileNum%, , Wave: 'BASIC defines beginning of file as 1
Freq& = 22000: 'default playback frequency
getWaveInfo
Freq& = WaveInfo.Freq
Freq2& = Freq& * 2
StereoWav% = WaveInfo.StereoWav
sixteenbit% = WaveInfo.sixteenbit
cskip = cardversion% <= 3 AND NOT sixteenbit% AND StereoWav%: 'skip one
'cskip2 = cardversion% <= 2 AND NOT sixteenbit% AND NOT StereoWav%
LOCATE 1, 65: PRINT "cycles free"

MEMPACK
Bseg?? = VARSEG(WavBuffer&(0))
Boff?? = VARPTR(WavBuffer&(0))

CLS
PRINT "Bseg?? = ";Bseg??
PRINT "Boff? = ";Boff??

vol = 10
'LOCATE 18, 1: PRINT "Buffer at " + HEX$(Bseg??); ":"; HEX$(Boff??)
RLength& = WaveInfo.Length: 'RLength& is number of remaining bytes
IF RLength& > (LOF(FileNum%) - %HeaderSize + 1) THEN
RLength& = LOF(FileNum%) - %HeaderSize + 1
LOCATE 20, 1: PRINT "warning: Truncated .WAV detected."
END IF

firsttime = 1
GetArray FileNum%, WavBuffer&(), L??, BytesRead??
IF RLength& >= SoundLen?? THEN
L?? = SoundLen??
L?? = SoundLen??
ELSE
L?? = RLength&
L?? = CINT(RLength&)
END IF
t1# = TIMER

DO
IF RLength& <= 0 AND firsttime = 0 THEN EXIT SUB
firsttime = 0
'............play block in the background.......................
LOCATE P% + 20,5
PRINT "Playing"
INCR P%
LOCATE 1, 13: COLOR 14
DMAPlay Bseg??, BOff??, L??, Freq&, StereoWav%
'..............................................................
'fill buffer
IF RLength& >= SoundLen?? THEN
L?? = SoundLen??
L?? = SoundLen??
ELSE
L?? = RLength&
L?? = SoundLen??
END IF
GetArray FileNum%,WavBuffer&(),L??,ReadBytes??
RLength& = RLength& - L?? 'update remaining length
'done filling buffer,,,,,,,,,,,,,,
last:
cycles% = 0
DO UNTIL DMADone%(DMA16%, L??)
IF INKEY$ > "" THEN stopflag = 1:EXIT LOOP
LOOP
IF stopflag THEN EXIT DO: 'stop here so it doesn't freeze the computer
LOOP
LOCATE 23, 1: PRINT "DMA transfer completed!";
DMAState 0: 'stop sound
quit% = ResetDSP%
END SUB

FUNCTION ReadDAC%
' Reads a byte from the DAC.
WriteDSP &H20
ReadDAC% = ReadDSP%
END FUNCTION

FUNCTION ReadDSP%
WAIT (Baseport% + &HE), &H80: 'wait for bit 7 on pollport
DO: DSPIn% = INP(Baseport% + 10): LOOP UNTIL DSPIn% <> &HAA
ReadDSP% = DSPIn%
END FUNCTION

FUNCTION ResetDSP%
ct = 0: stat = 0: ready = &HAA
ResetPort?? = Baseport% + &H6
OUT ResetPort??, 1
! MOV DX, ResetPort??
! IN AL,DX
! IN AL,DX
! IN AL,DX
! IN AL,DX
! IN AL,DX
! IN AL,DX
DO
OUT Baseport% + &H6, 0
stat = INP(Baseport% + &HE)
stat = INP(Baseport% + &HA)
IF stat = ready THEN EXIT DO
INCR ct
LOOP WHILE ct < 200 'wait about 100 ms
IF stat = ready THEN ResetDSP% = 1 ELSE ResetDSP% = 0
END FUNCTION

SUB SpeakerState (OnOff%)
' Turns speaker on or off.
IF OnOff% THEN WriteDSP &HD1 ELSE WriteDSP &HD3
END SUB

SUB VocVolume (Right1%, Left1%, Getvol%)
OUT Baseport% + 4, &H4
IF Getvol% THEN
Left1% = INP(Baseport% + 5) \ 16
Right1% = INP(Baseport% + 5) AND &HF
EXIT SUB
ELSE
OUT Baseport% + 5, (Right1% + Left1% * 16) AND &HFF
END IF
END SUB

SUB WriteDSP (Byte2%)
' Writes a byte to the DSP
DO
A% = INP(Baseport% + 12) AND &H80
LOOP WHILE A%
OUT Baseport% + 12, Byte2%

$IF 0
! mov dx,wSBCBaseAddx ; SBC base I/O address 2x0h
! add dl,0Ch ; Write-Buffer Status port, 2xCh
Busy:
! in al,dx ; Read Write-Buffer Status port
! or al,al ; Can write to DSP?
! js Busy ; Bit 7 set, try again
! mov al,bData ; Get DSP command or data
! out dx,al ; Send to DSP
$ENDIF
END SUB


SUB GetArray(BYVAL InputFileHandle%,A&(),BYVAL ReadBytes??, BytesRead??)
LOCAL IputFileHandle??
InputFileHandle?? = FileAttr(InputFileHandle%,2)
BufferSeg?? = VARSEG(A&(0))
BufferOff?? = VARPTR(A&(0))

'read file

! push ds
! mov ax, &h3F00
! mov bx, InputFileHandle??
! mov cx, ReadBytes??
! mov dx, BufferOff??
! mov ds, BufferSeg??
! int &h21
! LES BX, BytesRead??
! mov ES:[BX], ax
! pop ds
END SUB

Here is a Link to the file
RadioTelephoneTutor.com/PBDmaPlay.zip

I think this is the root of the problem.

In no way do I think that sound using Dmaplay would be resource
hungry. I even tested it out by droping the cycles to 300. Same result.

Buggy, Buggy Buggy.

I hope someone can get this fixed.

Conquer the FCC GROL, & Amatuer Radio test

Reply 2 of 7, by Lassar

User metadata
Rank Newbie
Rank
Newbie

My system does not have a sound blaster card. Just integrated sound.
I hope someone with a real sound blaster card can confirm that this
works in real dos instead of DosBox.

If your system does have a real sound blaster card; please download the
program and check it out for me.

And let us know if it works in real dos.

The link is:

http://radiotelephonetutor.com/PBDmaPlay.zip

Conquer the FCC GROL, & Amatuer Radio test

Reply 4 of 7, by Lassar

User metadata
Rank Newbie
Rank
Newbie
wd wrote:

What are the symptoms that make it non-working?
How does it behave if you type "loadfix -32" or "loadfix -16" before starting it?

😦

I have not tried loadfix.

But I just managed to get dos sound driver's for my motherboard installed.
It's not sound blaster mind you. But at least now I can get sound in
pure dos.

It is messing up there too. So I have to eat crow on this one.

Which really makes me impressed with the Windows XP emulation of
dos sound.

How does Windows XP do that ?

I have a question on the above reply.

What do you mean by zeroing the dma page, not caring about dma buffer wrapping.

I think I might know what you mean by zeroing the dma page maybe.
But what is this about dma buffer wrapping ?

I am really trying to understand this.

I appreciate any help you could give me on this.

Conquer the FCC GROL, & Amatuer Radio test

Reply 5 of 7, by wd

User metadata
Rank DOSBox Author
Rank
DOSBox Author

DMA transfers are not allowed to cross 64k-boundaries
(XP doesn't emulate this aspect). So a buffer can only
range from for example 0x2000:0x0000 to 0x2fff:0x000f.
If you allocate a buffer without caring about this,
it can for example start at 0x2800:0x0000 but you
get a wrapping at 0x2fff:0x000f as the page ends there.
So you can't use the full 64k you allocated.

How to fix this: allocate memory starting at 64k page
boundaries, like clearing the lowest 16 bits and adding
64k to it (the allocated buffer needs to be 128k in
size to be safe).
For example the 0x2800:0x0000 buffer would get
0x2000:0x0000 through the clearing and 0x3000:0x0000
when adding the 64k. This last value is a valid dma
start address which allows using the full page (64k).

Now in your code you'll notice this address gives an
overflow as 0x3000*16+0x0000 does not fit into the
16bit dma offset register. That's what the dma page
register is for, would get 3 in this case (that's what
i meant with "always zeroing the page reg").

Maybe check the original sources and re-add necessary
code from there, or ask here if something is unclear.

Reply 6 of 7, by Lassar

User metadata
Rank Newbie
Rank
Newbie
wd wrote:
DMA transfers are not allowed to cross 64k-boundaries How to fix this: allocate memory starting at 64k page boundaries, like cle […]
Show full quote

DMA transfers are not allowed to cross 64k-boundaries
How to fix this: allocate memory starting at 64k page
boundaries, like clearing the lowest 16 bits and adding
64k to it (the allocated buffer needs to be 128k in
size to be safe).

Now in your code you'll notice this address gives an
overflow as 0x3000*16+0x0000 does not fit into the
16bit dma offset register. That's what the dma page
register is for, would get 3 in this case (that's what
i meant with "always zeroing the page reg").

I check on the dos allocate memory interrupt. It does not allow telling it
to allocate on page boundary. Your only choice is telling it how munch memory you want ?

So I was thinking maybe you could take advantage of ems instead.

I think it will return a address to a ems frame that does not pass a page boundary.

Do you think this will work ?

Conquer the FCC GROL, & Amatuer Radio test

Reply 7 of 7, by wd

User metadata
Rank DOSBox Author
Rank
DOSBox Author

Your only choice is telling it how munch memory you want ?

Yes, but the "allocate 128k and align address to 64k boundary" i've mentioned
above works fine.

ems and dma is a bit tricky, don't know how XP handles that.