SoundStream.st
author Claus Gittinger <cg@exept.de>
Sat, 02 May 2020 21:40:13 +0200
changeset 5476 7355a4b11cb6
parent 5468 e9da15c1a36c
permissions -rw-r--r--
#FEATURE by cg class: Socket class added: #newTCPclientToHost:port:domain:domainOrder:withTimeout: changed: #newTCPclientToHost:port:domain:withTimeout:

"{ Encoding: utf8 }"

"
 COPYRIGHT (c) 1993 by Claus Gittinger
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libbasic2' }"

"{ NameSpace: Smalltalk }"

FileStream subclass:#SoundStream
	instanceVariableNames:'sampleRate numberOfChannels bitsPerSample audioFormat handle1
		handle2 bufferOffset bufferSize lastErrorString fragmentSize
		openMode openAttributes'
	classVariableNames:'IsInitialized UnsupportedOperationSignal ConcreteClass'
	poolDictionaries:''
	category:'Streams-External'
!

SoundStream subclass:#DevAudio
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:SoundStream
!

SoundStream subclass:#IRISAudio
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:SoundStream
!

SoundStream subclass:#JackAudio
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:SoundStream
!

SoundStream subclass:#PortAudio
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:SoundStream
!

SoundStream subclass:#Win32DirectSound
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:SoundStream
!

SoundStream subclass:#Win32WaveSound
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:SoundStream
!

!SoundStream primitiveDefinitions!
%{

#include "stxOSDefs.h"

#ifndef NO_SOUND

# ifdef __win32__
#  define xxxSUPPORT_WIN32_DIRECTSOUND
#  ifndef SUPPORT_WIN32_WAVESOUND
#   define SUPPORT_WIN32_WAVESOUND
#  endif
# endif /* __win32__ */

# ifdef __iris__
#  ifndef IRIX5
#   ifndef SUPPORT_IRIS_AUDIO
#    define SUPPORT_IRIS_AUDIO
#   endif
#  endif
# endif // __iris__

# ifndef SUPPORT_IRIS_AUDIO
#  ifndef SUPPORT_ALSA_AUDIO
#   ifdef LINUX
#    ifndef SUPPORT_DEV_AUDIO
#     define SUPPORT_DEV_AUDIO
#    endif
#   endif // LINUX
#  endif
# endif // SUPPORT_IRIS_AUDIO

# ifdef __osx__
#  ifndef SUPPORT_PORTAUDIO
#   define xxxSUPPORT_PORTAUDIO 	// def comes from config file
#  endif
# endif // __osx__

#endif /* NO_SOUND */

#ifdef SUPPORT_IRIS_AUDIO
# include <audio.h>
# define __ALportVal(o)  (ALport)(__externalAddressVal(o))
# define alPort handle1
#endif

#ifdef SUPPORT_ALSA_AUDIO
# ifdef LINUX
#  include <alsa/asoundlib.h>
#  define MAX_NR_OF_CHANNELS 8
#  define DEBUG_SOUND
#  define readHandle handle1
#  define writeHandle handle2
# endif
#endif

#ifdef SUPPORT_DEV_AUDIO
# ifdef LINUX
#  include <stdio.h>
#  include <errno.h>
#  include <signal.h>
#  include <sys/ioctl.h>
#  include <sys/soundcard.h>
#  define DEV_AUDIO_DEFAULT_FREQ (8000)
#  define DEV_AUDIO_DEFAULT_BUFFERSIZE (16384)
# endif

# ifdef FREEBSD
#  include <stdio.h>
#  include <sys/time.h>
#  include <sys/ioctl.h>
#  include <machine/pcaudioio.h>
#  define DEV_AUDIO_DEFAULT_FREQ (8000)
#  define DEV_AUDIO_DEFAULT_BUFFERSIZE (16384)
# endif

# if defined(sunos) || defined(solaris)
#  include <stdio.h>
#  ifdef solaris
#   include <sys/audioio.h>
#  else
#   include <sun/audioio.h>
#  endif
#  define DEV_AUDIO_DEFAULT_FREQ (8000)
#  define DEV_AUDIO_DEFAULT_BUFFERSIZE (16384)
# endif

# if defined(hpux)
#  include <stdio.h>
#  include <sys/ioctl.h>
#  include <sys/inode.h>
#  include <sys/audio.h>
#  include <sys/time.h>
#  include <unistd.h>
#  define DEV_AUDIO_DEFAULT_FREQ (22050)
#  define DEV_AUDIO_DEFAULT_BUFFERSIZE (16384)
# endif
#endif /* SUPPORT_DEV_AUDIO */

#ifdef SUPPORT_PORTAUDIO
// # include "pthread.h"
# include "portaudio.h"
# define PORTAUDIO_DEFAULT_FREQ (44100)
# define PORTAUDIO_DEFAULT_BUFFERSIZE (16384)

# define xINITLOCK(lk)    { pthread_mutex_init(&(lk), NULL); }
# define xRELEASELOCK(lk) { pthread_mutex_destroy(&(lk)); }
# define xLOCK(lk)        { pthread_mutex_lock(&(lk)); }
# define xUNLOCK(lk)      { pthread_mutex_unlock(&(lk)); }
# define xMUTEX            pthread_mutex_t

# define INITLOCK(lk)    { (lk) = 0; }
# define RELEASELOCK(lk) { (lk) = 0; }
# define LOCK(lk)        { while ((lk)) ; (lk) = 1; }
# define UNLOCK(lk)      { (lk) = 0; }
# define MUTEX           int

#endif // SUPPORT_PORTAUDIO

#ifdef SUPPORT_JACKAUDIO
# include "jack/jack.h"
#endif // SUPPORT_JACKAUDIO

#ifdef __win32__
# define _WIN32

# undef INT
# undef Array
# undef Number
# undef Method
# undef Point
# undef Rectangle
# undef Block
# undef String
# undef Message
# undef Object
# undef Context
# undef Time
# undef Date
# undef Process
# undef Processor
# undef Set
# undef Signal
# undef Delay

/* # include <stdarg.h> /* */
# include <stdio.h> /* */
# include <windows.h>

# ifdef SUPPORT_WIN32_DIRECTSOUND
#  define CINTERFACE
#  include "dsound.h"
#  define __DirectSoundVal(o) (LPDIRECTSOUND)(__externalAddressVal(o))
#  define __DSBufferVal(o)    (LPDIRECTSOUNDBUFFER)(__externalAddressVal(o))

#  define RT_BUFFER_SIZE 4096
#  define NBUFS          4

#  define pDirectSound handle1
#  define pDSBuffer    handle2

# else /* USE WAVE... */
#  ifdef SUPPORT_WIN32_WAVESOUND
#   define __WaveHandleVal(o)    (HWAVEOUT)(__externalAddressVal(o))
#   define MAXBUF      10        /* Maximum number of buffers */
#   define DATALEN     2048      /* Size of wave data buffer */

struct buf {
    WAVEHDR hdr;                /* Wave data header */
    char data[DATALEN];         /* Actual wave data */
    struct buf *next;           /* Next buffer in free list */
};

static struct buf *free_list = NULL;      /* List of available buffers */
static CRITICAL_SECTION free_list_lock;
static int free_buffers = 0;             /* Number of buffers in free list */
static int total_buffers = 0;            /* Total number of buffers allocated */
static HANDLE free_buffer_event;         /* Automatic-reset event triggered whenever */

#   define waveHandle handle1

#  endif /* SUPPORT_WIN32_WAVESOUND */
# endif /* SUPPORT_WIN32_DIRECTSOUND */

# ifdef __DEF_Array
#  define Array __DEF_Array
# endif
# ifdef __DEF_Number
#  define Number __DEF_Number
# endif
# ifdef __DEF_Method
#  define Method __DEF_Method
# endif
# ifdef __DEF_Point
#  define Point __DEF_Point
# endif
# ifdef __DEF_Block
#  define Block __DEF_Block
# endif
# ifdef __DEF_String
#  define String __DEF_String
# endif
# ifdef __DEF_Message
#  define Message __DEF_Message
# endif
# ifdef __DEF_Object
#  define Object __DEF_Object
# endif
# ifdef __DEF_Context
#  define Context __DEF_Context
# endif
# ifdef __DEF_Time
#  define Time __DEF_Time
# endif
# ifdef __DEF_Date
#  define Date __DEF_Date
# endif
#ifdef __DEF_Process
# define Process __DEF_Process
#endif
#ifdef __DEF_Processor
# define Processor __DEF_Processor
#endif
#ifdef __DEF_Set
# define Set __DEF_Set
#endif
#ifdef __DEF_Signal
# define Signal __DEF_Signal
#endif
#ifdef __DEF_Delay
# define Delay __DEF_Delay
#endif

# define INT  STX_INT
# define UINT STX_UINT

#endif /* __win32__ */

#ifdef DEBUG_SOUND
# define DPRINTF(x) console_printf x
#else
# define DPRINTF(x) /* as nothing */
#endif

%}
! !

!SoundStream primitiveVariables!
%{
static int DEBUGGING = 0;
%}
! !

!SoundStream primitiveFunctions!
%{

#ifdef SUPPORT_WIN32_WAVESOUND

/*
 * This routine will be called by windows when audio is needed.
 * It may called at interrupt level and by a separate thread, so don't do anything
 * that could mess up the system like calling malloc() or free().
 */
static void CALLBACK
waveCallBack(HWAVE waveHandle, UINT msg, DWORD_PTR inst, DWORD_PTR p1, DWORD_PTR p2)
{
    if (msg == MM_WOM_DONE) {
        struct buf *bp = (struct buf *)p1;

        EnterCriticalSection(&free_list_lock);
        bp->next = free_list;
        free_list = bp;
        free_buffers++;
        SetEvent(free_buffer_event);
        LeaveCriticalSection(&free_list_lock);
    }
}

#endif /* SUPPORT_WIN32_WAVESOUND */

#ifdef SUPPORT_PORTAUDIO

struct paBuffer {
    void* sampleData;
    int bufferSize;
    struct paBuffer* nextBuffer;
};

struct paStreamData {
    PaStream *stream;
    MUTEX lock;
    int readOffset;
    int bytesPerSample;     // bytesPerSample (1, 2 or 4)
    int nChannels;          // num channels (1 or 2)
    int hasFinished;
    struct paBuffer* currentBuffer;
    struct paBuffer* lastBuffer;
    struct paBuffer* freeList;
};

/*
 * This routine will be called by the PortAudio engine when audio is needed.
 * It may called at interrupt level on some machines, so don't do anything
 * that could mess up the system like calling malloc() or free().
 */
static int
paCallback( const void *inputBuffer, void *outputBuffer,
            unsigned long framesPerBuffer,
            const PaStreamCallbackTimeInfo* timeInfo,
            PaStreamCallbackFlags statusFlags,
            void *userData )
{
    struct paStreamData *streamData = (struct paStreamData *)userData;
    struct paBuffer *buffer = streamData->currentBuffer;
    int nBytesToOutput = streamData->bytesPerSample * streamData->nChannels * framesPerBuffer;
    int nBytesLeftInBuffer;
    int readOffset;
    int writeOffset = 0;
    int nSent;
    int retVal = paContinue;

    readOffset = streamData->readOffset;
  again:
    if (buffer != NULL) {
        nBytesLeftInBuffer = buffer->bufferSize - readOffset;
        if (DEBUGGING) {
            fprintf(stderr, "pa: %d from %p[%d] to [%d]; next: %p last: %p)\n",
                        nBytesLeftInBuffer, buffer, readOffset, writeOffset,
                        buffer->nextBuffer, streamData->lastBuffer);
        }
    } else {
        nBytesLeftInBuffer = 0;
    }
    if (nBytesLeftInBuffer >= nBytesToOutput) {
        memcpy(outputBuffer+writeOffset, buffer->sampleData+readOffset, nBytesToOutput);
        nSent = nBytesToOutput;
        if (DEBUGGING) {
            fprintf(stderr, "pa: %d from buffer\n", nSent);
        }
        nBytesToOutput = 0;
        readOffset += nSent;
    } else {
        nSent = nBytesLeftInBuffer;
        if (nSent > 0) {
            memcpy(outputBuffer+writeOffset, buffer->sampleData+readOffset, nBytesLeftInBuffer);
            if (DEBUGGING) {
                fprintf(stderr, "pa: %d from buffer\n", nBytesLeftInBuffer);
            }
            nBytesToOutput -= nSent;
            readOffset += nBytesLeftInBuffer;
        }
    }
    if (buffer != NULL) {
        streamData->readOffset = readOffset;
        if (readOffset >= buffer->bufferSize) {
            LOCK(streamData->lock);
            // next buffer
            streamData->currentBuffer = buffer->nextBuffer;
            streamData->readOffset = readOffset = 0;
            // this buffer onto freeList
            buffer->nextBuffer = streamData->freeList;
            streamData->freeList = buffer;
            if (DEBUGGING) {
                fprintf(stderr, "pa: put on freelist: %p\n", buffer);
            }
            if (streamData->currentBuffer == NULL) {
                if (DEBUGGING) {
                    fprintf(stderr, "pa: done with last buffer\n");
                }
                streamData->lastBuffer = NULL;
                retVal = paComplete;
            }
            UNLOCK(streamData->lock);
            if (nBytesToOutput > 0) {
                writeOffset += nSent;
                if (streamData->currentBuffer == NULL) {
                    memset(outputBuffer+writeOffset, 0, nBytesToOutput);
                } else {
                    buffer = streamData->currentBuffer;
                    readOffset = 0;
                    if (DEBUGGING) {
                        fprintf(stderr, "pa: %d more\n", nBytesToOutput);
                    }
                    goto again;
                }
            }
        }
    }

    return paContinue;
}

/*
 * This routine is called by portaudio when playback is done.
 */
static void
paStreamFinished( void* userData )
{
    struct paStreamData *streamData = (struct paStreamData *)userData;

    streamData->hasFinished = 1;
    if (DEBUGGING) {
        fprintf(stderr, "pa: Stream Completed\n" );
    }
}

#endif /* SUPPORT_PORTAUDIO */

#ifdef SUPPORT_JACKAUDIO

struct jackBuffer {
    void* sampleData;
    int bufferSize;
    struct jackBuffer* nextBuffer;
};

struct jackStreamData {
    jack_port_t *jack_input_port;
    jack_port_t *jack_output_port;
    jack_client_t *jack_client;
    MUTEX lock;
    int readOffset;
    int bytesPerSample;     // bytesPerSample (1, 2 or 4)
    int nChannels;          // num channels (1 or 2)
    int hasFinished;
    struct jackBuffer* currentBuffer;
    struct jackBuffer* lastBuffer;
    struct jackBuffer* freeList;
};

/*
 * This routine will be called by the Jack engine when audio is needed.
 * It may called at interrupt level on some machines, so don't do anything
 * that could mess up the system like calling malloc() or free().
 */
static int
jack_callback(jack_nframes_t nframes, void *userData)
{
    struct jackStreamData *streamData = (struct jackStreamData*)userData;
    struct jackBuffer *buffer = streamData->currentBuffer;
    int nBytesToOutput = streamData->bytesPerSample * streamData->nChannels * nframes;
    // int nBytesToOutput = sizeof (jack_default_audio_sample_t) * nframes;
    int nBytesLeftInBuffer;
    int readOffset;
    int writeOffset = 0;
    int nSent;
    int retVal = paContinue;
    jack_default_audio_sample_t *in, *out;

    in = jack_port_get_buffer (streamData->jack_input_port, nframes);
    out = jack_port_get_buffer (streamData->jack_output_port, nframes);

    readOffset = streamData->readOffset;
  again:
    if (buffer != NULL) {
        nBytesLeftInBuffer = buffer->bufferSize - readOffset;
        if (DEBUGGING) {
            fprintf(stderr, "jack: %d from %p[%d] to [%d]; next: %p last: %p)\n",
                        nBytesLeftInBuffer, buffer, readOffset, writeOffset,
                        buffer->nextBuffer, streamData->lastBuffer);
        }
    } else {
        nBytesLeftInBuffer = 0;
    }
    if (nBytesLeftInBuffer >= nBytesToOutput) {
        memcpy(out+writeOffset, buffer->sampleData+readOffset, nBytesToOutput);
        nSent = nBytesToOutput;
        if (DEBUGGING) {
            fprintf(stderr, "jack: %d from buffer\n", nSent);
        }
        nBytesToOutput = 0;
        readOffset += nSent;
    } else {
        nSent = nBytesLeftInBuffer;
        if (nSent > 0) {
            memcpy(out+writeOffset, buffer->sampleData+readOffset, nBytesLeftInBuffer);
            if (DEBUGGING) {
                fprintf(stderr, "jack: %d from buffer\n", nBytesLeftInBuffer);
            }
            nBytesToOutput -= nSent;
            readOffset += nBytesLeftInBuffer;
        }
    }
    if (buffer != NULL) {
        streamData->readOffset = readOffset;
        if (readOffset >= buffer->bufferSize) {
            LOCK(streamData->lock);
            // next buffer
            streamData->currentBuffer = buffer->nextBuffer;
            streamData->readOffset = readOffset = 0;
            // this buffer onto freeList
            buffer->nextBuffer = streamData->freeList;
            streamData->freeList = buffer;
            if (DEBUGGING) {
                fprintf(stderr, "jack: put on freelist: %p\n", buffer);
            }
            if (streamData->currentBuffer == NULL) {
                if (DEBUGGING) {
                    fprintf(stderr, "jack: done with last buffer\n");
                }
                streamData->lastBuffer = NULL;
                retVal = paComplete;
            }
            UNLOCK(streamData->lock);
            if (nBytesToOutput > 0) {
                writeOffset += nSent;
                if (streamData->currentBuffer == NULL) {
                    memset(out+writeOffset, 0, nBytesToOutput);
                } else {
                    buffer = streamData->currentBuffer;
                    readOffset = 0;
                    if (DEBUGGING) {
                        fprintf(stderr, "jack: %d more\n", nBytesToOutput);
                    }
                    goto again;
                }
            }
        }
    }
    return 0;
}

/**
 * JACK calls this shutdown_callback if the server ever shuts down or
 * decides to disconnect the client.
 */
void
jack_shutdown (void *userData)
{
    struct jackStreamData *streamData = (struct jackStreamData*)userData;
}

#endif /* SUPPORT_JACKAUDIO */

%}
! !

