A well documented Windows audio out driver and mini tutorial about triple buffers.

For issues with communication ports, protocols, etc.
Post Reply
D.J.Peters
Posts: 8586
Joined: May 28, 2005 3:28
Contact:

A well documented Windows audio out driver and mini tutorial about triple buffers.

Post by D.J.Peters »

A well documented windows audio out example a kind of tiny tutorial about triple buffers at all. (I hope)
(and again sorry about my bad written English)

But warning put your audio volume down before you run it !

It will kill your audio device at first than your mother board :-)

Joshy

Code: Select all

#ifndef __FB_WIN32__
# error 666: Sorry this is for Windows x86/x86_64 only !
#endif

const as single PI =atn(1)*4
const as single PI2=atn(1)*8

' select the sample quality in scope of speed for games and demos I prefer 22 KHz.
' For a audio application like player, synthesizer, recording studio
' a higer quality are choosen may be 48 KHz. or 96 KHz. (if supported).
const nSampleRate = 22050 ' 11025, 22050, 44100, 48000 ...

' Minimum is a triple buffer cue.
const nBuffers = 3

' The idea behind a triple buffer cue are:
' At any time one prepared buffer must be inserted and waiting in the
' drivers buffer que, while another buffer are currently playing.

' If the playing buffer are done the audio driver can !immediately! play 
' the waiting buffer without any interruption of the audio stream !

' That means if one prepared and !LOCKED! buffer are waiting in the
' driver cue and another buffer are !LOCKED! also while playing,
' we need a third !UNLOCKED! audio buffer to fill with new audio data !

' I hope it makes sense why a triple buffer cue is a must !

' If not imagine you use two buffers only like if you use two graphic pages
' wher one page ar shown and you draw on the other hidden page.
' If you are done with drawing you can flip the two pages to any time.

' "to any time" is the point here !
' if your drawing on the hidden page needs longer as accepted 
' this not a big problem while the other page shown your last drawing.

' Now compare it with audio !
' If you fill/draw on a hidden/silent audio buffer and it's needs longer as from driver accepted
' this is a big problem the audio stream will be interrupted and your ears will notice it directly !

' Your ears and brain don't like any interruption of audio,
' short interruptions of 1 millisecond are not accepted.

' Trust me a third buffer is the first choice :-)

' But wait we have to solve two short problems.
' 1) How we know which buffer are currently the right to fill.
' 2) Important also, when is the right time to fill it !

' To get information from the audio driver we can setup a message callback.
' The driver will call to inform us whats currently going on and which buffer are done.
' May be you think this will solve our problems and we can open a bottle of bear know :-)

' But that solves only our first problem "which buffer are currently the right to fill"
' The second problem are still exist "when is the right time to fill it"

' The primary problem are the message callback runs in the audio drivers own thread
' and must be exit immediately or almost fast as possible.

' If not the audio stream will be interrupted and we have to prevent that in any case.

' So the message callback isn't the right place nor the right time to fill our audio buffer.

' One solution are we create our own fill thread and inside of the driver callback
' we inform our fill thread "her are a free buffer do your job in background" and exit the callback immediately.

' That sounds good and solves our problems.

' Of course you can pooling a shared var and fill the buffer in a loop without an extra thread.

' while bExit = false
'   while bNewBufer=false and bExit=false : sleep 1 : wend
'   if bExit=false and bNewBufer=true then
'     for i = 0 to nSamplesPerBuffer - 1
'       with FreeBuffer.Samples(i)
'         .leftChannel  = SoundGeneratorGetLeft(i)
'         .rightChannel = SoundGeneratorGetRight(i)
'       wend
'     next
'   end if 
' wend

' That will work and the sleep command ensures that we won't eat all CPU time.

' Normally "audio in general" are only the part of a game or demo that runs in the background
' the primary scope are more on update the graphics, handle player input, move the monsters
' handle multiplayer network stuff, do a timestep in physics etc.