!SoundStream class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 by Claus Gittinger
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    Preliminary (unfinished) interface to an audio device.
    Currently works with
        LINUXs
        SUNs (and other) /dev/audio driver
        IRIX (indy).
        PORTAUDIO (osx).
    On iris, the default setup is for 8 bit mono
    so I can play the standard sound files I have here.
    It needs much more work, for stereo, different sampling rates etc.

    This is an experimental class - its interface & implementation may change in the future.

    [author:]
        Claus Gittinger

    [caveat:]
        this class was written in the early 90's to experiment with a cheap soundblaster board,
        to provide output for a modular synth at that time.
        It is not supported or to be taken serious...
        Actually, it seems to be broken.
"
! !

!SoundStream class methodsFor:'initialization'!

debug:aBoolean
%{
    DEBUGGING = (aBoolean == true);
%}
!

initialize
    UnsupportedOperationSignal isNil ifTrue:[
        UnsupportedOperationSignal := StreamError newSignalMayProceed:true.
        UnsupportedOperationSignal nameClass:self message:#unsupportedOperationSignal.
        UnsupportedOperationSignal notifierString:'unsupported operation'.
    ]
! !

!SoundStream class methodsFor:'instance creation'!

determineConcreteClass
    self allSubclassesDo:[:each |
        each isAbstract ifFalse:[
            each isSupported ifTrue:[
                ^ each
            ]
        ]
    ].
    ^ nil

    "
     self determineConcreteClass
    "
!

new
    self == SoundStream ifTrue:[
        ConcreteClass isNil ifTrue:[
            ConcreteClass := self determineConcreteClass.
            ConcreteClass isNil ifTrue:[
                OpenError raiseErrorString:'missing sound support'.
            ].
        ].
        ^ ConcreteClass new.
    ].
    ^ self basicNew initialize

    "
     SoundStream new
    "
!

readWrite
    "create and return a new soundStream for readWrite (i.e. filtering)"

    |newStream|

    newStream := self new.
    newStream openForReadWrite isNil ifTrue:[^nil].
    ^ newStream

    "SoundStream readWrite"
!

reading
    "create and return a new soundStream for reading (i.e. recording)"

    |newStream|

    newStream := self new.
    newStream openForReading isNil ifTrue:[^nil].
    ^ newStream

    "SoundStream reading"

    "Modified: / 12.12.1997 / 16:51:56 / cg"
!

writing
    "create and return a new soundStream for writing (i.e. playback)"

    |newStream|

    newStream := self new.
    newStream openForWriting isNil ifTrue:[^nil].
    ^ newStream

    "
     SoundStream writing
    "

    "Created: / 17.11.1995 / 17:25:42 / cg"
    "Modified: / 12.12.1997 / 16:51:38 / cg"
!

writing16Bit
    "just an example, has never been tried (I also
     have no samples for this ... leave it as an exercise)"

    |newStream|

    newStream := self new.
    (newStream supportedAudioFormats includesAny:#(S16 U16)) ifFalse:[
        OpenError raiseRequestErrorString:'sound system does not support 16bit audio'
    ].
    newStream bitsPerSample:16.
    newStream openForWriting isNil ifTrue:[^nil].
    ^ newStream

    "SoundStream writing16Bit"

    "Modified: / 12.12.1997 / 16:51:49 / cg"
    "Created: / 21.12.1998 / 00:02:17 / cg"
!

writing16BitStereo
    "just an example, has never been tried (I also
     have no samples for this ... leave it as an exercise)"

    |newStream|

    newStream := self new.
    (newStream supportedAudioFormats includesAny:#(S16 U16)) ifFalse:[
        OpenError raiseRequestErrorString:'sound system does not support 16bit audio'
    ].
    newStream bitsPerSample:16.
    newStream numberOfChannels:2.
    newStream openForWriting isNil ifTrue:[^nil].
    ^ newStream

    "SoundStream writing16BitStereo"

    "Modified: / 12.12.1997 / 16:51:49 / cg"
!

writingFloat
    |newStream|

    newStream := self new.
    (newStream supportedAudioFormats includes:#F32) ifFalse:[
        OpenError raiseRequestErrorString:'sound system does not support float audio'
    ].
    newStream setAudioFormat:#F32.
    newStream numberOfChannels:1.
    newStream openForWriting isNil ifTrue:[^nil].
    ^ newStream

    "SoundStream writingFloat"
!

writingFloatStereo
    |newStream|

    newStream := self new.
    (newStream supportedAudioFormats includes:#F32) ifFalse:[
        OpenError raiseRequestErrorString:'sound system does not support float audio'
    ].
    newStream setAudioFormat:#F32.
    newStream numberOfChannels:2.
    newStream openForWriting isNil ifTrue:[^nil].
    ^ newStream

    "SoundStream writingFloatStereo"
! !

!SoundStream class methodsFor:'Signal constants'!

unsupportedOperationSignal
    ^ UnsupportedOperationSignal
! !

!SoundStream class methodsFor:'conversion helpers'!

aLawToLinear16:aLawValue
    "given an aLaw byte, return the decoded signed 16bit value"

    "
     Linearer Input      Output
     s0000000wxyza...        n000wxyz
     s0000001wxyza...        n001wxyz
     s000001wxyzab...        n010wxyz
     s00001wxyzabc...        n011wxyz
     s0001wxyzabcd...        n100wxyz
     s001wxyzabcde...        n101wxyz
     s01wxyzabcdef...        n110wxyz
     s1wxyzabcdefg...        n111wxyz
    "

    |ix iexp mant|

    ix := aLawValue bitAnd:16r007F. "/ remove sign bit
    iexp := ix rightShift: 4.       "/ extract exponent
    mant := ix bitAnd:16r000F.      "/ now get mantissa
    (iexp > 0) ifTrue:[
        mant := mant + 16.          "/ add leading '1', if exponent > 0
    ].
    mant := (mant bitShift: 4) + 16r0008.   "/ now mantissa left justified and
                                            "/ 1/2 quantization step added
    (iexp > 1) ifTrue:[                     "/ now left shift according exponent
        mant := mant bitShift: (iexp - 1).
    ].
    "/ from 12 to 16bit
    mant := mant bitShift:4.
    aLawValue > 127 ifTrue:[               "/ invert, if negative sample
        ^ mant
    ] ifFalse:[
        ^ mant negated
    ].

    "
     self aLawToLinear16:2r00000000    -8
     self aLawToLinear16:2r00000001    -24
     self aLawToLinear16:2r00010000    -264
     self aLawToLinear16:2r00100000    -528
     self aLawToLinear16:2r01000000    -2112
     self aLawToLinear16:2r11000000    2112
    "
!

linear16ToUlaw:a16bitSignedValue
    "given a 16it signed value, encode into uLaw byte"

    |absVal sign exp mantissa byte|

%{
    /*
     * so heavily used when playing sounds ...
     * made it a primitive.
     */
    if (__isSmallInteger(a16bitSignedValue)) {
        int __sign = 0;
        int __absVal = __intVal(a16bitSignedValue);
        int __exp, __mantissa, __byte;
        static char __uLawExp[] =
                    {
                        0,1,2,2,3,3,3,3,4,4,4,4,4,4,4,4,
                        5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,
                        6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,
                        6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,
                        7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,
                        7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,
                        7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,
                        7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7
                    };

        if (__absVal < 0) {
            if (__absVal <= -32256) {
                RETURN (__MKSMALLINT(0));
            }
            __absVal = -__absVal;
            __sign = 0x80;
        } else {
            if (__absVal >= 32256) {
                RETURN (__MKSMALLINT(128));
            }
        }

        __exp = __uLawExp[__absVal >> 8];
        __mantissa = (__absVal >> (__exp+3)) & 0xF;
        __byte = ~(__sign | (__exp<<4) | __mantissa) & 0xFF;
        RETURN (__MKSMALLINT(__byte));
    }
%}.
    "/
    "/ fallback for non-integral argument
    "/
    a16bitSignedValue isInteger ifFalse:[
        ^ self uLawToLinear16:a16bitSignedValue asInteger
    ].
    ^ 0

    "
     SoundStream uLawToLinear16:(SoundStream linear16ToUlaw:0)
     SoundStream uLawToLinear16:(SoundStream linear16ToUlaw:32256)
     SoundStream uLawToLinear16:(SoundStream linear16ToUlaw:-32256)
     SoundStream uLawToLinear16:(SoundStream linear16ToUlaw:32767)
     SoundStream uLawToLinear16:(SoundStream linear16ToUlaw:-32767)
     SoundStream uLawToLinear16:(SoundStream linear16ToUlaw:100)
     SoundStream uLawToLinear16:(SoundStream linear16ToUlaw:-100)
     SoundStream uLawToLinear16:(SoundStream linear16ToUlaw:104)
     SoundStream uLawToLinear16:(SoundStream linear16ToUlaw:-104)
    "

    "Modified: / 9.12.1997 / 16:46:24 / cg"
!

uLawToLinear16:uLawValue
    "given a uLaw byte, return the decoded signed 16bit value.
     Currently unused - but will be"

    ^ #(
        "0  "     -32256
        "1  "     -31228
        "2  "     -30200
        "3  "     -29172
        "4  "     -28143
        "5  "     -27115
        "6  "     -26087
        "7  "     -25059
        "8  "     -24031
        "9  "     -23002
        "10 "     -21974
        "11 "     -20946
        "12 "     -19918
        "13 "     -18889
        "14 "     -17861
        "15 "     -16833
        "16 "     -16062
        "17 "     -15548
        "18 "     -15033
        "19 "     -14519
        "20 "     -14005
        "21 "     -13491
        "22 "     -12977
        "23 "     -12463
        "24 "     -11949
        "25 "     -11435
        "26 "     -10920
        "27 "     -10406
        "28 "     -9892
        "29 "     -9378
        "30 "     -8864
        "31 "     -8350
        "32 "     -7964
        "33 "     -7707
        "34 "     -7450
        "35 "     -7193
        "36 "     -6936
        "37 "     -6679
        "38 "     -6422
        "39 "     -6165
        "40 "     -5908
        "41 "     -5651
        "42 "     -5394
        "43 "     -5137
        "44 "     -4880
        "45 "     -4623
        "46 "     -4365
        "47 "     -4108
        "48 "     -3916
        "49 "     -3787
        "50 "     -3659
        "51 "     -3530
        "52 "     -3402
        "53 "     -3273
        "54 "     -3144
        "55 "     -3016
        "56 "     -2887
        "57 "     -2759
        "58 "     -2630
        "59 "     -2502
        "60 "     -2373
        "61 "     -2245
        "62 "     -2116
        "63 "     -1988
        "64 "     -1891
        "65 "     -1827
        "66 "     -1763
        "67 "     -1698
        "68 "     -1634
        "69 "     -1570
        "70 "     -1506
        "71 "     -1441
        "72 "     -1377
        "73 "     -1313
        "74 "     -1249
        "75 "     -1184
        "76 "     -1120
        "77 "     -1056
        "78 "     -992
        "79 "     -927
        "80 "     -879
        "81 "     -847
        "82 "     -815
        "83 "     -783
        "84 "     -751
        "85 "     -718
        "86 "     -686
        "87 "     -654
        "88 "     -622
        "89 "     -590
        "90 "     -558
        "91 "     -526
        "92 "     -494
        "93 "     -461
        "94 "     -429
        "95 "     -397
        "96 "     -373
        "97 "     -357
        "98 "     -341
        "99 "     -325
        "100"     -309
        "101"     -293
        "102"     -277
        "103"     -261
        "104"     -245
        "105"     -228
        "106"     -212
        "107"     -196
        "108"     -180
        "109"     -164
        "110"     -148
        "111"     -132
        "112"     -120
        "113"     -112
        "114"     -104
        "115"     -96
        "116"     -88
        "117"     -80
        "118"     -72
        "119"     -64
        "120"     -56
        "121"     -48
        "122"     -40
        "123"     -32
        "124"     -24
        "125"     -16
        "126"     -8
        "127"     0
        "128"     32256
        "129"     31228
        "130"     30200
        "131"     29172
        "132"     28143
        "133"     27115
        "134"     26087
        "135"     25059
        "136"     24031
        "137"     23002
        "138"     21974
        "139"     20946
        "140"     19918
        "141"     18889
        "142"     17861
        "143"     16833
        "144"     16062
        "145"     15548
        "146"     15033
        "147"     14519
        "148"     14005
        "149"     13491
        "150"     12977
        "151"     12463
        "152"     11949
        "153"     11435
        "154"     10920
        "155"     10406
        "156"     9892
        "157"     9378
        "158"     8864
        "159"     8350
        "160"     7964
        "161"     7707
        "162"     7450
        "163"     7193
        "164"     6936
        "165"     6679
        "166"     6422
        "167"     6165
        "168"     5908
        "169"     5651
        "170"     5394
        "171"     5137
        "172"     4880
        "173"     4623
        "174"     4365
        "175"     4108
        "176"     3916
        "177"     3787
        "178"     3659
        "179"     3530
        "180"     3402
        "181"     3273
        "182"     3144
        "183"     3016
        "184"     2887
        "185"     2759
        "186"     2630
        "187"     2502
        "188"     2373
        "189"     2245
        "190"     2116
        "191"     1988
        "192"     1891
        "193"     1827
        "194"     1763
        "195"     1698
        "196"     1634
        "197"     1570
        "198"     1506
        "199"     1441
        "200"     1377
        "201"     1313
        "202"     1249
        "203"     1184
        "204"     1120
        "205"     1056
        "206"     992
        "207"     927
        "208"     879
        "209"     847
        "210"     815
        "211"     783
        "212"     751
        "213"     718
        "214"     686
        "215"     654
        "216"     622
        "217"     590
        "218"     558
        "219"     526
        "220"     494
        "221"     461
        "222"     429
        "223"     397
        "224"     373
        "225"     357
        "226"     341
        "227"     325
        "228"     309
        "229"     293
        "230"     277
        "231"     261
        "232"     245
        "233"     228
        "234"     212
        "235"     196
        "236"     180
        "237"     164
        "238"     148
        "239"     132
        "240"     120
        "241"     112
        "242"     104
        "243"     96
        "244"     88
        "245"     80
        "246"     72
        "247"     64
        "248"     56
        "249"     48
        "250"     40
        "251"     32
        "252"     24
        "253"     16
        "254"     8
        "255"     0
    ) at:(uLawValue + 1)

    "Modified: / 9.12.1997 / 16:34:17 / cg"
! !

!SoundStream class methodsFor:'default values'!

defaultAudioFormat
    OperatingSystem isMSWINDOWSlike ifTrue:[
        ^ #S16
    ].
    OperatingSystem isOSXlike ifTrue:[
        ^ #S16
    ].
    ^ #U8
!

defaultBitsPerSample
    "minimum, supported by all audio systems"

    OperatingSystem isMSWINDOWSlike ifTrue:[
        ^ 16
    ].
    OperatingSystem isOSXlike ifTrue:[
        ^ 16
    ].
    ^ 8
!

defaultNumberOfChannels
    "minimum, supported by all audio systems"

    ^ 1
!

defaultSampleRate
    "minimum, supported by all audio systems"

    ^ 8000
! !

!SoundStream class methodsFor:'playing'!

playSoundFile:aFilename
    "play a soundFile"

    |mime inStream soundStream count totalCount buffer startTime playTime delayedTime waitTime|

    mime := aFilename asFilename mimeTypeFromName.
    mime isAudioType ifFalse:[
        self error:'not an audio file: ',aFilename asFilename baseName
    ].
    self halt.
    inStream := aFilename asFilename readStream.
    inStream isNil ifTrue:[self error:'cannot open'].

    soundStream := self writing.
    soundStream isNil ifTrue:[self error:'cannot open sound device'].

    startTime := Timestamp now.
    totalCount := 0.

    buffer := ByteArray new:4096.
    [(count := inStream nextBytesInto:buffer) > 0] whileTrue:[
        totalCount := totalCount + count.
        soundStream nextPutBytes:count from:buffer.
    ].

    inStream close.
    soundStream flush.

    "/
    "/ at least the linux audio driver behaves funny, if we close too early...
    "/
    playTime := totalCount / soundStream sampleRate.
    delayedTime := Timestamp now secondDeltaFrom: startTime.
    waitTime := playTime - delayedTime + 0.1.

    (Delay forSeconds:waitTime) wait.

    soundStream close.

    "
     SoundStream playSoundFile:'/usr/local/lib/sounds/laugh.snd'
     SoundStream playSoundFile:'/usr/local/lib/sounds/spacemusic.snd'
     SoundStream playSoundFile:'../../goodies/not_ported/sound/sampleFiles/pluck-pcm16.aiff'
    "

    "Created: / 17-11-1995 / 17:25:30 / cg"
    "Modified: / 17-03-2019 / 15:02:57 / Claus Gittinger"
! !

!SoundStream class methodsFor:'queries'!

defaultClass
    ^ ConcreteClass

    "
     SoundStream defaultClass:(SoundStream::JackAudio)
    "
!

defaultClass:aClass
    self assert:(aClass isSupported).
    ConcreteClass := aClass.

    "
     SoundStream defaultClass:(SoundStream::JackAudio)
     SoundStream defaultClass:(SoundStream::PortAudio)
    "
!

isSupported
    ^ false.
!