' Is more evident doing all the primary stuff in the main loop
' and handle audio "parallel" in a backgoud thread. 

' One feature of threads vs polling loops are: 
' You can control its running state with conditions and mutex.
' For example a waiting thread doesn't consume CPU cycles so we need only to wake up 
' our fill thread if the audio driver send a done message to the callback.

' How many samples are in one playback buffers.
const nSamplesPerBuffer = 4096 ' common are a power of 2

' The size of the buffers defines indirect 
' how often the fill thread will be called per second.
' buffers per second = nSamplesPerSecond / nSamplesPerBuffer 
' 22050 / 4096 = ~5.4  (fps) = 1000 ms / 5.4  = every 185 milliseconds
' 44100 / 512  = ~86.2 (fps) = 1000 ms / 86.2 = every  11 milliseconds

#ifndef NULL 
# define NULL cptr(any ptr,0)
#endif

type tSample
  as short l,r ' left and right channel 16 bit
end type
type tWaveHeader field=1
  as tSample ptr     Samples        ' =  samples[0 ... nSamplesPerBuffer-1]
  as ulong           nBytesPlayback ' size of one buffer in bytes
  as ulong           nBytesCapture  ' used for recording samples
  as any ptr         UserData       ' can be used for any user data
  as ulong           flags          ' the driver set flags for prepared buffers and if the buffer locked in the the cue the user can set falgs for loop begin or loop end
  as ulong           nLoops         ' can be used as loop counter
  as tWaveHeader ptr pNext          ' not used (buffer list was never implemented on windows)
  as any ptr         reserved       ' reserved not used
end type

type tThreadArgs
  as tWaveHeader ptr WaveHeader     ' inside the message callback used to signal the wich buffer to fill
  as any ptr         hDevice        ' the thread must send new filled buffers back to the audio device so this is the handle to it
  as any ptr         Mutex          ' a mutex must be created for the thread to use the condition object
  as any ptr         Condition      ' the condition object are use to let the thread sleeping and signal "wake up fill new buffer"  
  as ulong           ExitThread     ' our main thread / loop can signal the tread it's time to die :-) 
end type

const PCM_FORMAT_TAG = 1
type tWaveFormat field=1            ' the old struct on windows to define PCM audio for new formats (float multichannel) use WaveFormatEx
  as ushort WaveFormaTag            ' must be 1 for PCM data
  as ushort nChannels               ' I use stero so 2 is the right value
  as ulong  nSamplesPerSecond       ' 8000,11025,22050,44100,48000,96000 ...
  as ulong  nBytesPerSecond         ' samplerate * channels * (bits\8)
  as ushort nBlockAlign             ' sizeof(tSample) = 4
  as ushort nBitsPerSample          ' I use 16 bit
  as ushort nExtraSize              ' If this struct are a part of an WaveFormatEx struct it defines the size of extra stuff
end type

' Only some functions from a bunch of wave audio commads 
declare function DeviceOpen alias "waveOutOpen" (byval hDevice as any ptr,byval iDevice as long=-1, byval pWaveFormat as any ptr, byval pCallback as any ptr, byval userdata as any ptr, byval flags as ulong) as ulong
declare function DevicePrepare alias "waveOutPrepareHeader" (byval hDevice as any ptr, whdr as tWaveHeader ptr, hdrSize as ulong=sizeof(tWaveHeader)) as ulong
declare function DeviceWrite alias "waveOutWrite" (byval hDevice as any ptr, byval whdr as tWaveHeader ptr,hdrSize as ulong=sizeof(tWaveHeader)) as ulong
declare function DeviceUnprepare alias "waveOutUnprepareHeader" (byval hDevice as any ptr, whdr as tWaveHeader ptr, hdrSize as ulong=sizeof(tWaveHeader)) as ulong
declare function DeviceReset alias "waveOutReset" (byval hDevice as any ptr) as ulong
declare function DeviceClose alias "waveOutClose" (byval hDevice as any ptr) as ulong