noteToHertz:noteName
    "notename is one of:
        a1, b2, f3, c#3 etc."

    |octave lastDigit note f sharp|

    octave := 4.
    (lastDigit := noteName last) isDigit ifTrue:[
        octave := lastDigit digitValue
    ].
    note := noteName first.
    sharp := (noteName size > 1) and:[noteName second == $#].
    note = $a ifTrue:[
        f := sharp ifTrue:[466.2] ifFalse:[440]
    ] ifFalse:[ note = $b ifTrue:[
        f := 493.8
    ] ifFalse:[ note = $c ifTrue:[
        f := sharp ifTrue:[277.2] ifFalse:[261.6]
    ] ifFalse:[ note = $d ifTrue:[
        f := sharp ifTrue:[311.1] ifFalse:[293.6]
    ] ifFalse:[ note = $e ifTrue:[
        f := 329.6
    ] ifFalse:[ note = $f ifTrue:[
        f := sharp ifTrue:[370] ifFalse:[349.2]
    ] ifFalse:[ note = $g ifTrue:[
        f := sharp ifTrue:[415.3] ifFalse:[392]
    ]]]]]]].

    f := f * (2 raisedTo:octave-4).
    ^ f.

    "
    SoundStream noteToHertz:'a'
    SoundStream noteToHertz:'g4'
    SoundStream noteToHertz:'e5'
    SoundStream noteToHertz:'b3'
    SoundStream noteToHertz:'c#3'
    "

    "Modified: / 31.1.1999 / 12:06:27 / cg"
!

usedAudio
    "returns a symbol describing which audio system is used;
     one of PORTAUDIO, DEV_AUDIO, WIN32_WAVESOUND, IRIS_AUDIO"

    ConcreteClass isNil ifTrue:[^ nil].
    ^ ConcreteClass nameSymbol
! !

!SoundStream methodsFor:'catching invalid methods'!

pathName:filename
    "catch pathname access - its fixed here"

    self shouldNotImplement
!

pathName:filename in:aDirectory
    "catch pathname access - its fixed here"

    self shouldNotImplement
! !

!SoundStream methodsFor:'error handling'!

lastErrorString
    "return a message string describing the last error"

    lastErrorString notNil ifTrue:[
        ^ lastErrorString
    ].
    ^ super lastErrorString
! !

!SoundStream methodsFor:'mode setting'!

bitsPerSample
    "return the number of bits per sample - usually 8"

    ^ bitsPerSample
!

bitsPerSample:aNumber
    "set the number of bits per sample"

    |supported ok|

    ok := false.
    supported := self supportedAudioFormats.
    aNumber == 16 ifTrue:[
        #(S16 S16_LE S16_BE U16 U16_LE U16_BE) doWithExit:[:fmt :exit |
            (supported includes:fmt) ifTrue:[
                self setAudioFormat:fmt.
                ok := true.
                exit value:nil.
            ]
        ]
    ].
    aNumber == 8 ifTrue:[
        #(S8 U8) doWithExit:[:fmt :exit |
            (supported includes:fmt) ifTrue:[
                self setAudioFormat:fmt.
                ok := true.
                exit value:nil.
            ]
        ]
    ].
    aNumber == 24 ifTrue:[
        #(S24 S24_LE S24_BE U24 U24_LE U24_BE) doWithExit:[:fmt :exit |
            (supported includes:fmt) ifTrue:[
                self setAudioFormat:fmt.
                ok := true.
                exit value:nil.
            ]
        ]
    ].
    aNumber == 32 ifTrue:[
        #(S32 S32_LE S32_BE U32 U32_LE U32_BE) doWithExit:[:fmt :exit |
            (supported includes:fmt) ifTrue:[
                self setAudioFormat:fmt.
                ok := true.
                exit value:nil.
            ]
        ]
    ].
    ok ifFalse:[
        UnsupportedOperationSignal raiseRequestErrorString:'unsupported format'.
    ].
    bitsPerSample := aNumber
!

numberOfChannels
    "return the number of channels (1 or 2; usually 1)"

    ^ numberOfChannels
!

numberOfChannels:aNumber
    "set the number of channels
     - on some devices, this is a nop"

    numberOfChannels := aNumber
!

sampleRate
    "return the sample rate"

    ^ sampleRate
!

sampleRate:aNumber
    "set the sample rate in hertz
     - on some devices, this is a nop"

    self setSampleRate:aNumber.
! !

!SoundStream methodsFor:'private'!

dumpSettings
    "debugging interface - dump the current settings"

    audioFormat == #S16 ifTrue:[
        UninterpretedBytes isBigEndian ifTrue:[
            audioFormat := #S16_BE
        ] ifFalse:[
            audioFormat := #S16_LE
        ]
    ].
    audioFormat == #U16 ifTrue:[
        UninterpretedBytes isBigEndian ifTrue:[
            audioFormat := #U16_BE
        ] ifFalse:[
            audioFormat := #U16_LE
        ]
    ].
    Transcript show:'sampleRate: '; showCR:sampleRate.
    Transcript show:'format: '; showCR:audioFormat.
    Transcript show:'fragmentSize: '; showCR:fragmentSize.
    Transcript show:'channels: '; showCR:numberOfChannels.
    Transcript show:'supported audioFormats: '; showCR:(self supportedAudioFormats).

    "
     self writing dumpSettings; close
    "
!

fileDescriptorOrNil
    handle notNil ifTrue:[
        ^ self fileDescriptor.
    ].
    ^ nil
!

initialize
    "initialize for least common mode"

    super initialize.
    "/ transparent
    eolMode := nil.
    buffered := false.
    binary := true.
    bitsPerSample := self class defaultBitsPerSample.
    audioFormat := self class defaultAudioFormat.
    numberOfChannels := self class defaultNumberOfChannels.
    sampleRate := self class defaultSampleRate.
    pathName := nil.
!

resetSoundCard
    "debugging interface - reset the soundCard"

    ^ UnsupportedOperationSignal raise

    "
     self writing resetSoundCard; dumpSettings; close
    "
!

setAudioFormat:aSymbol
    "set the format of the audio data as specified by aSymbol.
     Returns true if sucessful - may fail with some formats on many sound devices."

    audioFormat := aSymbol.
    ((audioFormat == #U8) or:[audioFormat == #S8]) ifTrue:[
        bitsPerSample := 8.
        ^ self
    ].
    (#(U16 U16_LE U16_BE S16 S16_LE S16_BE) includes:audioFormat) ifTrue:[
        bitsPerSample := 16.
        ^ self
    ].
    (#(U24 U24_LE U24_BE S24 S24_LE S24_BE) includes:audioFormat) ifTrue:[
        bitsPerSample := 24.
        ^ self
    ].
    (#(U32 U32_LE U32_BE S32 S32_LE S32_BE) includes:audioFormat) ifTrue:[
        bitsPerSample := 32.
        ^ self
    ].
    (audioFormat == #F32) ifTrue:[
        bitsPerSample := 32.
        ^ self
    ].
    bitsPerSample := 8.

    "
     self writing dumpSettings; close
     self writing setAudioFormat:#'MU_LAW'; close
     self writing setAudioFormat:#'U8'; dumpSettings; close
     self writing setAudioFormat:#'MPEG'; dumpSettings; close
    "
!

setChannels:nChannels
    "set the number of channels (1 -> mono; 2 -> stereo).
     Returns true if sucessful - may fail with many sound devices."

    numberOfChannels := nChannels.

    "
     self writing setChannels:2; dumpSettings; close
     self writing setChannels:2; setSampleRate:10000; dumpSettings; close
     self writing setChannels:2; setSampleRate:40000; dumpSettings; close
    "
!

setFragmentSize:blockSize
    "set the soundDriver's fragmentSize"

    fragmentSize := blockSize.
!

setSampleRate:hz
    "set the sample rate"

    sampleRate := hz.

    "
     self writing setSampleRate:10000; dumpSettings; close
     self writing setSampleRate:1000; dumpSettings; close
     self writing setSampleRate:8000; dumpSettings; close
    "
!

supportedAudioFormats
    "return a collection of supported audio formats.
     possibly returned symbols are:
        U8        unsigned 8bit samples
        S8        signed 8bit samples
        U16       unsigned 16bit samples in native format
        U16_LE    unsigned 16bit big endian samples
        U16_BE    unsigned 16bit big endian samples
        S16       signed 16bit little endian samples in native format
        S16_LE    signed 16bit little endian samples
        S16_BE    signed 16bit big endian samples
        S24       signed 24bit little endian samples in native format
        S24_LE    signed 24bit little endian samples
        S24_BE    signed 24bit big endian samples
        S32       signed 32bit little endian samples in native format
        S32_LE    signed 32bit little endian samples
        S32_BE    signed 32bit big endian samples
        F32       float samples
        MPEG      audio mpeg encoded
        MU_LAW    u-law encoded 8bit samples
        A_LAW     a-law encoded 8bit samples
        IMA_ADPCM adpcm encoded
     the set of returned symbols depends on the underlying sound hardware.
    "

    ^ #( U8)

    "
     |s formats|

     s := self writing.
     formats := s supportedAudioFormats.
     s close.
     formats
    "
! !

!SoundStream methodsFor:'redefined'!

close
    self flush.
    super close.
! !

!SoundStream protectedMethodsFor:'redefined'!

closeFile
    "a stream has been collected - close the file"

    self subclassResponsibility
! !

!SoundStream methodsFor:'redefined'!

flush
    "wait until all sound has been played"

    self subclassResponsibility

!

isOpen
    self isExecutor ifTrue:[
        ^ false.
    ].
    handle1 notNil ifTrue:[^ true].
    handle2 notNil ifTrue:[^ true].
    ^ handle notNil

    "Modified: / 23-04-2018 / 18:29:42 / stefan"
!

nextBytes:count into:anObject startingAt:start
    "read the next count bytes into an object and return the number of
     bytes read or nil on error.
     Use with ByteArrays only."

    self subclassResponsibility
!

nextPutBytes:count from:anObject startingAt:start
    "write count bytes from an object starting at index start.
     return the number of bytes written or nil on error.
     Redefined, since IRIS audio library cannot be used with stdio.
     (at least I don't know). Use with ByteArrays only."

    self subclassResponsibility
!

openWithMode:aMode attributes:attributeSpec
    self subclassResponsibility
! !

!SoundStream methodsFor:'sine wave generation'!

pause:nSeconds
    "output noting for nSeconds"

    |buffer numSamples restSamples|

    "allocate memory for 1 sec playing time"
    numSamples := self sampleRate.
    audioFormat == #U16 ifTrue:[
        buffer := WordArray new:numSamples withAll:16r8000.
    ] ifFalse:[ audioFormat == #S16 ifTrue:[
        buffer := SignedWordArray new:numSamples withAll:0.
    ] ifFalse:[ audioFormat == #F32 ifTrue:[
        buffer := FloatArray new:numSamples withAll:0.0.
    ] ifFalse:[
        self halt
    ]]].

    1 to:nSeconds truncated do:[:s |
        self nextPutBytes:(numSamples*2) from:buffer startingAt:1
    ].
    restSamples := ((nSeconds - nSeconds truncated) * numSamples) truncated.
    restSamples > 0 ifTrue:[
        self nextPutBytes:(restSamples*2) from:buffer startingAt:1
    ].
!

playSine16:freq forSeconds:nSeconds
    "output some tone for some time
     in S16 audioFormat - a test method"

    |buffer numSamples val scale isUnsigned restSamples|

    (audioFormat startsWith:#U16) ifFalse:[
        (audioFormat startsWith:#S16) ifFalse:[
            self error:'must be in 16bit mode' mayProceed:true.
            ^ self
        ]
    ].

    numSamples := self sampleRate.
    buffer := WordArray new:numSamples.

    "fill it with a sine wave"

    isUnsigned := audioFormat startsWith:#U16.

    scale := freq * 2 * (Float pi).
    1 to:numSamples do:[:i |
        val := (scale * i / self sampleRate) sin.
        val := (val * 16r7FFF) rounded.
        isUnsigned ifTrue:[
            val := val + 32768
        ].
        buffer at:i put:(val bitAnd:16rFFFF)
    ].

    1 to:nSeconds truncated do:[:s |
        self nextPutBytes:(numSamples*2) from:buffer startingAt:1
    ].
    restSamples := ((nSeconds - nSeconds truncated) * numSamples) truncated.
    restSamples > 0 ifTrue:[
        self nextPutBytes:(restSamples*2) from:buffer startingAt:1
    ].

    "
     SoundStream writing setAudioFormat:#S16; playSine16:440 forSeconds:2; close
     SoundStream writing setAudioFormat:#S16; playSine16:880 forSeconds:2; close
     SoundStream writing setAudioFormat:#S16; playSine16:1760 forSeconds:2; close
     SoundStream writing setAudioFormat:#S16; playSine16:3520 forSeconds:2; close
     SoundStream writing tuneTone:440; close

     SoundStream writing setAudioFormat:#U16; playSine16:880 forSeconds:2; close
     SoundStream writing setAudioFormat:#U16_LE; playSine16:880 forSeconds:2; close
    "

    "Modified: / 31.1.1999 / 12:12:41 / cg"
!

playSine:freq forSeconds:nSeconds
    "output some tone for some time - a test method"

    audioFormat == #F32 ifTrue:[
        self playSineF32:freq forSeconds:nSeconds.
        ^ self.
    ].
    self playSine16:freq forSeconds:nSeconds.

    "
     SoundStream writing setAudioFormat:#F32; playSine:440 forSeconds:2; close
     SoundStream writing setAudioFormat:#F32; playSine:880 forSeconds:2; close
     SoundStream writing setAudioFormat:#F32; playSine:1760 forSeconds:2; close
     SoundStream writing setAudioFormat:#F32; playSine:3520 forSeconds:2; close
    "
!

playSineF32:freq forSeconds:nSeconds
    "output some tone for some time
     in F32 audioFormat - a test method"

    |buffer numSamples val scale restSamples numChannels|

    (audioFormat == #F32) ifFalse:[
        self error:'must be in float mode' mayProceed:true.
    ].

    numSamples := self sampleRate.
    numChannels := self numberOfChannels.
    buffer := FloatArray new:(numSamples * numChannels).

    "fill it with a sine wave"

    scale := freq * 2 * (Float pi).
    numChannels == 2 ifTrue:[
        1 to:numSamples do:[:i |
            val := (scale * i / self sampleRate) sin.
            buffer at:(i-1)*2 put:val.
            buffer at:(i-1)*2+1 put:0.
        ].
    ] ifFalse:[
        1 to:numSamples do:[:i |
            val := (scale * i / self sampleRate) sin.
            buffer at:i put:val
        ].
    ].

    1 to:nSeconds truncated do:[:s |
        self nextPutBytes:(numSamples*4) from:buffer startingAt:1
    ].
    restSamples := ((nSeconds - nSeconds truncated) * numSamples) truncated.
    restSamples > 0 ifTrue:[
        self nextPutBytes:(restSamples*4) from:buffer startingAt:1
    ].

    "
     SoundStream writing setAudioFormat:#F32; playSineF32:440 forSeconds:2; close
     SoundStream writing setAudioFormat:#F32; playSineF32:880 forSeconds:2; close
     SoundStream writing setAudioFormat:#F32; playSineF32:1760 forSeconds:2; close
     SoundStream writing setAudioFormat:#F32; playSineF32:3520 forSeconds:2; close
    "

    "Modified: / 31.1.1999 / 12:12:41 / cg"
!

testMelody
    #(g 0.5
      e 0.5
      e 0.5
      f 0.5
      d 0.5
      d 0.5
      c 0.5
      d 0.5
      e 0.5
      f 0.5
      g 0.5
      g 0.5
      g 0.5
    ) pairWiseDo:[:note :duration |
        self playSine:(self class noteToHertz:note) forSeconds:duration.
        self pause:0.05.
    ].

    "
     self writing testMelody; close
    "

    "Created: / 31.1.1999 / 12:07:45 / cg"
    "Modified: / 31.1.1999 / 12:16:09 / cg"
!

testOctaves
    3 timesRepeat:[
        self playSine:220 forSeconds:0.5.
        self playSine:440 forSeconds:0.5.
        self playSine:880 forSeconds:0.5.
        self playSine:1760 forSeconds:0.5.
        self playSine:3520 forSeconds:0.5.
    ]

    "
     self writing testOctaves; close
    "

    "Created: / 31.1.1999 / 12:07:45 / cg"
    "Modified: / 31.1.1999 / 12:16:09 / cg"
!

tuneTone
    ^ self tuneTone:440

    "
    SoundStream debug:true
     SoundStream writing tuneTone; close
     SoundStream writing setSampleRate:4000; tuneTone; close
     SoundStream writing setSampleRate:8000; tuneTone; close
     SoundStream writing setSampleRate:10000; tuneTone; close
     SoundStream writing setSampleRate:20000; tuneTone; close
     SoundStream writing setSampleRate:40000; tuneTone; close
     SoundStream writing setSampleRate:44000; tuneTone; close

     SoundStream writing setSampleRate:40000; dumpSettings; close
     SoundStream writing setSampleRate:20000; dumpSettings; close
    "

    "Modified: / 31.1.1999 / 12:06:27 / cg"
!