#inclib "winmm"

' This is the audio out driver message proc 
' which we have to leave as fast as possible.
' The content of Argument 1/2 are message dependent.
' Is it a buffer done message than Argument1 points the buffer which we can use to fill with new samples.
' only the userdata argument (we set while opening the device) are present every call
sub MessageProc(byval hDevice   as any ptr, _
                byval uMessage  as ulong  , _
                byval Userdata  as any ptr, _
                byval Argument1 as any ptr, _
                byval Argument2 as any ptr)
  dim as tThreadArgs ptr ThreadArgs = Userdata 
  dim as tWaveHeader ptr WaveHeader = Argument1
  uMessage-=955 ' make message in range of a fast jumptable index
  select case as const uMessage ' "as const" is by far faster then any if elsif then constructions
  case 0: print "device open"
  case 1: print "device close"
    if (ThreadArgs<>NULL) then
      ' signal the sleeping thread job are done
      ThreadArgs->ExitThread=1
      ' wake it up to terminate
      CondSignal(ThreadArgs->Condition)
    end if  
  case 2: 'print "MSG buffer done"
    if (ThreadArgs<>NULL) andalso (WaveHeader<>NULL) then 
      ' witch buffer to fill
      ThreadArgs->WaveHeader = WaveHeader
      ' wake up the thread to fill
      CondSignal(ThreadArgs->Condition)
    end if  
  end select
end sub

' NOTE: In fbsound I can encode OGG/MP3 streams and mix 100 sounds
' all inside the buffer fill callback if you hear audio stream interruptions 
' than your code are to slow or to complex :-)
' TIP: if you program complex stuff like DSP effects a sythesizer engine etc.
' use precalculated tables for sin/cos and other time critical math stuff.
sub DspThread(ThreadArgument as any ptr) 
  const as single f1HerzStep = pi2/nSampleRate
  dim as ulong ret
  dim as integer iZoom
  dim as single a,b,c=1,d=1,cstep=0.11,dstep=0.025
  dim as tThreadArgs ptr ThreadArgs=ThreadArgument
  iZoom=nSamplesPerBuffer/640
  windowtitle "DSP thread run "
  ThreadArgs->ExitThread=0
  while ThreadArgs->ExitThread=0
    ' let it sleeping
    MutexLock(ThreadArgs->Mutex)
      CondWait(ThreadArgs->Condition,ThreadArgs->Mutex)
    MutexUnlock(ThreadArgs->Mutex)
    if (ThreadArgs->ExitThread=0) then
      ' fill the sample buffer 
      c+=cStep 
      if c>10 then
        c=10 : cStep*=-1
      elseif c<1 then 
        c=1:cStep*=-1
      end if  
      
      d+=dStep 
      if d>10 then
        d=10 : dStep*=-1
      elseif d<1 then 
        d=1:dStep*=-1
      end if  

      dim as tSample ptr buffer=ThreadArgs->WaveHeader->Samples
      for index as integer = 0 to nSamplesPerBuffer-1
        buffer[index].l = 1000 * sin(c*sin(a)+b)*c
        buffer[index].r = -buffer[index].l
        a=b*0.1*d
        b += f1HerzStep*220*d : if b>PI2*5 then b-=PI2*5
      next

      do ' send new audio data to the device
        ret = DeviceWrite(ThreadArgs->hDevice,ThreadArgs->WaveHeader)
        if ret<>0 then beep
      loop while (ThreadArgs->ExitThread=0) andalso (ret=33) ' if device are busy

      screenlock : cls
      line (0,240)-step(639,0),15
      pset(0,240+buffer[0].l shr 6)
      for index as integer = 1 to 639
       line -(index,240+buffer[index].l shr 6),1
      next
      screenunlock
    end if
  wend
  windowtitle "DSP thread terminated"
end sub

'
' main
'
dim as tThreadArgs ThreadArgs
dim as ulong ptr   hDevice
dim as tWaveFormat WaveFormt
dim as tSample ptr SampleMemory
dim as tWaveHeader Buffers(nBuffers-1)
screenres 640,480
' define a 16 bit stereo audio format
with WaveFormt
  .WaveFormaTag      = PCM_FORMAT_TAG
  .nChannels         = 2
  .nSamplesPerSecond = nSampleRate
  .nBytesPerSecond   = nSampleRate shl 2
  .nBlockAlign       = 4
  .nBitsPerSample    = 16
end with  
const MESSAGE_PROC_FLAG = &h30000
const WAVE_MAPPER       = -1
' open the windows default audio device
if DeviceOpen(@hDevice, WAVE_MAPPER, @WaveFormt, @MessageProc, @ThreadArgs, MESSAGE_PROC_FLAG) then
  print "error: can't open the default audio device with current format settings !"
  beep : sleep : end 1
end if

' allocate sample meory
SampleMemory = callocate(nSamplesPerBuffer*nBuffers*sizeof(tSample))

' setup and prepare the buffers
for i as integer = 0 to nBuffers-1 
  Buffers(i).Samples        = @SampleMemory[i*nSamplesPerBuffer]
  Buffers(i).nBytesPlayback = nSamplesPerBuffer*sizeof(tSample)
  DevicePrepare(hDevice, @Buffers(i))
next

with ThreadArgs
  .hDevice     = hDevice
  .Mutex       = MutexCreate()
  .Condition   = CondCreate()
  .ExitThread  = 1
end with  
ThreadCreate(@DspThread,@ThreadArgs)
' wait for start of the thread
while ThreadArgs.ExitThread=1:sleep 1:wend

for i as integer = 0 to nBuffers-1 
  ' put it in the driver cue and play it
  DeviceWrite(hDevice, @Buffers(i))
next


print "  main thread sleeps ..."
sleep
' signal thread termination
ThreadArgs.ExitThread=1
' mark all waiting buffers are done
DeviceReset(hDevice)
' close the device
DeviceClose(hDevice)
' unprepare the buffers
for i as integer = 0 to nBuffers-1
  DeviceUnprepare(hDevice, @Buffers(i))
next
' free the sample memory
deallocate(SampleMemory)
print "done press any key ..."
sleep
D.J.Peters
Posts: 8586
Joined: May 28, 2005 3:28
Contact:

Re: A well documented Windows audio out driver and mini tutorial about triple buffers.

Post by D.J.Peters »

Don't be confuse about what I'm wrote in the DSP buffer fill thread.

Here are an empty (random noise) template for your own fill thread

Code: Select all

sub DspThread(ThreadArgument as any ptr) 
  dim as tThreadArgs ptr ThreadArgs=ThreadArgument
  ThreadArgs->ExitThread=0
  while ThreadArgs->ExitThread=0
    ' let it sleeping
    MutexLock(ThreadArgs->Mutex)
      CondWait(ThreadArgs->Condition,ThreadArgs->Mutex)
    MutexUnlock(ThreadArgs->Mutex)
    
    ' no thread termination  so fill the buffer 
    if (ThreadArgs->ExitThread=0) then

      ' fill the sample buffer 
      dim as tSample ptr buffer=ThreadArgs->WaveHeader->Samples
      for index as integer = 0 to nSamplesPerBuffer-1
        buffer[index].l = (rnd-rnd)*3000
        buffer[index].r = (rnd-rnd)*3000
      next
      
       ' send new audio data to the device
      dim as ulong ret
      do
        ret = DeviceWrite(ThreadArgs->hDevice,ThreadArgs->WaveHeader)
      loop while (ThreadArgs->ExitThread=0) andalso (ret=33) ' if device are busy

    end if
  wend
end sub
dafhi
Posts: 1640
Joined: Jun 04, 2005 9:51

Re: A well documented Windows audio out driver and mini tutorial about triple buffers.

Post by dafhi »

did you recently fry a board? xD
Post Reply