tuneTone16:freq seconds:nSeconds
    "output some tone for nSeconds in S16 audioFormat - a test method"

    |buffer numSamples val scale restSamples|

    (audioFormat startsWith:#U16) ifFalse:[
        (audioFormat startsWith:#S16) ifFalse:[
            self error:'must be in 16bit mode' mayProceed:true.
            ^ self
        ]
    ].

    "allocate memory for 1 sec playing time"
    numSamples := self sampleRate.
    audioFormat == #U16 ifTrue:[
        buffer := WordArray new:numSamples.
    ] ifFalse:[
        buffer := SignedWordArray new:numSamples.
    ].

    "fill it with a sine wave"
    "/ buffer is 1 second,
    "/ contains freq periods,
    "/ each of which is 0 .. 2pi
    scale := freq * 2 * (Float pi) / numSamples.
    1 to:numSamples do:[:i |
        val := (scale * (i-1)) sin.
        val := (val * 16r7FFF) rounded.
        audioFormat == #U16 ifTrue:[
            val := val + 16r8000
        ].
        buffer at:i put:val
    ].

    1 to:nSeconds truncated do:[:s |
        self nextPutBytes:(numSamples*2) from:buffer startingAt:1
    ].
    restSamples := ((nSeconds - nSeconds truncated) * numSamples) truncated.
    restSamples > 0 ifTrue:[
        self nextPutBytes:(restSamples*2) from:buffer startingAt:1
    ].

    "of course, the frequency should be below half the
     sampleRate - hear below ...

     SoundStream writing setSampleRate:4000; tuneTone16:440 seconds:3; close
     SoundStream writing setSampleRate:8000; tuneTone16:440 seconds:3; close
     SoundStream writing setSampleRate:10000; tuneTone16:440 seconds:1; close
     SoundStream writing setSampleRate:20000; tuneTone16:440 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone16:440 seconds:3; close
     SoundStream writing tuneTone16:440 seconds:1; close
    "

    "Modified: / 21.12.1998 / 09:11:30 / cg"
!

tuneTone8:freq seconds:nSeconds
    "output some tone for nSeconds in U8 audioFormat - a test method"

    |buffer numSamples val scale restSamples|

    (audioFormat == #U8) ifFalse:[
        (audioFormat == #S8) ifFalse:[
            self error:'must be in 8bit mode' mayProceed:true.
            ^ self
        ]
    ].

    "allocate memory for 1 sec playing time"
    numSamples := self sampleRate.
    buffer := ByteArray new:numSamples.

    "fill it with a sine wave"

    scale := freq * 2 * (Float pi) / numSamples.
    1 to:numSamples do:[:i |
        val := (scale * i) sin.
        val := (val * 127) rounded.
        audioFormat == #U8 ifTrue:[
            val := val + 16r80.
        ].
        buffer at:i put:(val bitAnd:16rFF)
    ].

    1 to:nSeconds truncated do:[:s |
        self nextPutBytes:numSamples from:buffer startingAt:1
    ].
    restSamples := ((nSeconds - nSeconds truncated) * numSamples) truncated.
    restSamples > 0 ifTrue:[
        self nextPutBytes:restSamples from:buffer startingAt:1
    ].

    "of course, the frequency should be below half the
     sampleRate - hear below ...

     SoundStream writing tuneTone; close
     SoundStream writing setSampleRate:4000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:4000; tuneTone:2000 seconds:1; close
     SoundStream writing setSampleRate:8000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:8000; tuneTone:2000 seconds:1; close
     SoundStream writing setSampleRate:8000; tuneTone:4000 seconds:1; close
     SoundStream writing setSampleRate:10000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:10000; tuneTone:2000 seconds:1; close
     SoundStream writing setSampleRate:10000; tuneTone:4000 seconds:1; close
     SoundStream writing setSampleRate:20000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:20000; tuneTone:2000 seconds:1; close
     SoundStream writing setSampleRate:20000; tuneTone:4000 seconds:1; close
     SoundStream writing setSampleRate:20000; tuneTone:8000 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:2000 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:4000 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:8000 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:10000 seconds:1; close
    "

    "Modified: / 15.12.1997 / 13:43:05 / cg"
    "Created: / 31.1.1999 / 12:05:17 / cg"
!

tuneTone:freq
    self tuneTone:freq seconds:3

    "
     SoundStream writing tuneTone:880; close
     SoundStream writing setSampleRate:4000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:4000; tuneTone:880 seconds:1; close
     SoundStream writing setSampleRate:8000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:8000; tuneTone:880 seconds:1; close
     SoundStream writing setSampleRate:10000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:10000; tuneTone:880 seconds:1; close

     SoundStream writing setSampleRate:20000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:20000; tuneTone:880 seconds:1; close

     SoundStream writing setSampleRate:40000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:880 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:1760 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:3520 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:7020 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:14040 seconds:1; close

     SoundStream writing setSampleRate:44100; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:44100; tuneTone:880 seconds:1; close
     SoundStream writing setSampleRate:44100; tuneTone:1760 seconds:1; close
     SoundStream writing setSampleRate:44100; tuneTone:3520 seconds:1; close
     SoundStream writing setSampleRate:44100; tuneTone:7020 seconds:1; close
     SoundStream writing setSampleRate:44100; tuneTone:14040 seconds:1; close

     SoundStream writing setSampleRate:20000; dumpSettings; close
    "

    "Modified: / 31.1.1999 / 12:07:14 / cg"
!

tuneTone:freq seconds:nSeconds
    ((audioFormat startsWith:#S16) or:[audioFormat startsWith:#U16]) ifTrue:[
        ^ self tuneTone16:freq seconds:nSeconds
    ].
    audioFormat == #F32 ifTrue:[
        ^ self tuneToneF32:freq seconds:nSeconds
    ].
    audioFormat == #MU_LAW ifTrue:[
        ^ self tuneToneMU:freq seconds:nSeconds
    ].
    self tuneTone8:freq seconds:nSeconds

    "
     SoundStream writing tuneTone:880; close
     SoundStream writing setSampleRate:4000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:4000; tuneTone:880 seconds:1; close
     SoundStream writing setSampleRate:8000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:8000; tuneTone:880 seconds:1; close
     SoundStream writing setSampleRate:10000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:10000; tuneTone:880 seconds:1; close

     SoundStream writing setSampleRate:20000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:20000; tuneTone:880 seconds:1; close

     SoundStream writing setSampleRate:40000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:880 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:1760 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:3520 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:7020 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:14040 seconds:1; close

     SoundStream writing setSampleRate:44100; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:44100; tuneTone:880 seconds:1; close
     SoundStream writing setSampleRate:44100; tuneTone:1760 seconds:1; close
     SoundStream writing setSampleRate:44100; tuneTone:3520 seconds:1; close
     SoundStream writing setSampleRate:44100; tuneTone:7020 seconds:1; close
     SoundStream writing setSampleRate:44100; tuneTone:14040 seconds:1; close

     SoundStream writing setSampleRate:20000; dumpSettings; close
    "

    "Modified: / 31.1.1999 / 12:07:14 / cg"
!

tuneToneF32:freq seconds:nSeconds
    "output some tone for nSeconds in F32 audioFormat - a test method"

    |buffer numSamples val scale restSamples|

    (audioFormat == #F32) ifFalse:[
        self error:'must be in f32 mode' mayProceed:true.
        ^ self
    ].

    "allocate memory for 1sec playing time"
    numSamples := self sampleRate.
    buffer := FloatArray new:numSamples.

    "fill it with a sine wave"

    scale := freq * 2 * (Float pi) / numSamples.
    1 to:numSamples do:[:i |
        val := (scale * i) sin.
        buffer at:i put:val
    ].

    1 to:nSeconds truncated do:[:s |
        self nextPutBytes:(numSamples*4) from:buffer startingAt:1
    ].
    restSamples := ((nSeconds - nSeconds truncated) * numSamples) truncated.
    restSamples > 0 ifTrue:[
        self nextPutBytes:(restSamples*4) from:buffer startingAt:1
    ].

    "of course, the frequency should be below half the
     sampleRate - hear below ...

     SoundStream debug:true
     SoundStream debug:false

     SoundStream writing tuneTone; close
     SoundStream writing setAudioFormat:#F32; tuneTone; close
     SoundStream writing setSampleRate:4000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:4000; tuneTone:2000 seconds:1; close
     SoundStream writing setSampleRate:8000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:8000; tuneTone:2000 seconds:1; close
     SoundStream writing setSampleRate:8000; tuneTone:4000 seconds:1; close
     SoundStream writing setSampleRate:10000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:10000; tuneTone:2000 seconds:1; close
     SoundStream writing setSampleRate:10000; tuneTone:4000 seconds:1; close
     SoundStream writing setSampleRate:20000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:20000; tuneTone:2000 seconds:1; close
     SoundStream writing setSampleRate:20000; tuneTone:4000 seconds:1; close
     SoundStream writing setSampleRate:20000; tuneTone:8000 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:440 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:2000 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:4000 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:8000 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneTone:10000 seconds:1; close
    "

    "Modified: / 15.12.1997 / 13:43:05 / cg"
    "Created: / 31.1.1999 / 12:05:17 / cg"
!

tuneToneMU:freq seconds:nSeconds
    "output some tone for nSeconds in MU_LAW audioFormat - a test method"

    |buffer numSamples val scale restSamples|

    "allocate memory for 1sec playing time"
    numSamples := self sampleRate.
    buffer := ByteArray new:numSamples.

    "fill it with a sine wave"

    scale := freq * 2 * (Float pi) / numSamples.
    1 to:numSamples do:[:i |
        val := (scale * i) sin.
        val := (val * 16r7FFF) rounded.
        buffer at:i put:(self class linear16ToUlaw:val)
    ].

    1 to:nSeconds truncated do:[:s |
        self nextPutBytes:numSamples from:buffer startingAt:1
    ].
    restSamples := ((nSeconds - nSeconds truncated) * numSamples) truncated.
    restSamples > 0 ifTrue:[
        self nextPutBytes:restSamples from:buffer startingAt:1
    ].

    "of course, the frequency should be below half the
     sampleRate - hear below ...

     SoundStream writing setSampleRate:8000; tuneToneMU:440 seconds:1; close
     SoundStream writing setSampleRate:10000; tuneToneMU:440 seconds:1; close
     SoundStream writing setSampleRate:20000; tuneToneMU:440 seconds:1; close
     SoundStream writing setSampleRate:40000; tuneToneMU:440 seconds:1; close
    "

    "Modified: / 15.12.1997 / 13:46:19 / cg"
! !

!SoundStream::DevAudio class methodsFor:'default values'!

defaultSampleRate
    "minimum, supported by all audio systems"

%{
#ifdef SUPPORT_DEV_AUDIO
    RETURN (__MKSMALLINT(DEV_AUDIO_DEFAULT_FREQ));
#endif
%}.

    ^ 8000
! !

!SoundStream::DevAudio class methodsFor:'documentation'!

documentation
"
    interface to /dev/audio (sun, hpux, linux, ...)
"
! !

!SoundStream::DevAudio class methodsFor:'queries'!

isSupported
%{
#ifdef SUPPORT_DEV_AUDIO
    RETURN(true);
#endif
%}.
    ^ false.
! !

!SoundStream::DevAudio methodsFor:'misc'!

dumpSettings
    "debugging interface - dump the current settings"

    |fd blockSize speed channels stereo format|

    fd := self fileDescriptorOrNil.

    audioFormat == #S16 ifTrue:[
        UninterpretedBytes isBigEndian ifTrue:[
            audioFormat := #S16_BE
        ] ifFalse:[
            audioFormat := #S16_LE
        ]
    ].
    audioFormat == #U16 ifTrue:[
        UninterpretedBytes isBigEndian ifTrue:[
            audioFormat := #U16_BE
        ] ifFalse:[
            audioFormat := #U16_LE
        ]
    ].

%{
#ifdef SUPPORT_DEV_AUDIO
    if (fd != nil) {
        int f = __intVal(fd);
        int __blockSize = -1;
        int __speed = -1;
        int __channels = __intVal(__INST(numberOfChannels));
        int __stereo = __channels > 1;
        int __format = -1;

        channels = nil;
        blockSize = nil;
        stereo = nil;
        speed = nil;

# if defined(SNDCTL_DSP_GETBLKSIZE)
        if (ioctl(f, SNDCTL_DSP_GETBLKSIZE, &__blockSize) >= 0) {
            blockSize = __MKSMALLINT(__blockSize);
        }
# endif

# if defined(SNDCTL_DSP_CHANNELS)
        if (ioctl(f, SNDCTL_DSP_CHANNELS, &__channels) >= 0) {
            channels = __MKSMALLINT(__channels);
            stereo = __MKSMALLINT(__channels > 1);
        }
# else
#  if defined(SNDCTL_DSP_STEREO)
        if (ioctl(f, SNDCTL_DSP_STEREO, &__stereo) >= 0) {
            stereo = __MKSMALLINT(__stereo);
        }
#  endif
# endif

# if defined(SNDCTL_DSP_SPEED)
        if (ioctl(f, SNDCTL_DSP_SPEED, &__speed) >= 0) {
            speed = __MKSMALLINT(__speed);
        }
# endif

# if defined(SNDCTL_DSP_GETFMT)
        if (ioctl(f, SNDCTL_DSP_GETFMT, &__format) >= 0) {
            format = __MKSMALLINT(__format);
        }
# else
#  if defined(SNDCTL_DSP_SETFMT) && defined(AFMT_QUERY)
        __format = AFMT_QUERY;
        if (ioctl(f, SNDCTL_DSP_SETFMT, &__format) >= 0) {
            switch (__format) {
#   ifdef AFMT_MU_LAW
                case AFMT_MU_LAW:
                    format = @symbol(MU_LAW);
                    break;
#   endif
#   ifdef AFMT_A_LAW
                case AFMT_A_LAW:
                    format = @symbol(A_LAW);
                    break;
#   endif
#   ifdef AFMT_U8
                case AFMT_U8:
                    format = @symbol(U8);
                    break;
#   endif
#   ifdef AFMT_S8
                case AFMT_S8:
                    format = @symbol(S8);
                    break;
#   endif
#   ifdef AFMT_S16_LE
                case AFMT_S16_LE:
                    format = @symbol(S16_LE);
                    break;
#   endif
#   ifdef AFMT_S16_BE
                case AFMT_S16_BE:
                    format = @symbol(S16_BE);
                    break;
#   endif
#   ifdef AFMT_U16_LE
                case AFMT_U16_LE:
                    format = @symbol(U16_LE);
                    break;
#   endif
#   ifdef AFMT_U16_BE
                case AFMT_U16_BE:
                    format = @symbol(U16_BE);
                    break;
#   endif
#   ifdef AFMT_MPEG
                case AFMT_MPEG:
                    format = @symbol(MPEG);
                    break;
#   endif
                default:
                    format = nil;
            }
        }
    }
#  endif
# endif
#endif /* SUPPORT_DEV_AUDIO */

%}.
    format notNil ifTrue:[
        Transcript show:'format: '; showCR:format
    ].
    blockSize notNil ifTrue:[
        Transcript show:'blockSize: '; showCR:blockSize
    ].
    speed notNil ifTrue:[
        Transcript show:'speed: '; showCR:speed
    ].
    channels notNil ifTrue:[
        Transcript show:'channels: '; showCR:channels
    ].
    stereo notNil ifTrue:[
        Transcript show:'stereo: '; showCR:stereo
    ].

    Transcript show:'supported audioFormats: '; showCR:(self supportedAudioFormats).

    "
     self writing dumpSettings; close
    "
!

flush
    "wait until all sound has been played"

    self fileDescriptorOrNil isNil ifTrue:[^ self].
    super flush.
! !

!SoundStream::DevAudio methodsFor:'open & close'!

closeFile
    "a stream has been collected - close the file"

%{
#ifdef SUPPORT_DEV_AUDIO
    OBJ fp;
    int fd;
    FILE *f;

    if ((fp = __INST(handle)) != nil) {
        f = __FILEVal(fp);
        __INST(handle) = nil;
# ifdef LINUX
        sigsetmask(~0);
# endif
        if (__INST(buffered) == true) {
            fflush(f);
            fclose(f);
        } else {
            fd = fileno(f);
            close(fd);
            fclose(f);
        }
# ifdef LINUX
        sigsetmask(0);
# endif
    }
    RETURN (self);
#endif /* SUPPORT_DEV_AUDIO */
%}.
!

openWithMode:aMode attributes:attributeSpec
    |ok error errorStringOrNil|

%{
#ifdef SUPPORT_DEV_AUDIO
      int __fd;
      int __mode;
      FILE *f;

      ok = false;
      if (strcmp(__stringVal(aMode), "w") == 0) {
          __mode = O_WRONLY;
      } else if (strcmp(__stringVal(aMode), "r") == 0) {
          __mode = O_RDONLY;
      } else {
          __mode = O_RDWR;
      }
      do {
          __BEGIN_INTERRUPTABLE__
          __fd = open((char *) __stringVal(__INST(pathName)), __mode /* |O_NDELAY */);
          __END_INTERRUPTABLE__
      } while ((__fd < 0) && (errno == EINTR));

      if (__fd >= 0) {
          /*
           * make it a FILE *
           */
          f = fdopen(__fd, __stringVal(aMode));
          if (! f) {
              error = __mkSmallInteger(errno);
              __BEGIN_INTERRUPTABLE__
              close(__fd);
              __END_INTERRUPTABLE__
              goto out;
          }
          setbuf(f, NULL);
          __INST(buffered) = false;
          __INST(handle) = __MKEXTERNALADDRESS(f);
          __STORESELF(handle);

#if defined(PCM_ENABLE_OUTPUT) && defined(PCM_ENABLE_INPUT)
# if defined(SNDCTL_DSP_SETTRIGGER)
          if (__mode == O_RDWR) {
              int enable_bits = ~(PCM_ENABLE_OUTPUT|PCM_ENABLE_INPUT);

              if (ioctl(__fd, SNDCTL_DSP_SETTRIGGER, &enable_bits) == -1)
              {
                  console_fprintf(stderr, "can't request synchronous start of fullduplex operation");
              }
          }
# endif
#endif
          ok = true;
      } else {
          error = __mkSmallInteger(errno);
      }
out:;
#endif /* SUPPORT_DEV_AUDIO */
%}.
    ok == false ifTrue:[
        lastErrorString := errorStringOrNil.
        lastErrorNumber := error ? -1.
        self openError:error.
        "normally not reached"
        ^ nil.
    ].
    self registerForFinalization.
! !

!SoundStream::DevAudio methodsFor:'private'!

initialize
    "initialize for least common mode"

    super initialize.

    OperatingSystem isUNIXlike ifTrue:[
        '/dev/audio' asFilename exists ifTrue:[
            "/
            "/ sunos or linux
            "/
            pathName := '/dev/audio'.
        ].
    ].
!

resetSoundCard
    "debugging interface - reset the soundCard"

    |fd|

    fd := self fileDescriptorOrNil.
    fd isNil ifTrue:[
        self errorNotOpen.
        ^ nil
    ].
%{
#ifdef SUPPORT_DEV_AUDIO
    int f = __intVal(fd);

    if (__isSmallInteger(fd)) {
        int __dummy;
# if defined(SNDCTL_DSP_RESET)
        if (ioctl(f, SNDCTL_DSP_RESET, &__dummy) >= 0) {
            RETURN (self);
        }
# endif
    }
#endif /* SUPPORT_DEV_AUDIO */
%}.
    ^ UnsupportedOperationSignal raise

    "
     self writing resetSoundCard; dumpSettings; close
    "
!

setAudioFormat:aSymbol
    "set the format of the audio data as specified by aSymbol.
     Returns true if sucessful - may fail with some formats on many sound devices."

    |fd ok|

    audioFormat == aSymbol ifTrue:[^ self].
    super setAudioFormat:aSymbol.

    fd := self fileDescriptor.
    fd isNil ifTrue:[
        ^ self
    ].
%{
#ifdef SUPPORT_DEV_AUDIO
    OBJ sym = aSymbol;

    if (__isSmallInteger(fd)) {
        int f = __intVal(fd);
        int __fmt = 0, __fmtWant;
        union {
            unsigned short us;
            unsigned char ub[2];
        } u;

        if (__isSymbol(sym)) {
            if (sym == @symbol(U16)) {
                u.us = 0x1234;
                if (u.ub[0] == 0x34) {
                    /* printf("U16_LE\n"); */
                    sym = @symbol(U16_LE);
                } else {
                    /* printf("U16_BE\n"); */
                    sym = @symbol(U16_BE);
                }
            } else if (sym == @symbol(S16)) {
                u.us = 0x1234;
                if (u.ub[0] == 0x34) {
                    /* printf("S16_LE\n"); */
                   sym = @symbol(S16_LE);
                } else {
                    /* printf("S16_BE\n"); */
                   sym = @symbol(S16_BE);
                }
            }

            if (0) {
# ifdef AFMT_MU_LAW
            } else if (sym == @symbol(MU_LAW)) {
                __fmt = AFMT_MU_LAW;
# endif
# ifdef AFMT_A_LAW
            } else if (sym == @symbol(A_LAW)) {
                __fmt = AFMT_A_LAW;
# endif
# ifdef AFMT_IMA_ADPCM
            } else if (sym == @symbol(IMA_ADPCM)) {
                __fmt = AFMT_IMA_ADPCM;
# endif
# ifdef AFMT_U8
            } else if (sym == @symbol(U8)) {
                __fmt = AFMT_U8;
# endif
# ifdef AFMT_S8
            } else if (sym == @symbol(S8)) {
                __fmt = AFMT_S8;
# endif
# ifdef AFMT_U16_LE
            } else if (sym == @symbol(U16_LE)) {
                __fmt = AFMT_U16_LE;
# endif
# ifdef AFMT_U16_BE
            } else if (sym == @symbol(U16_BE)) {
                __fmt = AFMT_U16_BE;
# endif
# ifdef AFMT_S16_LE
            } else if (sym == @symbol(S16_LE)) {
                __fmt = AFMT_S16_LE;
# endif
# ifdef AFMT_S16_BE
            } else if (sym == @symbol(S16_BE)) {
                __fmt = AFMT_S16_BE;
# endif
# ifdef AFMT_MPEG
            } else if (sym == @symbol(MPEG)) {
                __fmt = AFMT_MPEG;
# endif

# ifdef AUDIO_FORMAT_LINEAR16BIT
            } else if (sym == @symbol(S16)) {
                __fmt = AUDIO_FORMAT_LINEAR16BIT;
# endif
# ifdef AUDIO_FORMAT_ULAW
            } else if (sym == @symbol(MU_LAW)) {
                __fmt = AUDIO_FORMAT_ULAW;
# endif
# ifdef AUDIO_FORMAT_ALAW
            } else if (sym == @symbol(A_LAW)) {
                __fmt = AUDIO_FORMAT_ALAW;
# endif
            } else {
                console_fprintf(stderr, "bad format: %s\n", __stringVal(sym));
                ok = false;
                goto bad;
            }
        }

# ifdef SNDCTL_DSP_SETFMT
        __fmtWant = __fmt;

        if (ioctl(f, SNDCTL_DSP_SETFMT, &__fmt) >= 0) {
            if (__fmt == __fmtWant) {
                __INST(audioFormat) = sym;
            } else {
                /* console_fprintf(stderr, "want: %x; got: %x\n", __fmtWant, __fmt); */
            }
        } else {
            /* console_fprintf(stderr, "got err-ret from setFmp %x\n", __fmt); */
            ok = false;
        }
# else
#  ifdef AUDIO_SET_DATA_FORMAT /* hpux */
        if (ioctl (f, AUDIO_SET_DATA_FORMAT, __fmt)) {
            /* console_fprintf(stderr, "got err-ret from AUDIO_SET_DATA_FORMAT\n"); */
        }
#  endif
# endif /* SNDCTL_DSP_SETFMT */

bad: ;
    }
#endif /* SUPPORT_DEV_AUDIO */
%}.

    "
     self writing dumpSettings; close
     self writing setAudioFormat:#'MU_LAW'; close
     self writing setAudioFormat:#'U8'; dumpSettings; close
     self writing setAudioFormat:#'MPEG'; dumpSettings; close
    "
!

setChannels:nChannels
    "set the number of channels (1 -> mono; 2 -> stereo).
     Returns true if sucessful - may fail with many sound devices."

    |fd|

    numberOfChannels := nChannels.

    fd := self fileDescriptorOrNil.
    fd isNil ifTrue:[
        ^ self
    ].
%{

#ifdef SUPPORT_DEV_AUDIO
    if (__isSmallInteger(fd) && __isSmallInteger(nChannels)) {
        int f = __intVal(fd);
        int __nCh = __intVal(nChannels);

# ifdef SNDCTL_DSP_STEREO
        if ((__nCh == 1) || (__nCh == 2)) {
            int __stereo = (__nCh == 2) ? 1 : 0;

            if (ioctl(f, SNDCTL_DSP_STEREO, &__stereo) >= 0) {
                if (__stereo == 0) {
                    __INST(numberOfChannels) = __MKSMALLINT(1);
                } else {
                    __INST(numberOfChannels) = __MKSMALLINT(2);
                }
                RETURN (self);
            }
        }
# else
#  ifdef SOUND_PCM_WRITE_CHANNELS
        if (ioctl(f, SOUND_PCM_WRITE_CHANNELS, &__nCh) >= 0) {
            RETURN (self);
        }
#  else
#   ifdef AUDIO_SET_CHANNELS /* hpux */
        if (ioctl (f, AUDIO_SET_CHANNELS, __nCh)) {
            /* console_fprintf(stderr, "got err-ret from AUDIO_SET_CHANNELS\n"); */
            RETURN (self);
        }
#   endif
#  endif
# endif
    }
#endif /* SUPPORT_DEV_AUDIO */
%}.

    "
     self writing setChannels:2; dumpSettings; close
     self writing setChannels:2; setSampleRate:10000; dumpSettings; close
     self writing setChannels:2; setSampleRate:40000; dumpSettings; close
    "
!

setFragmentSize:blockSize
    "set the soundDriver's fragmentSize"

    |fd|

    fragmentSize := blockSize.

    fd := self fileDescriptorOrNil.
    fd isNil ifTrue:[
        ^ self
    ].

%{
#ifdef SUPPORT_DEV_AUDIO
    int f = __intVal(fd);
    int __blockSize = __intVal(blockSize);

    if (__isSmallInteger(fd) && __isSmallInteger(blockSize)) {
        __blockSize = __intVal(blockSize);
# if defined(SNDCTL_DSP_SETFRAGMENT)
        if (ioctl(f, SNDCTL_DSP_SETFRAGMENT, &__blockSize) >= 0) {
            RETURN (self);
        }
# endif
# ifdef AUDIO_SET_CHANNELS /* hpux */
        if (ioctl (f, AUDIO_SET_TXBUFSIZE, __blockSize)) {
            /* console_fprintf(stderr, "got err-ret from AUDIO_SET_TXBUFSIZE\n"); */
            RETURN (self);
        }
# endif
    }
#endif // SUPPORT_DEV_AUDIO
%}.
!

setSampleRate:hz
    "set the sample rate"

    |fd|

    sampleRate := hz.

    fd := self fileDescriptorOrNil.
    fd isNil ifTrue:[
        ^ self
    ].
%{
#ifdef SUPPORT_DEV_AUDIO
    int f = __intVal(fd);
    int __rate = __intVal(hz);

    if (__isSmallInteger(fd) && __isSmallInteger(hz)) {
        int __rateWant = __rate;

# if defined(SNDCTL_DSP_SPEED)
        if (ioctl(f, SNDCTL_DSP_SPEED, &__rate) >= 0) {
            if (__rate != __rateWant) {
                console_fprintf(stderr, "SoundStream [warning]: actual rate is %d\n", __rate);
                hz = __MKSMALLINT(__rate);
            }
            __INST(sampleRate) = hz;
            RETURN (self);
        }
# else
#  if defined(SOUND_PCM_WRITE_RATE)
        if (ioctl(f, SOUND_PCM_WRITE_RATE, &__rate) >= 0) {
            if (__rate != __rateWant) {
                console_fprintf(stderr, "SoundStream [warning]: actual rate is %d\n", __rate);
                hz = __MKSMALLINT(__rate);
            }
            __INST(sampleRate) = hz;
            RETURN (self);
        }
#  else
#   ifdef AUDIO_SET_SAMPLE_RATE /* hpux */
        if (ioctl (f, AUDIO_SET_SAMPLE_RATE, __rate)) {
            /* console_fprintf(stderr, "got err-ret from AUDIO_SET_SAMPLE_RATE\n"); */
            __INST(sampleRate) = hz;
            RETURN (self);
        }
#   endif
#  endif
# endif
    }
#endif // SUPPORT_DEV_AUDIO
%}.

    "
     self writing setSampleRate:10000; dumpSettings; close
     self writing setSampleRate:1000; dumpSettings; close
     self writing setSampleRate:8000; dumpSettings; close
    "
! !

!SoundStream::DevAudio methodsFor:'queries'!

supportedAudioFormats
    "return a collection of supported audio formats.
     possibly returned symbols are:
        U8        unsigned 8bit samples
        S8        signed 8bit samples
        U16       unsigned 16bit samples in native format
        U16_LE    unsigned 16bit big endian samples
        U16_BE    unsigned 16bit big endian samples
        S16       signed 16bit little endian samples in native format
        S16_LE    signed 16bit little endian samples
        S16_BE    signed 16bit big endian samples
        S24       signed 24bit little endian samples in native format
        S24_LE    signed 24bit little endian samples
        S24_BE    signed 24bit big endian samples
        S32       signed 32bit little endian samples in native format
        S32_LE    signed 32bit little endian samples
        S32_BE    signed 32bit big endian samples
        F32       float samples
        MPEG      audio mpeg encoded
        MU_LAW    u-law encoded 8bit samples
        A_LAW     a-law encoded 8bit samples
        IMA_ADPCM adpcm encoded
     the set of returned symbols depends on the underlying sound hardware.
    "

    |fd audioFormatMask
     supportedFormats
     supports_MU_LAW supports_A_LAW supports_MPEG
     supports_IMA_ADPCM
     supports_S8 supports_U8
     supports_S16_LE supports_S16_BE
     supports_U16_LE supports_U16_BE
     supports_U32_LE supports_U32_BE
     supports_S24_LE supports_S24_BE
     supports_S32_LE supports_S32_BE
     supports_F32
    |

    fd := self fileDescriptorOrNil.

%{
#ifdef SUPPORT_DEV_AUDIO
    supports_MU_LAW = true;

    if (fd != nil) {
        int f = __intVal(fd);
        int __audioFormatMask = 0;

# if defined(SNDCTL_DSP_GETFMTS)
        if (ioctl(f, SNDCTL_DSP_GETFMTS, &__audioFormatMask) >= 0) {
            audioFormatMask = __MKSMALLINT(__audioFormatMask);

#  ifdef AFMT_MU_LAW
            supports_MU_LAW = (__audioFormatMask & AFMT_MU_LAW) ? true : false;
#  endif
#  ifdef AFMT_A_LAW
            supports_A_LAW = (__audioFormatMask & AFMT_A_LAW) ? true : false;
#  endif
#  ifdef AFMT_IMA_ADPCM
            supports_IMA_ADPCM = (__audioFormatMask & AFMT_IMA_ADPCM) ? true : false;
#  endif
#  ifdef AFMT_U8
            supports_U8 = (__audioFormatMask & AFMT_U8) ? true : false;
#  endif
#  ifdef AFMT_S16_LE
            supports_S16_LE = (__audioFormatMask & AFMT_S16_LE) ? true : false;
#  endif
#  ifdef AFMT_S16_BE
            supports_S16_BE = (__audioFormatMask & AFMT_S16_BE) ? true : false;
#  endif
#  ifdef AFMT_S8
            supports_S8 = (__audioFormatMask & AFMT_S8) ? true : false;
#  endif
#  ifdef AFMT_U16_LE
            supports_U16_LE = (__audioFormatMask & AFMT_U16_LE) ? true : false;
#  endif
#  ifdef AFMT_U16_BE
            supports_U16_BE = (__audioFormatMask & AFMT_U16_BE) ? true : false;
#  endif
#  ifdef AFMT_MPEG
            supports_MPEG = (__audioFormatMask & AFMT_MPEG) ? true : false;
#  endif
        }
    }
# endif // SNDCTL_DSP_GETFMTS

# ifdef hpux
    supports_A_LAW = true;
    supports_S16_BE = true;
# endif
#endif /* SUPPORT_DEV_AUDIO */
%}.
    supportedFormats := IdentitySet new.
    (supports_MU_LAW ? false) ifTrue:[
        supportedFormats add:#'MU_LAW'
    ].
    (supports_A_LAW ? false)  ifTrue:[
        supportedFormats add:#'A_LAW'
    ].
    (supports_IMA_ADPCM ? false)  ifTrue:[
        supportedFormats add:#'IMA_ADPCM'
    ].
    (supports_MPEG ? false)  ifTrue:[
        supportedFormats add:#'MPEG'
    ].
    (supports_S8 ? false)  ifTrue:[
        supportedFormats add:#'S8'
    ].
    (supports_U8 ? false)  ifTrue:[
        supportedFormats add:#'U8'
    ].
    (supports_S16_LE ? false)  ifTrue:[
        supportedFormats add:#'S16_LE'.
        UninterpretedBytes isBigEndian ifFalse:[
            supportedFormats add:#'S16'.
        ]
    ].
    (supports_S16_BE ? false)  ifTrue:[
        supportedFormats add:#'S16_BE'.
        UninterpretedBytes isBigEndian ifTrue:[
            supportedFormats add:#'S16'.
        ]
    ].
    (supports_S24_LE ? false)  ifTrue:[
        supportedFormats add:#'S24_LE'.
        UninterpretedBytes isBigEndian ifFalse:[
            supportedFormats add:#'S24'.
        ]
    ].
    (supports_S24_BE ? false)  ifTrue:[
        supportedFormats add:#'S24_BE'.
        UninterpretedBytes isBigEndian ifTrue:[
            supportedFormats add:#'S24'.
        ]
    ].
    (supports_S32_LE ? false)  ifTrue:[
        supportedFormats add:#'S32_LE'.
        UninterpretedBytes isBigEndian ifFalse:[
            supportedFormats add:#'S32'.
        ]
    ].
    (supports_S32_BE ? false)  ifTrue:[
        supportedFormats add:#'S32_BE'.
        UninterpretedBytes isBigEndian ifTrue:[
            supportedFormats add:#'S32'.
        ]
    ].
    (supports_U16_LE ? false)  ifTrue:[
        supportedFormats add:#'U16_LE'.
        UninterpretedBytes isBigEndian ifFalse:[
            supportedFormats add:#'U16'.
        ]
    ].
    (supports_U16_BE ? false)  ifTrue:[
        supportedFormats add:#'U16_BE'.
        UninterpretedBytes isBigEndian ifTrue:[
            supportedFormats add:#'U16'.
        ]
    ].
    (supports_F32 ? false)  ifTrue:[
        supportedFormats add:#'F32'
    ].
    ^ supportedFormats.

    "
     |s formats|

     s := self writing.
     formats := s supportedAudioFormats.
     s close.
     formats
    "
! !

!SoundStream::DevAudio methodsFor:'reading'!

nextBytes:count into:anObject startingAt:start
    "read the next count bytes into an object and return the number of
     bytes read or nil on error.
     Use with ByteArrays only."

%{
#ifdef SUPPORT_DEV_AUDIO
   /*
    * redefined to work around a bug in the linux sound driver;
    * if a read is interrupted (EINTR), it is not defined, how many
    * bytes have been read from the device.
    *
    * As a workaround, disable signals here to prevent being interrupted.
    */
    int cnt, offs, objSize, n;
    char *cp;
    OBJ fp;
    FILE *f;
    int fd;

    if ((fp = __INST(handle)) != nil) {
        f = __FILEVal(fp);
        if (__INST(mode) != @symbol(writeonly)) {
            if (__bothSmallInteger(count, start)) {
                cnt = __intVal(count);
                offs = __intVal(start) - 1;

                objSize = _Size(anObject) - OHDR_SIZE;
                if ( (offs >= 0) && (cnt >= 0) && (objSize >= (cnt + offs)) ) {
                    do {
                        cp = (char *)__InstPtr(anObject) + OHDR_SIZE + offs;

                        n = cnt;
# ifdef LINUX
                        sigsetmask(~0);
# endif
                        if (__INST(buffered) == true) {
                            n = fread(cp, 1, n, f);
                        } else {
                            fd = fileno(f);
                            n = read(fd, cp, n);
                        }
# ifdef LINUX
                        sigsetmask(0);
# endif
                        __BEGIN_INTERRUPTABLE__
                        __END_INTERRUPTABLE__
                        // console_fprintf(stderr, "SoundStream: read %d bytes\n", n);
                        if (n > 0) {
                            offs += n;
                            cnt -= n;
                        } else {
                            if (n < 0) {
                                console_fprintf(stderr, "read error: %d\n", __threadErrno);
                                RETURN (count);
                            }
                        }
                    } while (cnt);
                }
                RETURN (count);
            }
        }
    }
#endif /* SUPPORT_DEV_AUDIO */

%}.
    self errorUnsupportedOperation
! !

!SoundStream::DevAudio methodsFor:'writing'!

nextPutBytes:count from:anObject startingAt:start
    "write count bytes from an object starting at index start.
     return the number of bytes written or nil on error.
     Redefined, since IRIS audio library cannot be used with stdio.
     (at least I don't know). Use with ByteArrays only."

%{
#ifdef SUPPORT_DEV_AUDIO
   /*
    * redefine to work around a bug in the linux sound driver;
    * if a write is interrupted (EINTR), it is not defined, how many
    * bytes have been written to the device.
    * I.e. a retry of the write may lead to ever-playing without ever
    * finishing.
    *
    * As a workaround, disable signals here to prevent the write from
    * being interrupted.
    */
    int cnt, offs, objSize, n;
    char *cp;
    OBJ fp;
    FILE *f;
    int fd;

    if ((fp = __INST(handle)) != nil) {
        f = __FILEVal(fp);
        if (__INST(mode) != @symbol(readonly)) {
            if (__bothSmallInteger(count, start)) {
                cnt = __intVal(count);
                offs = __intVal(start) - 1;

                objSize = _Size(anObject) - OHDR_SIZE;
                if ( (offs >= 0) && (cnt >= 0) && (objSize >= (cnt + offs)) ) {
                    do {
                        cp = (char *)__InstPtr(anObject) + OHDR_SIZE + offs;

                        n = cnt;
# ifdef LINUX
                        sigsetmask(~0);
# endif
                        if (__INST(buffered) == true) {
                            n = fwrite(cp, 1, n, f);
                        } else {
                            fd = fileno(f);
                            n = write(fd, cp, n);
                        }
# ifdef LINUX
                        sigsetmask(0);
# endif
                        __BEGIN_INTERRUPTABLE__
                        __END_INTERRUPTABLE__
                        if (n > 0) {
                            offs += n;
                            cnt -= n;
                        } else {
                            if (n < 0) {
                                console_fprintf(stderr, "write error: %d\n", __threadErrno);
                                RETURN (count);
                            }
                        }
                    } while (cnt);
                }
                RETURN (count);
            }
        }
    }
#endif /* SUPPORT_DEV_AUDIO */

%}.
    ^ self errorUnsupportedOperation
! !

!SoundStream::IRISAudio class methodsFor:'documentation'!

documentation
"
    interface to the silicon graphics IRIX audio system
"
! !

!SoundStream::IRISAudio class methodsFor:'queries'!

isSupported
%{
#ifdef SUPPORT_IRIS_AUDIO
    RETURN(true);
#endif
%}.
    ^ false.
! !

!SoundStream::IRISAudio methodsFor:'misc'!

flush
    "wait until all sound has been played"

%{
#ifdef SUPPORT_IRIS_AUDIO
    OPJ port;
    ALport p;

    if ((port = __INST(alPort)) != nil) {
        p = __ALportVal(port);
        while (ALgetfilled(p) > 0) {
            sginap(1);
        }
    }
    RETURN(self);
#endif /* SUPPORT_IRIS_AUDIO */
%}.

! !

!SoundStream::IRISAudio methodsFor:'open & close'!

closeFile
    "a stream has been collected - close the file"

%{
#ifdef SUPPORT_IRIS_AUDIO
    OBJ port;

    if ((port = __INST(alPort)) != nil) {
        __INST(alPort) = nil;
        ALcloseport(__ALportVal(port));
    }
    RETURN (self);
#endif /* SUPPORT_IRIS_AUDIO */
%}.

!

openWithMode:aMode attributes:attributeSpec
    |ok error errorStringOrNil|

%{
#ifdef SUPPORT_IRIS_AUDIO
    ALconfig config;
    ALport p;
    long params[] = {
        AL_INPUT_SOURCE, AL_INPUT_MIC,
        AL_INPUT_RATE, 8000,
        AL_OUTPUT_RATE, 8000,
    };

    ok = false.
    config = ALnewconfig();
    if (__INST(numberOfChannels) == __MKSMALLINT(2))
        ALsetchannels(config, AL_STEREO);
    else
        ALsetchannels(config, AL_MONO);
    if (__INST(bitsPerSample) == __MKSMALLINT(16))
        ALsetwidth(config, AL_SAMPLE_16);
    else
        ALsetwidth(config, AL_SAMPLE_8);

    if (__isSmallInteger(__INST(sampleRate)))
        params[3] = params[5] = __intVal(__INST(sampleRate));

    ALsetparams(AL_DEFAULT_DEVICE, params, 6);
    p = ALopenport("smallchat", (char *)_stringVal(aMode), config);
    if (p) {
        OBJ t;

        t = __MKEXTERNALADDRESS(p); __INST(alPort) = t; __STORE(self, t);
    } else {
        __INST(alPort) = nil;
        goto out;
    }
    __INST(binary) = true;

    ALfreeconfig(config);
    /*
     * get the parameters actually installed
     */
    config = ALgetconfig(p);
    switch (ALgetchannels(config)) {
        default:
            /* cannot happen */
        case AL_MONO:
            __INST(numberOfChannels) = __MKSMALLINT(1);
            break;
        case AL_STEREO:
            __INST(numberOfChannels) = __MKSMALLINT(2);
            break;
    }
    switch (ALgetwidth(config)) {
        default:
            /* cannot happen */
        case AL_SAMPLE_8:
            __INST(bitsPerSample) = __MKSMALLINT(8);
            break;
        case AL_SAMPLE_16:
            __INST(bitsPerSample) = __MKSMALLINT(16);
            break;
        case AL_SAMPLE_24:
            __INST(bitsPerSample) = __MKSMALLINT(24);
            break;
    }
    ALgetparams(AL_DEFAULT_DEVICE, params, 6);
    __INST(sampleRate) = __MKSMALLINT(params[3]);

    ALfreeconfig(config);
    ok = true;
out:;
#endif /* SUPPORT_IRIS_AUDIO */

%}.
    ok == false ifTrue:[
        lastErrorString := errorStringOrNil.
        lastErrorNumber := error ? -1.
        self openError:error.
        "normally not reached"
        ^ nil.
    ].
    self registerForFinalization.
! !

!SoundStream::IRISAudio methodsFor:'queries'!

supportedAudioFormats
    "return a collection of supported audio formats.
     possibly returned symbols are:
        U8        unsigned 8bit samples
        S8        signed 8bit samples
        U16       unsigned 16bit samples in native format
        U16_LE    unsigned 16bit big endian samples
        U16_BE    unsigned 16bit big endian samples
        S16       signed 16bit little endian samples in native format
        S16_LE    signed 16bit little endian samples
        S16_BE    signed 16bit big endian samples
        S24       signed 24bit little endian samples in native format
        S24_LE    signed 24bit little endian samples
        S24_BE    signed 24bit big endian samples
        S32       signed 32bit little endian samples in native format
        S32_LE    signed 32bit little endian samples
        S32_BE    signed 32bit big endian samples
        F32       float samples
        MPEG      audio mpeg encoded
        MU_LAW    u-law encoded 8bit samples
        A_LAW     a-law encoded 8bit samples
        IMA_ADPCM adpcm encoded
     the set of returned symbols depends on the underlying sound hardware.
    "

    ^ #( U8 U16_BE U16 )

    "
     |s formats|

     s := self writing.
     formats := s supportedAudioFormats.
     s close.
     formats
    "
! !

!SoundStream::IRISAudio methodsFor:'reading'!

nextBytes:count into:anObject startingAt:start
    "read the next count bytes into an object and return the number of
     bytes read or nil on error.
     Use with ByteArrays only."

%{
#ifdef SUPPORT_IRIS_AUDIO
  {
    OBJ port;
    ALport p;
    int cnt, offs, nSamp;
    int objSize;
    char *cp;

    if ((port = __INST(alPort)) != nil) {
        if (__INST(mode) != _writeonly) {
            if (__bothSmallInteger(count, start)) {
                cnt = __intVal(count);
                offs = __intVal(start) - 1;
                p = __ALportVal(port);
                objSize = _Size(anObject) - OHDR_SIZE;
                if ((offs >= 0) && (cnt >= 0) && (objSize >= (cnt + offs))) {
                    cp = (char *)__InstPtr(anObject) + OHDR_SIZE + offs;
                    if (__INST(bitsPerSample) == __MKSMALLINT(16))
                        nSamp = cnt / 2;
                    else
                        nSamp = cnt;
                    ALreadsamps(p, cp, nSamp);
                    RETURN ( __MKSMALLINT(cnt) );
                }
            }
        }
    }
  }
#endif /* SUPPORT_IRIS_AUDIO */

%}.
    self errorUnsupportedOperation
! !

!SoundStream::IRISAudio methodsFor:'writing'!

nextPutBytes:count from:anObject startingAt:start
    "write count bytes from an object starting at index start.
     return the number of bytes written or nil on error.
     Redefined, since IRIS audio library cannot be used with stdio.
     (at least I don't know). Use with ByteArrays only."

%{
#ifdef SUPPORT_IRIS_AUDIO
  {
    OBJ port;
    ALport p;
    int cnt, offs, nSamp;
    int objSize;
    char *cp;

    if ((port = __INST(alPort)) != nil) {
        if (__INST(mode) != @symbol(readonly)) {
            if (__bothSmallInteger(count, start)) {
                cnt = __intVal(count);
                offs = __intVal(start) - 1;
                p = __ALportVal(port);

                /*
                 * compute number of samples
                 */
                objSize = _Size(anObject) - OHDR_SIZE;
                if ( (offs >= 0) && (cnt >= 0) && (objSize >= (cnt + offs)) ) {
                    cp = (char *)__InstPtr(anObject) + OHDR_SIZE + offs;
                    if (__INST(bitsPerSample) == __MKSMALLINT(16))
                        nSamp = cnt / 2;
                    else
                        nSamp = cnt;
                    ALwritesamps(p, cp, cnt);
                    RETURN ( count );
                }
            }
        }
    }
  }
#endif /* SUPPORT_IRIS_AUDIO */
%}.
    self errorUnsupportedOperation
! !

!SoundStream::JackAudio class methodsFor:'documentation'!

documentation
"
    interface to the jack audio system
"
! !

!SoundStream::JackAudio class methodsFor:'queries'!

defaultAudioFormat
    ^ #F32
!

isSupported
%{
#ifdef SUPPORT_JACKAUDIO
    RETURN(true);
#endif
%}.
    ^ false.
! !

!SoundStream::JackAudio methodsFor:'open & close'!

closeFile
    "a stream has been collected - close the file"

%{
#ifdef SUPPORT_JACKAUDIO
    OBJ str;
    if ((str = __INST(handle1)) != nil) {
        struct jackStreamData* streamData = (struct jackStreamData*)__externalAddressVal(str);
        struct jackBuffer* buffer;

        if (DEBUGGING) {
            fprintf(stderr, "jack close\n");
        }
        __externalAddressVal(str) = NULL;
        __INST(handle1) = nil;
        jack_client_close( streamData->jack_client );

        LOCK(streamData->lock);

        buffer = streamData->currentBuffer;
        streamData->currentBuffer = NULL;
        streamData->lastBuffer = NULL;
        while (buffer != NULL) {
            struct jackBuffer* nextBuffer = buffer->nextBuffer;
            free(buffer->sampleData);
            free(buffer);
            buffer = nextBuffer;
        }
        buffer = streamData->freeList;
        streamData->freeList = NULL;
        while (buffer != NULL) {
            struct jackBuffer* nextBuffer = buffer->nextBuffer;
            free(buffer->sampleData);
            free(buffer);
            buffer = nextBuffer;
        }

        UNLOCK(streamData->lock);
        RELEASELOCK(streamData->lock);
        free(streamData);
    }
    RETURN (self);
#endif // SUPPORT_JACKAUDIO
%}.
!

openWithMode:aMode attributes:attributeSpec
    |ok error errorStringOrNil|

    openMode := aMode.
    openAttributes := attributeSpec.
%{
#ifdef SUPPORT_JACKAUDIO
    jack_options_t options = JackNullOption;
    jack_client_t *client;
    jack_port_t *output_port;
    struct jackStreamData* streamData;
    int nChannels, sampleRate, bytesPerSample;
#   define FRAMES_PER_BUFFER 128

    ok = false;

    if (__isSmallInteger(__INST(numberOfChannels))) {
        nChannels = __intVal(__INST(numberOfChannels));
    } else {
        nChannels = 1;
    }

    if (__INST(audioFormat) == @symbol(F32)) {
        bytesPerSample = 4;
    } else {
        fprintf(stderr, "SoundStream [warning]: only f32 supported with jack\n");
        errorStringOrNil = __MKSTRING("audioFormat must be f32 with jack");
        goto out;
    }

    streamData = (struct jackStreamData*)malloc(sizeof(struct jackStreamData));
    if (streamData == NULL) {
        fprintf(stderr, "SoundStream [warning]: failed to allocate jackStream\n");
        errorStringOrNil = __MKSTRING("failed to allocate jackStream");
        goto out;
    }

    if ((client = jack_client_open ("stx", JackNullOption, NULL)) == 0) {
        fprintf(stderr, "SoundStream [warning]: JACK server not running?\n");
        free(streamData);
        errorStringOrNil = __MKSTRING("JACK server not running");
        goto out;
    }
    jack_set_process_callback (client, jack_callback, 0);

    output_port = jack_port_register (client, "stx_out", JACK_DEFAULT_AUDIO_TYPE, JackPortIsOutput, 0);
    sampleRate = jack_get_sample_rate (client);
    __INST(sampleRate) = __MKSMALLINT(sampleRate);
    // if (__isSmallInteger(__INST(sampleRate))) {
    //     sampleRate = __intVal(__INST(sampleRate));
    // } else {
    //     fprintf(stderr, "SoundStream [warning]: using default sampleRate 8000\n");
    //     sampleRate = 8000;
    // }

    streamData->jack_client = client;
    streamData->jack_output_port = output_port;
    INITLOCK(streamData->lock);
    streamData->readOffset = 0;
    streamData->bytesPerSample = bytesPerSample;
    streamData->nChannels = nChannels;

    streamData->currentBuffer = NULL;
    streamData->lastBuffer = NULL;
    streamData->freeList = NULL;
    streamData->hasFinished = 0;

    {
        OBJ t;
        t = __MKEXTERNALADDRESS(streamData); __INST(handle1) = t; __STORE(self, t);
    }
    __INST(binary) = true;

//    paErr = Pa_SetStreamFinishedCallback( stream, &paStreamFinished );
//    if( paErr != paNoError ) {
//        fprintf(stderr, "SoundStream [warning]: setFinishedCallback: %s\n", Pa_GetErrorText( paErr ));
//        free(paStreamData);
//        errorStringOrNil = __MKSTRING(Pa_GetErrorText( paErr ));
//        goto out;
//    };

    ok = true;
out:;
#endif /* SUPPORT_JACKAUDIO */

%}.
    ok == false ifTrue:[
        lastErrorString := errorStringOrNil.
        lastErrorNumber := error ? -1.
        self openError:error.
        "normally not reached"
        ^ nil.
    ].
    self registerForFinalization.
!

reopenStream
    handle1 isNil ifTrue:[^ self].
    self closeFile.
    self openWithMode:openMode attributes:openAttributes
! !

!SoundStream::JackAudio methodsFor:'queries'!

supportedAudioFormats
    "return a collection of supported audio formats.
     possibly returned symbols are:
        U8        unsigned 8bit samples
        S8        signed 8bit samples
        U16       unsigned 16bit samples in native format
        U16_LE    unsigned 16bit big endian samples
        U16_BE    unsigned 16bit big endian samples
        S16       signed 16bit little endian samples in native format
        S16_LE    signed 16bit little endian samples
        S16_BE    signed 16bit big endian samples
        S24       signed 24bit little endian samples in native format
        S24_LE    signed 24bit little endian samples
        S24_BE    signed 24bit big endian samples
        S32       signed 32bit little endian samples in native format
        S32_LE    signed 32bit little endian samples
        S32_BE    signed 32bit big endian samples
        F32       float samples
        MPEG      audio mpeg encoded
        MU_LAW    u-law encoded 8bit samples
        A_LAW     a-law encoded 8bit samples
        IMA_ADPCM adpcm encoded
     the set of returned symbols depends on the underlying sound hardware.
    "

    ^ #(F32)

    "
     |s formats|

     s := self writing.
     formats := s supportedAudioFormats.
     s close.
     formats
    "
! !

!SoundStream::PortAudio class methodsFor:'default values'!

defaultSampleRate
    "minimum, supported by all audio systems"

%{
#ifdef SUPPORT_PORTAUDIO
    RETURN (__MKSMALLINT(PORTAUDIO_DEFAULT_FREQ));
#endif
%}.

    ^ 8000
! !

!SoundStream::PortAudio class methodsFor:'documentation'!

documentation
"
    interface to the portaudio library
"
! !

!SoundStream::PortAudio class methodsFor:'initialization'!

primitiveInitializeDevice
    |errorMessageOrNil|

%{
#ifdef SUPPORT_PORTAUDIO
    PaError paErr = 0;

    if (DEBUGGING) {
        fprintf(stderr, "calling Pa_Initialize...\n");
    }
    if ((paErr = Pa_Initialize()) != paNoError ) {
        errorMessageOrNil = __MKSTRING(Pa_GetErrorText( paErr ) );
        fprintf(stderr, "SoundStream [error]: Pa_Initialize failed\n");
    };
#endif
%}.
    errorMessageOrNil notNil ifTrue:[
        self error:'failed to initialize audio device: ',errorMessageOrNil
    ].

! !

!SoundStream::PortAudio class methodsFor:'queries'!

defaultAudioFormat
    ^ #S16
!

isSupported
%{
#ifdef SUPPORT_PORTAUDIO
    RETURN(true);
#endif
%}.
    ^ false.
! !

!SoundStream::PortAudio methodsFor:'misc'!

flush
    "wait until all sound has been played"

    [self hasOutputPending] whileTrue:[
        Delay waitForMilliseconds:20.
        "/ Processor yield
    ]
!

hasOutputPending
%{
#ifdef SUPPORT_PORTAUDIO
    OBJ str;
    if ((str = __INST(handle1)) != nil) {
        struct paStreamData* streamData = (struct paStreamData*)__externalAddressVal(str);

        RETURN ((streamData->currentBuffer != NULL) ? true : false);
    }
#endif /* SUPPORT_PORTAUDIO */
%}.
    ^ false
!

outputBytesPending
%{
#ifdef SUPPORT_PORTAUDIO
    OBJ str;
    int n = 0;

    if ((str = __INST(handle1)) != nil) {
        struct paStreamData* streamData = (struct paStreamData*)__externalAddressVal(str);
        int offs;
        struct paBuffer *buffer;

        if (streamData != NULL) {
            offs = streamData->readOffset;

            buffer = streamData->currentBuffer;
            if (buffer != NULL) {
                n = buffer->bufferSize - offs;
                while ((buffer = buffer->nextBuffer) != NULL) {
                    n += buffer->bufferSize;
                }
            }
        }
    }
    RETURN (__MKSMALLINT(n));
#endif /* SUPPORT_PORTAUDIO */
%}.
    ^ 0
! !

!SoundStream::PortAudio methodsFor:'open & close'!

closeFile
    "a stream has been collected - close the file"

%{
#ifdef SUPPORT_PORTAUDIO
    OBJ str;
    if ((str = __INST(handle1)) != nil) {
        struct paStreamData* streamData = (struct paStreamData*)__externalAddressVal(str);
        struct paBuffer* buffer;

        if (DEBUGGING) {
            fprintf(stderr, "pa close\n");
        }
        __externalAddressVal(str) = NULL;
        __INST(handle1) = nil;
        // Pa_StopStream( streamData->stream );
        Pa_CloseStream( streamData->stream );

        LOCK(streamData->lock);

        buffer = streamData->currentBuffer;
        streamData->currentBuffer = NULL;
        streamData->lastBuffer = NULL;
        while (buffer != NULL) {
            struct paBuffer* nextBuffer = buffer->nextBuffer;
            free(buffer->sampleData);
            free(buffer);
            buffer = nextBuffer;
        }
        buffer = streamData->freeList;
        streamData->freeList = NULL;
        while (buffer != NULL) {
            struct paBuffer* nextBuffer = buffer->nextBuffer;
            free(buffer->sampleData);
            free(buffer);
            buffer = nextBuffer;
        }

        UNLOCK(streamData->lock);
        RELEASELOCK(streamData->lock);
        free(streamData);
    }
    RETURN (self);
#endif // SUPPORT_PORTAUDIO
%}.
!

openWithMode:aMode attributes:attributeSpec
    |ok error errorStringOrNil|

    openMode := aMode.
    openAttributes := attributeSpec.
%{
#ifdef SUPPORT_PORTAUDIO
    static PaStreamParameters outputParameters;
    PaStream *stream;
    PaError paErr;
    struct paStreamData* streamData;
    int nChannels, sampleRate, bytesPerSample;
#   define FRAMES_PER_BUFFER 128

    ok = false;

    /* default output device */
    outputParameters.device = Pa_GetDefaultOutputDevice();
    if (outputParameters.device == paNoDevice) {
        fprintf(stderr, "SoundStream [warning]: No default output device.\n");
        errorStringOrNil = __MKSTRING("No default output device");
        goto out;
    }

    if (__isSmallInteger(__INST(numberOfChannels))) {
        nChannels = __intVal(__INST(numberOfChannels));
    } else {
        nChannels = 1;
    }
    outputParameters.channelCount = nChannels;
    outputParameters.suggestedLatency = Pa_GetDeviceInfo( outputParameters.device )->defaultLowOutputLatency;
    outputParameters.hostApiSpecificStreamInfo = NULL;

    // The standard formats paFloat32, paInt16, paInt32, paInt24, paInt8
    // and aUInt8 are usually implemented by all implementations.
    // The floating point representation (paFloat32) uses +1.0 and -1.0 as the
    // maximum and minimum respectively.
    // paUInt8 is an unsigned 8 bit format where 128 is considered "ground"

    if (__INST(audioFormat) == @symbol(S16)) {
        outputParameters.sampleFormat = paInt16;
        bytesPerSample = 2;
    } else if (__INST(audioFormat) == @symbol(S32)) {
        outputParameters.sampleFormat = paInt32;
        bytesPerSample = 4;
    } else if (__INST(audioFormat) == @symbol(S24)) {
        outputParameters.sampleFormat = paInt24;
        bytesPerSample = 3;
    } else if (__INST(audioFormat) == @symbol(S8)) {
        outputParameters.sampleFormat = paInt8;
        bytesPerSample = 1;
    } else if (__INST(audioFormat) == @symbol(F32)) {
        outputParameters.sampleFormat = paFloat32;
        bytesPerSample = 4;
    } else if (__INST(audioFormat) == @symbol(U8)) {
        outputParameters.sampleFormat = paUInt8;
        bytesPerSample = 1;
    } else {
        fprintf(stderr, "SoundStream [warning]: unknown format - using U8\n");
        outputParameters.sampleFormat = paUInt8;
        bytesPerSample = 1;
    }

    if (__isSmallInteger(__INST(sampleRate))) {
        sampleRate = __intVal(__INST(sampleRate));
    } else {
        fprintf(stderr, "SoundStream [warning]: using default sampleRate 8000\n");
        sampleRate = 8000;
    }

    streamData = (struct paStreamData*)malloc(sizeof(struct paStreamData));
    if (streamData == NULL) {
        fprintf(stderr, "SoundStream [warning]: failed to allocate paStream\n");
        errorStringOrNil = __MKSTRING("failed to allocate paStream");
        goto out;
    }

    paErr = Pa_OpenStream(
              &stream,
              NULL, /* no input */
              &outputParameters,
              sampleRate,
              FRAMES_PER_BUFFER,
              paClipOff,      /* we won't output out of range samples so don't bother clipping them */
              paCallback,
              streamData );

    if (paErr != paNoError) {
        fprintf(stderr, "SoundStream [warning]: openStream: %s\n", Pa_GetErrorText( paErr ));
        free(streamData);
        errorStringOrNil = __MKSTRING(Pa_GetErrorText( paErr ));
        goto out;
    }
    streamData->stream = stream;
    INITLOCK(streamData->lock);
    streamData->readOffset = 0;
    streamData->bytesPerSample = bytesPerSample;
    streamData->nChannels = nChannels;

    streamData->currentBuffer = NULL;
    streamData->lastBuffer = NULL;
    streamData->freeList = NULL;
    streamData->hasFinished = 0;

    {
        OBJ t;
        t = __MKEXTERNALADDRESS(streamData); __INST(handle1) = t; __STORE(self, t);
    }
    __INST(binary) = true;

    paErr = Pa_SetStreamFinishedCallback( stream, &paStreamFinished );
    if( paErr != paNoError ) {
        fprintf(stderr, "SoundStream [warning]: setFinishedCallback: %s\n", Pa_GetErrorText( paErr ));
        free(streamData);
        errorStringOrNil = __MKSTRING(Pa_GetErrorText( paErr ));
        goto out;
    };

    ok = true;
out:;
#endif /* SUPPORT_PORTAUDIO */

%}.
    ok == false ifTrue:[
        lastErrorString := errorStringOrNil.
        lastErrorNumber := error ? -1.
        self openError:error.
        "normally not reached"
        ^ nil.
    ].
    self registerForFinalization.

!

reopenStream
    handle1 isNil ifTrue:[^ self].
    self closeFile.
    self openWithMode:openMode attributes:openAttributes
! !

!SoundStream::PortAudio methodsFor:'private'!

initialize
    "initialize for least common mode"

    super initialize.

    (IsInitialized ? false) ifFalse:[
        self class primitiveInitializeDevice
    ].

    "Created: 17.11.1995 / 17:28:14 / cg"
!

setAudioFormat:aSymbol
    super setAudioFormat:aSymbol.
    self reopenStream
!

setChannels:numChannels
    super setChannels:numChannels.
    self reopenStream
!

setFragmentSize:blockSize
    super setFragmentSize:blockSize.
    self reopenStream
!

setSampleRate:hz
    super setSampleRate:hz.
    self reopenStream
! !

!SoundStream::PortAudio methodsFor:'queries'!

supportedAudioFormats
    "return a collection of supported audio formats.
     possibly returned symbols are:
        U8        unsigned 8bit samples
        S8        signed 8bit samples
        U16       unsigned 16bit samples in native format
        U16_LE    unsigned 16bit big endian samples
        U16_BE    unsigned 16bit big endian samples
        S16       signed 16bit little endian samples in native format
        S16_LE    signed 16bit little endian samples
        S16_BE    signed 16bit big endian samples
        S24       signed 24bit little endian samples in native format
        S24_LE    signed 24bit little endian samples
        S24_BE    signed 24bit big endian samples
        S32       signed 32bit little endian samples in native format
        S32_LE    signed 32bit little endian samples
        S32_BE    signed 32bit big endian samples
        F32       float samples
        MPEG      audio mpeg encoded
        MU_LAW    u-law encoded 8bit samples
        A_LAW     a-law encoded 8bit samples
        IMA_ADPCM adpcm encoded
     the set of returned symbols depends on the underlying sound hardware.
    "

    ^ #(U8 S8 S16_LE S16 S24_LE S24 S32_LE S32 F32)

    "
     |s formats|

     s := self writing.
     formats := s supportedAudioFormats.
     s close.
     formats
    "
! !

!SoundStream::PortAudio methodsFor:'reading'!

nextBytes:count into:anObject startingAt:start
    "read the next count bytes into an object and return the number of
     bytes read or nil on error.
     Use with ByteArrays only."

    self errorUnsupportedOperation
! !

!SoundStream::PortAudio methodsFor:'writing'!

nextPutBytes:count from:anObject startingAt:start
    "write count bytes from an object starting at index start.
     return the number of bytes written or nil on error.
     Redefined, since IRIS audio library cannot be used with stdio.
     (at least I don't know). Use with ByteArrays only."

%{
#ifdef SUPPORT_PORTAUDIO
    OBJ str;

    if ((str = __INST(handle1)) != nil) {
        if (__INST(mode) != @symbol(readonly)) {
            if (__bothSmallInteger(count, start)) {
                // allocate a buffer
                struct paStreamData* streamData = (struct paStreamData*)__externalAddressVal(str);
                int cnt = __intVal(count);
                int offs = __intVal(start) - 1;
                int objSize;

                objSize = _Size(anObject) - OHDR_SIZE;
                if ( (offs >= 0) && (cnt >= 0) && (objSize >= (cnt + offs)) ) {
                    struct paBuffer* newBuffer;
                    struct paBuffer* toFree;
                    int mustStart = 0;
                    unsigned char* newSampleData;

                    // try freeList
                    LOCK(streamData->lock);
                    if ((streamData->freeList != NULL)
                     && (streamData->freeList->bufferSize == cnt)) {
                        // reuse
                        newBuffer = streamData->freeList;
                        streamData->freeList = newBuffer->nextBuffer;
                        newSampleData = newBuffer->sampleData;
                        toFree = NULL;
                        if (DEBUGGING) {
                            fprintf(stderr, "from free: %p (->%p)\n", newBuffer, newBuffer->sampleData);
                        }
                    } else {
                        // free them all
                        toFree = streamData->freeList;
                        streamData->freeList = NULL;
                        newBuffer = malloc(sizeof(struct paBuffer));
                        newSampleData = malloc(cnt);
                        newBuffer->sampleData = newSampleData;
                        newBuffer->bufferSize = cnt;
                        if (DEBUGGING) {
                            fprintf(stderr, "alloc: %p (->%p)\n", newBuffer, newBuffer->sampleData);
                        }
                    }

                    memcpy(newSampleData, (__ByteArrayInstPtr(anObject)->ba_element)+offs, cnt);
                    newBuffer->nextBuffer = NULL;

                    if (streamData->lastBuffer == NULL) {
                        // start stream's buffer list
                        streamData->currentBuffer = newBuffer;
                        mustStart = 1;
                    } else {
                        // append to stream's buffer list
                        streamData->lastBuffer->nextBuffer = newBuffer;
                    }
                    streamData->lastBuffer = newBuffer;
                    streamData->hasFinished = 0;
                    UNLOCK(streamData->lock);

                    if (mustStart) {
                        PaError paErr = Pa_StartStream( streamData->stream );
                        if ( paErr != paNoError ) {
                            if (DEBUGGING) {
                                fprintf(stderr, "start error\n");
                            }
                            RETURN (0);
                        };
                    }
                    RETURN (count);
                }
            }
        }
    }
#endif /* SUPPORT_PORTAUDIO */

%}.
    self errorUnsupportedOperation
! !

!SoundStream::Win32DirectSound class methodsFor:'documentation'!

documentation
"
    interface to the windows direct sound API
"
! !

!SoundStream::Win32DirectSound class methodsFor:'queries'!

isSupported
%{
#ifdef SUPPORT_WIN32_DIRECTSOUND
    RETURN(true);
#endif
%}.
    ^ false.
! !

!SoundStream::Win32DirectSound methodsFor:'misc'!

flush
    "wait until all sound has been played"

    "/ as yet unimplemented
    ^ self
! !

!SoundStream::Win32DirectSound methodsFor:'open & close'!

closeFile
    "a stream has been collected - close the file"

%{
#ifdef SUPPORT_WIN32_DIRECTSOUND
    OBJ oDirectSound, oDSBuffer;
    LPDIRECTSOUND       t_pDirectSound;
    LPDIRECTSOUNDBUFFER t_pDSBuffer;

    if ((oDSBuffer = __INST(pDSBuffer)) != nil) {
        __INST(pDSBuffer) = nil;
        t_pDSBuffer = __DSBufferVal(oDSBuffer);
        if (t_pDSBuffer) {
            IDirectSoundBuffer_Stop(t_pDSBuffer);
            IDirectSoundBuffer_Release(t_pDSBuffer);
        }
    }
    if ((oDirectSound = __INST(pDirectSound)) != nil) {
        __INST(pDirectSound) = nil;
        t_pDirectSound = __DirectSoundVal(oDirectSound);
        if (t_pDirectSound) {
            IDirectSound_Release(t_pDirectSound);
        }
    }
    RETURN (self);
#endif /* SUPPORT_WIN32_DIRECTSOUND */
%}.

!

openWithMode:aMode attributes:attributeSpec
    |ok error errorStringOrNil|

%{
#ifdef SUPPORT_WIN32_DIRECTSOUND
    HRESULT result;
    LPDIRECTSOUND       t_pDirectSound;
    LPDIRECTSOUNDBUFFER t_pDSBuffer, t_pDSPrimeBuffer;
    WAVEFORMATEX        wfFormat;
    DSBUFFERDESC        dsbdDesc, primarydsbDesc;
    BYTE                *pDSBuffData;
    int                 t_cbBufSize;
    int                 dwDataLen;

    ok = false;

    /* Create the DS object */
    if ((result = DirectSoundCreate(NULL, &t_pDirectSound, NULL)) != DS_OK) {
        console_fprintf(stderr,"SoundStream: Cannot open default sound device!!\n");
        goto out;
    }

    /* Define the wave format structure */
    wfFormat.wFormatTag = WAVE_FORMAT_PCM;
    wfFormat.nChannels = __intVal(__INST(numberOfChannels));
    wfFormat.nSamplesPerSec = __intVal(__INST(sampleRate));
    wfFormat.wBitsPerSample = __intVal(__INST(bitsPerSample));
    wfFormat.nBlockAlign = wfFormat.nChannels * wfFormat.wBitsPerSample / 8;
    wfFormat.nAvgBytesPerSec = wfFormat.nSamplesPerSec * wfFormat.nBlockAlign;
    wfFormat.cbSize = 0;

#  if 0
    /* Setup the primary DS buffer description */
    ZeroMemory(&primarydsbDesc, sizeof(DSBUFFERDESC));
    primarydsbDesc.dwSize = sizeof(DSBUFFERDESC);
    primarydsbDesc.dwFlags = DSBCAPS_PRIMARYBUFFER;
    primarydsbDesc.dwBufferBytes = 0;
    primarydsbDesc.lpwfxFormat = NULL;

    /* Create the primary DS buffer */
    if ((result = IDirectSound_CreateSoundBuffer(t_pDirectSound, &primarydsbDesc,
                                                 &t_pDSPrimeBuffer, NULL)) != DS_OK) {
        console_fprintf(stderr,"SoundStream: Cannot get the primary DS buffer address!\n");
        IDirectSound_Release(t_pDirectSound);
        goto out;
    }

    /* Set the primary DS buffer sound format.  We have to do this because
       the default primary buffer is 8-bit, 22kHz! */
    if ((result = IDirectSoundBuffer_SetFormat(t_pDSPrimeBuffer, &wfFormat)) != DS_OK) {
        console_fprintf(stderr,"SoundStream: Cannot set the primary DS buffer to proper sound format (%x) (%d)!\n", result, result);
        IDirectSoundBuffer_Stop(t_pDSPrimeBuffer);
        IDirectSoundBuffer_Release(t_pDSPrimeBuffer);
        IDirectSound_Release(t_pDirectSound);
        goto out;
    }
#  endif /* 0 */

    /* Setup the secondary DS buffer description */
    t_cbBufSize = RT_BUFFER_SIZE * sizeof(short) * NBUFS;
    __INST(bufferSize) = __MKSMALLINT(t_cbBufSize);

    ZeroMemory(&dsbdDesc, sizeof(DSBUFFERDESC));
    dsbdDesc.dwSize = sizeof(DSBUFFERDESC);
    dsbdDesc.dwFlags = DSBCAPS_GLOBALFOCUS;
    dsbdDesc.dwBufferBytes = t_cbBufSize;
    dsbdDesc.lpwfxFormat = &wfFormat;

    /* Create the secondary DS buffer */
    if ((result = IDirectSound_CreateSoundBuffer(t_pDirectSound, &dsbdDesc, &t_pDSBuffer, NULL)) != DS_OK) {
        console_fprintf(stderr,"SoundStream: couldn't create sound buffer!\n");
        IDirectSoundBuffer_Stop(t_pDSPrimeBuffer);
        IDirectSoundBuffer_Release(t_pDSPrimeBuffer);
        IDirectSound_Release(t_pDirectSound);
        goto out;
    }

    /* Lock the DS buffer */
    if ((result = IDirectSoundBuffer_Lock(t_pDSBuffer, 0, t_cbBufSize, (LPLPVOID)&pDSBuffData,
                                          &dwDataLen, NULL, NULL, 0)) != DS_OK) {
        console_fprintf(stderr,"SoundStream: couldn't lock sound buffer!\n");
        goto errorAndOut;
    }

    /* Zero the DS buffer */
    ZeroMemory(pDSBuffData, dwDataLen);

    /* Unlock the DS buffer */
    if ((result = IDirectSoundBuffer_Unlock(t_pDSBuffer, pDSBuffData, dwDataLen, NULL, 0)) != DS_OK) {
        console_fprintf(stderr,"SoundStream: couldn't unlock sound buffer!\n");
        goto errorAndOut;
    }

    __INST(bufferOffset) = __MKSMALLINT(0);  // reset last write position to start of buffer

    /* Start the buffer playback */
    if ((result = IDirectSoundBuffer_Play(t_pDSBuffer, 0, 0, DSBPLAY_LOOPING) != DS_OK)) {
        console_fprintf(stderr,"SoundStream: couldn't play sound buffer!\n");

errorAndOut:
        IDirectSoundBuffer_Stop(t_pDSBuffer);
        IDirectSoundBuffer_Stop(t_pDSPrimeBuffer);
        IDirectSoundBuffer_Release(t_pDSPrimeBuffer);
        IDirectSound_Release(t_pDirectSound);
        goto out;
    }

    {
        OBJ t;

        t = __MKEXTERNALADDRESS(t_pDSBuffer); __INST(pDSBuffer) = t; __STORE(self, t);
        t = __MKEXTERNALADDRESS(t_pDirectSound); __INST(pDirectSound) = t; __STORE(self, t);
    }
    ok = true;
out:;
#endif /* SUPPORT_WIN32_DIRECTSOUND */

%}.
    ok == false ifTrue:[
        lastErrorString := errorStringOrNil.
        lastErrorNumber := error ? -1.
        self openError:error.
        "normally not reached"
        ^ nil.
    ].
    self registerForFinalization.
! !

!SoundStream::Win32DirectSound methodsFor:'queries'!

supportedAudioFormats
    "return a collection of supported audio formats.
     possibly returned symbols are:
        U8        unsigned 8bit samples
        S8        signed 8bit samples
        U16       unsigned 16bit samples in native format
        U16_LE    unsigned 16bit big endian samples
        U16_BE    unsigned 16bit big endian samples
        S16       signed 16bit little endian samples in native format
        S16_LE    signed 16bit little endian samples
        S16_BE    signed 16bit big endian samples
        S24       signed 24bit little endian samples in native format
        S24_LE    signed 24bit little endian samples
        S24_BE    signed 24bit big endian samples
        S32       signed 32bit little endian samples in native format
        S32_LE    signed 32bit little endian samples
        S32_BE    signed 32bit big endian samples
        F32       float samples
        MPEG      audio mpeg encoded
        MU_LAW    u-law encoded 8bit samples
        A_LAW     a-law encoded 8bit samples
        IMA_ADPCM adpcm encoded
     the set of returned symbols depends on the underlying sound hardware.
    "

    ^ #(S16_LE S16)

    "
     |s formats|

     s := self writing.
     formats := s supportedAudioFormats.
     s close.
     formats
    "
! !

!SoundStream::Win32DirectSound methodsFor:'reading'!

nextBytes:count into:anObject startingAt:start
    "read the next count bytes into an object and return the number of
     bytes read or nil on error.
     Use with ByteArrays only."

    self errorUnsupportedOperation
! !

!SoundStream::Win32DirectSound methodsFor:'writing'!

nextPutBytes:count from:anObject startingAt:start
    "write count bytes from an object starting at index start.
     return the number of bytes written or nil on error.
     Redefined, since IRIS audio library cannot be used with stdio.
     (at least I don't know). Use with ByteArrays only."

%{
#ifdef SUPPORT_WIN32_DIRECTSOUND
  {
    HRESULT hr;
    DWORD status;
    LPVOID lpbuf1 = NULL;
    LPVOID lpbuf2 = NULL;
    DWORD dwsize1 = 0;
    DWORD dwsize2 = 0;
    DWORD playPos, safePos, endWrite;
    DWORD millis;
    OBJ oDirectSound, oDSBuffer;
    LPDIRECTSOUND       t_pDirectSound = (LPDIRECTSOUND)0;
    LPDIRECTSOUNDBUFFER t_pDSBuffer = (LPDIRECTSOUNDBUFFER)0;
    int t_cbBufOffset, t_cbBufSize;
    short *buf;
    int cnt, offs;

    if ((oDSBuffer = __INST(pDSBuffer)) != nil) {
        t_pDSBuffer = __DSBufferVal(oDSBuffer);
    }
    if ((oDirectSound = __INST(pDirectSound)) != nil) {
        t_pDirectSound = __DirectSoundVal(oDirectSound);
    }

    if (!t_pDSBuffer || !t_pDirectSound) {
        console_fprintf(stderr, "SoundStream not open!\n");
        RETURN (0);
    }
    t_cbBufOffset = __intVal(__INST(bufferOffset));
    t_cbBufSize = __intVal(__INST(bufferSize));

    cnt = __intVal(count);
    offs = __intVal(start) - 1;
    buf = (short *)__InstPtr(anObject) + OHDR_SIZE + offs;

    // Should be playing, right?
    hr = IDirectSoundBuffer_GetStatus(t_pDSBuffer, &status );
    if (!(status && DSBSTATUS_PLAYING)) {
        console_fprintf(stderr, "Buffer not playing!\n");
        RETURN (0);
    }

    // Sleep until we have enough room in buffer.
    hr = IDirectSoundBuffer_GetCurrentPosition(t_pDSBuffer, &playPos, &safePos );
    if( hr != DS_OK ) {
        console_fprintf(stderr, "Cannot get position!\n");
        RETURN (0);
    }
    if( playPos < t_cbBufOffset ) playPos += t_cbBufSize;

    endWrite = t_cbBufOffset + (cnt * sizeof(short));
    while ( playPos < endWrite ) {
        // Calculate number of milliseconds until we will have room, as
        // time = distance * (milliseconds/second) / ((bytes/sample) * (samples/second)),
        // rounded up.
        millis = (DWORD) (1.0 + ((endWrite - playPos) * 1000.0) / ( sizeof(short) * __intVal(__INST(sampleRate))));

        // Sleep for that long
        Sleep( millis );

        // Wake up, find out where we are now
        hr = IDirectSoundBuffer_GetCurrentPosition(t_pDSBuffer, &playPos, &safePos );
        if( hr != DS_OK ) {
            console_fprintf(stderr, "Cannot get position!\n");
            RETURN (0);
        }
        if( playPos < t_cbBufOffset ) playPos += t_cbBufSize; // unwrap offset
    }

    // Lock free space in the DS
    hr = IDirectSoundBuffer_Lock(t_pDSBuffer, t_cbBufOffset, cnt * sizeof(short), &lpbuf1, &dwsize1, &lpbuf2, &dwsize2, 0);
    if (hr == DS_OK) {
        // Copy the buffer into the DS
        CopyMemory(lpbuf1, buf, dwsize1);
        if(NULL != lpbuf2) CopyMemory(lpbuf2, buf+dwsize1, dwsize2);

        // Update our buffer offset and unlock sound buffer
        t_cbBufOffset = (t_cbBufOffset + dwsize1 + dwsize2) % t_cbBufSize;
        IDirectSoundBuffer_Unlock(t_pDSBuffer, lpbuf1, dwsize1, lpbuf2, dwsize2);
    }
    __INST(buffferOffset) = __MKSMALLINT(t_cbBufOffset);

    RETURN (count);
  }
#endif /* SUPPORT_WIN32_DIRECTSOUND */

%}.
    self errorUnsupportedOperation
! !

!SoundStream::Win32WaveSound class methodsFor:'documentation'!

documentation
"
    interface to the windows wave sound API
"
! !

!SoundStream::Win32WaveSound class methodsFor:'queries'!

isSupported
%{
#ifdef SUPPORT_WIN32_WAVESOUND
    RETURN(true);
#endif
%}.
    ^ false.
! !

!SoundStream::Win32WaveSound methodsFor:'misc'!

flush
    "wait until all sound has been played"

    "/ as yet unimplemented
    ^ self
! !

!SoundStream::Win32WaveSound methodsFor:'open & close'!

closeFile
    "a stream has been collected - close the file"

%{
#ifdef SUPPORT_WIN32_WAVESOUND
    struct buf *bp, *next;
    int r;
    HWAVEOUT t_waveHandle;
    OBJ oWaveHandle;

    if ((oWaveHandle = __INST(waveHandle)) != nil) {
        t_waveHandle = __WaveHandleVal(oWaveHandle);

# ifdef NO_WAIT_IN_CLOSE
        /* Force cancellation of any pending buffers */
        (void)waveOutReset(t_waveHandle);
# endif

        /* Wait until all pending buffers have been freed */
        while (free_buffers < total_buffers) {
            WaitForSingleObject(free_buffer_event, INFINITE);
        }

# ifndef NO_WAIT_IN_CLOSE
        /* Force cancellation of any pending buffers */
        (void)waveOutReset(t_waveHandle);
# endif

        /* Close the device */
        if ((r = waveOutClose(t_waveHandle)) != 0) {
            console_printf("waveOutClose\n");
            RETURN(self);
        }

        EnterCriticalSection(&free_list_lock);

        /* Free allocated buffers */
        for (bp = free_list; bp != NULL; bp = next) {
            next = bp->next;
            (void)free(bp);
        }
        free_list = NULL;

        LeaveCriticalSection(&free_list_lock);

        __INST(waveHandle) = nil;
    }
    RETURN (self);
#endif /* SUPPORT_WIN32_WAVESOUND */
%}.

!

openWithMode:aMode attributes:attributeSpec
    |ok error errorStringOrNil|

%{
#ifdef SUPPORT_WIN32_WAVESOUND
    PCMWAVEFORMAT waveFormat;
    int r;
    HWAVEOUT t_waveHandle;
    OBJ oWaveHandle;

    ok = false;

    if ((oWaveHandle = __INST(waveHandle)) != nil) {
        goto out;
    }

    waveFormat.wf.wFormatTag = WAVE_FORMAT_PCM;
    waveFormat.wf.nChannels = __intVal(__INST(numberOfChannels));
    waveFormat.wf.nSamplesPerSec = __intVal(__INST(sampleRate));
    waveFormat.wBitsPerSample = __intVal(__INST(bitsPerSample));
    waveFormat.wf.nBlockAlign = waveFormat.wf.nChannels * waveFormat.wBitsPerSample / 8;
    waveFormat.wf.nAvgBytesPerSec = waveFormat.wf.nSamplesPerSec * waveFormat.wf.nBlockAlign;

    r = waveOutOpen(&t_waveHandle,
                    WAVE_MAPPER,
                    (WAVEFORMAT *)&waveFormat,
                    (DWORD_PTR)waveCallBack,
                    (DWORD_PTR)0,
                    CALLBACK_FUNCTION);
    if (r != 0) {
        console_printf("waveOutOpen\n");
        goto out;
    }

    (void)waveOutReset(t_waveHandle);

    free_list = NULL;
    InitializeCriticalSection(&free_list_lock);
    free_buffers = 0;
    free_buffer_event = CreateEvent(NULL, FALSE, FALSE, NULL);
    total_buffers = 0;

    {
        OBJ t;

        t = __MKEXTERNALADDRESS(t_waveHandle); __INST(waveHandle) = t; __STORE(self, t);
    }

# if 0
    /*
     * HACK: If we immediately start writing valid audio data to the device
     * then the sound is choppy in the beginning. Writing a null packet to
     * to the device first seems to fix this problem although I have no idea
     * why - DAC
     */
    {
        char null[DATALEN];
        int i;
        for (i = 0; i < DATALEN; i++) {
            null[i] = 127;
        }
        audioWrite(null, DATALEN);
    }
# endif /* 0 */
    ok = true;

out:;

#endif /* !SUPPORT_WIN32_DIRECTSOUND */
%}.
    ok == false ifTrue:[
        lastErrorString := errorStringOrNil.
        lastErrorNumber := error ? -1.
        self openError:error.
        "normally not reached"
        ^ nil.
    ].
    self registerForFinalization.
! !

!SoundStream::Win32WaveSound methodsFor:'queries'!

supportedAudioFormats
    "return a collection of supported audio formats.
     possibly returned symbols are:
        U8        unsigned 8bit samples
        S8        signed 8bit samples
        U16       unsigned 16bit samples in native format
        U16_LE    unsigned 16bit big endian samples
        U16_BE    unsigned 16bit big endian samples
        S16       signed 16bit little endian samples in native format
        S16_LE    signed 16bit little endian samples
        S16_BE    signed 16bit big endian samples
        S24       signed 24bit little endian samples in native format
        S24_LE    signed 24bit little endian samples
        S24_BE    signed 24bit big endian samples
        S32       signed 32bit little endian samples in native format
        S32_LE    signed 32bit little endian samples
        S32_BE    signed 32bit big endian samples
        F32       float samples
        MPEG      audio mpeg encoded
        MU_LAW    u-law encoded 8bit samples
        A_LAW     a-law encoded 8bit samples
        IMA_ADPCM adpcm encoded
     the set of returned symbols depends on the underlying sound hardware.
    "

    ^ #(S16_LE S16)

    "
     |s formats|

     s := self writing.
     formats := s supportedAudioFormats.
     s close.
     formats
    "
! !

!SoundStream::Win32WaveSound methodsFor:'reading'!

nextBytes:count into:anObject startingAt:start
    "read the next count bytes into an object and return the number of
     bytes read or nil on error.
     Use with ByteArrays only."

    self errorUnsupportedOperation
! !

!SoundStream::Win32WaveSound methodsFor:'writing'!

nextPutBytes:count from:anObject startingAt:start
    "write count bytes from an object starting at index start.
     return the number of bytes written or nil on error.
     Redefined, since IRIS audio library cannot be used with stdio.
     (at least I don't know). Use with ByteArrays only."

%{
#ifdef SUPPORT_WIN32_WAVESOUND
  {
    struct buf *bp;
    int len, i, r;
    int dataLen, offs;
    short *buf;

    HWAVEOUT t_waveHandle;
    OBJ oWaveHandle;

    if ((oWaveHandle = __INST(waveHandle)) == nil) {
        RETURN(0);
    }
    t_waveHandle = __WaveHandleVal(oWaveHandle);

    dataLen = __intVal(count);
    offs = __intVal(start) - 1;
    buf = (short *)__InstPtr(anObject) + OHDR_SIZE + offs;

    while (dataLen > 0) {
        if (free_list == NULL && total_buffers < MAXBUF) {
            /* Expand available buffer space */
            bp = (struct buf *)malloc(sizeof(struct buf));
            total_buffers++;
        } else {
            if (free_list == NULL) {
                /* We must wait for a free buffer */
                while (free_list == NULL) {
                    WaitForSingleObject(free_buffer_event, INFINITE);
                }
            }
            EnterCriticalSection(&free_list_lock);
            bp = free_list;
            free_list = free_list->next;
            --free_buffers;
            LeaveCriticalSection(&free_list_lock);
            r = waveOutUnprepareHeader(t_waveHandle, &bp->hdr, sizeof(WAVEHDR));
            if (r != 0) {
                console_printf("waveOutUnprepareHeader\n");
                RETURN(self);
            }
        }
        len = min(dataLen, DATALEN);
        bp->hdr.lpData = (char *)bp->data;
        bp->hdr.dwBufferLength = len;
        bp->hdr.dwBytesRecorded = len;
        bp->hdr.dwUser = (INT)(bp);
        bp->hdr.dwFlags = 0;
        bp->hdr.dwLoops = 0;
        r = waveOutPrepareHeader(t_waveHandle, &bp->hdr, sizeof(WAVEHDR));
        if (r != 0) {
            console_printf("waveOutPrepareHeader\n");
            RETURN(self);
        }
        for (i = 0; i < len; i++) {
            bp->data[i] = buf[i];
        }
        r = waveOutWrite(t_waveHandle, &bp->hdr, sizeof(WAVEHDR));
        if (r != 0) {
            console_printf("waveOutWrite\n");
            RETURN(self);
        }
        buf += len;
        dataLen -= len;
    }
    RETURN (count);
  }
#endif /* SUPPORT_WIN32_WAVESOUND */
%}.
    self errorUnsupportedOperation
! !

!SoundStream class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !


SoundStream initialize!