SoundStream.st
author Claus Gittinger <cg@exept.de>
Mon, 15 Dec 1997 11:54:20 +0100
changeset 594 0d62900b49c8
parent 593 719f9d1c7bbb
child 595 fcff6c911d4a
permissions -rw-r--r--
*** empty log message ***

"
 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.
"

FileStream subclass:#SoundStream
	instanceVariableNames:'sampleRate numberOfChannels bitsPerSample audioFormat'
	classVariableNames:''
	poolDictionaries:''
	category:'Streams-External'
!

!SoundStream primitiveDefinitions!
%{
#ifdef IRIS
# ifndef IRIX5
#  define IRIS_AUDIO
# endif
#endif

#ifdef IRIS_AUDIO
# include <audio.h>
# define _ALportVal(o)  (ALport)(__externalAddressVal(o))
#endif

#ifdef LINUX
# define DEV_AUDIO
# include <sys/soundcard.h>
#endif

#if defined(sunos) || defined(solaris)
# define DEV_AUDIO
#endif

#ifdef DEV_AUDIO
# include <stdio.h>
#endif
%}
! !

!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 audio device.
    Currently works with LINUXs or SUNs /dev/audio driver and
    IRIX (indy). 
    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
"
! !

!SoundStream class methodsFor:'instance creation'!

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

    |newStream|
    newStream := (self basicNew) initialize.
    newStream openForReading isNil ifTrue:[^nil].
    newStream buffered:false.
    newStream binary.
    ^ 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 basicNew) initialize.
    newStream openForWriting isNil ifTrue:[^nil].
    newStream buffered:false.
    newStream binary.
    ^ newStream

    "
     SoundStream writing
    "

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

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

    |newStream|

    OperatingSystem getCPUType ~= 'irix' ifTrue:[
	self error:'unsupported audio mode'.
	^ nil
    ].
    newStream := (self basicNew) initialize.
    newStream buffered:false.
    newStream binary.
    newStream bitsPerSample:16.
    newStream numberOfChannels:2.
    newStream openForWriting isNil ifTrue:[^nil].
    ^ newStream

    "SoundStream writing16BitStereo"

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

!SoundStream class methodsFor:'conversion helpers'!

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"
!

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
    "/
    sign := 0.
    (absVal := a16bitSignedValue asInteger) < 0 ifTrue:[
	(absVal <= -32256) ifTrue:[
	    ^ 0
	].
	absVal := absVal negated.
	sign := 16r80
    ] ifFalse:[
	absVal >= 32256 ifTrue:[
	    ^ 128
	]
    ].

    exp := #[
	      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 
	   ] at:(absVal bitShift:-1)+1.
    mantissa := (absVal bitShift:(exp+3) negated) bitAnd:16r0F.
    byte := ((sign bitOr:(exp bitShift:4)) bitOr:mantissa) bitInvert bitAnd:16rFF.
    ^ byte

    "
     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"
! !

!SoundStream class methodsFor:'default values'!

defaultBitsPerSample
    "minimum, supported by all audio systems"

    ^ 8
!

defaultAudioFormat
    ^ #U8 
!

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"

    |inStream soundStream count totalCount buffer startTime playTime delayedTime waitTime|

    inStream := aFilename asFilename readStream.
    inStream isNil ifTrue:[^ self].

    soundStream := self writing.
    soundStream isNil ifTrue:[^ self].
    soundStream buffered:false.

    startTime := AbsoluteTime now.
    totalCount := 0.

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

    inStream close.
    soundStream commit.

    "/
    "/ at least the linux audio driver behaves funny, if we close too early ...
    "/
    playTime := totalCount / soundStream sampleRate.
    delayedTime := (AbsoluteTime now - 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'
    "

    "Created: 17.11.1995 / 17:25:30 / cg"
    "Modified: 17.11.1995 / 17:45:40 / cg"
! !

!SoundStream methodsFor:'private'!

dumpSettings
    "debugging interface - dump the current settings"

    |fd blockSize audioFormatMask speed channels stereo|

    fd := self fileDescriptor.
    fd isNil ifTrue:[
	self error.
	^ nil
    ].
%{
    int f = __intVal(fd);
    int __audioFormatMask = 0;
    int __blockSize = -1;
    int __speed = 0;
    int __stereo = 0;
    int __channels = 0;

#if defined(DEV_AUDIO) 
# if defined(LINUX)
    if (ioctl(f, SNDCTL_DSP_GETBLKSIZE, &__blockSize) >= 0) {
	blockSize = __MKSMALLINT(__blockSize);
    }
    if (ioctl(f, SNDCTL_DSP_CHANNELS, &__channels) >= 0) {
	channels = __MKSMALLINT(__channels);
    }
    if (ioctl(f, SNDCTL_DSP_STEREO, &__stereo) >= 0) {
	stereo = __MKSMALLINT(__stereo);
    }
    if (ioctl(f, SNDCTL_DSP_SPEED, &__speed) >= 0) {
	speed = __MKSMALLINT(__speed);
    }
    if (ioctl(f, SNDCTL_DSP_GETFMTS, &__audioFormatMask) >= 0) {
	audioFormatMask = __MKSMALLINT(__audioFormatMask);
    }
# endif /* LINUX */
#endif /* DEV_AUDIO */
%}.
    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
    ].

    audioFormatMask notNil ifTrue:[
	Transcript show:'audioFormatMask: '; showCR:audioFormatMask hexPrintString
    ].

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

    "
     self writing dumpSettings; close
    "
!

supportedAudioFormats
    "return a collection of supported audio formats.
     returned symbols are:
	U8        unsigned 8bit samples
	S8        signed 8bit samples
	MU_LAW    u-law encoded 8bit samples
	A_LAW     a-law encoded 8bit samples
	IMA_ADPCM adpcm encoded
	U16       unsigned 16bit samples
	U16_LE    unsigned 16bit big endian samples
	U16_BE    unsigned 16bit big endian samples
	S16       signed 16bit little endian samples
	S16_LE    signed 16bit little endian samples
	S16_BE    signed 16bit big endian samples
	MPEG      audio mpeg encoded
    "

    |fd audioFormatMask
     supportedFormats
     supports_MU_LAW supports_A_LAW
     supports_IMA_ADPCM supports_U8
     supports_S16_LE supports_S16_BE
     supports_S8 supports_U16_LE
     supports_U16_BE supports_MPEG|

    fd := self fileDescriptor.
    fd isNil ifTrue:[
	self error.
	^ nil
    ].
%{
    int f = __intVal(fd);
    int __audioFormatMask = 0;

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

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

#ifdef IRIS_AUDIO
	supports_U8 = true;
	supports_U16_BE = true;
#endif

%}.
    supportedFormats := IdentitySet new.
    audioFormatMask notNil ifTrue:[
	supports_MU_LAW ifTrue:[
	    supportedFormats add:#'MU_LAW'
	].
	supports_A_LAW ifTrue:[
	    supportedFormats add:#'A_LAW'
	].
	supports_IMA_ADPCM ifTrue:[
	    supportedFormats add:#'IMA_ADPCM'
	].
	supports_S8 ifTrue:[
	    supportedFormats add:#'S8'
	].
	supports_U8 ifTrue:[
	    supportedFormats add:#'U8'
	].
	supports_S16_LE ifTrue:[
	    supportedFormats add:#'S16_LE'.
	    supportedFormats add:#'S16'.
	].
	supports_S16_BE ifTrue:[
	    supportedFormats add:#'S16_BE'.
	    supportedFormats add:#'S16'.
	].
	supports_U16_LE ifTrue:[
	    supportedFormats add:#'U16_LE'.
	    supportedFormats add:#'U16'.
	].
	supports_U16_BE ifTrue:[
	    supportedFormats add:#'U16_BE'.
	    supportedFormats add:#'U16'.
	].
	supports_MPEG ifTrue:[
	    supportedFormats add:#'MPEG'
	].
    ].
    ^ supportedFormats.

    "
     |s formats|

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

resetSoundCard
    "debugging interface - reset the soundCard"

    |fd|

    fd := self fileDescriptor.
    fd isNil ifTrue:[
	self error.
	^ nil
    ].
%{
    int f = __intVal(fd);
    int __dummy;

#if defined(DEV_AUDIO) && defined(LINUX)
    if (ioctl(f, SNDCTL_DSP_RESET, &__dummy) >= 0) {
	RETURN (true);
    }
#endif
%}.
    ^ false

    "
     self writing resetSoundCard; dumpSettings; close
    "
!

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

    |fd|

    fd := self fileDescriptor.
    fd isNil ifTrue:[
	self error.
	^ nil
    ].
%{
    int f = __intVal(fd);
    int __fmt = 0;
    union {
	unsigned short us;
	unsigned char ub[2];
    } u;

#if defined(DEV_AUDIO) && defined(LINUX)
    if (__isSymbol(aSymbol)) {

	if (aSymbol == @symbol(U16)) {
	    u.us = 0x1234;
	    if (u.ub[0] == 0x12) {
		__fmt = AFMT_U16_BE;
	    } else {
		__fmt = AFMT_U16_LE;
	    }
	} else if (aSymbol == @symbol(S16)) {
	    u.us = 0x1234;
	    if (u.ub[0] == 0x12) {
		__fmt = AFMT_S16_BE;
	    } else {
		__fmt = AFMT_S16_LE;
	    }
	}

	if (aSymbol == @symbol(MU_LAW)) {
	    __fmt = AFMT_MU_LAW;
	} else if (aSymbol == @symbol(A_LAW)) {
	    __fmt = AFMT_A_LAW;
	} else if (aSymbol == @symbol(IMA_ADPCM)) {
	    __fmt = AFMT_IMA_ADPCM;
	} else if (aSymbol == @symbol(U8)) {
	    __fmt = AFMT_U8;
	} else if (aSymbol == @symbol(S8)) {
	    __fmt = AFMT_S8;
	} else if (aSymbol == @symbol(U16_LE)) {
	    __fmt = AFMT_U16_LE;
	} else if (aSymbol == @symbol(U16_BE)) {
	    __fmt = AFMT_U16_BE;
	} else if (aSymbol == @symbol(S16_LE)) {
	    __fmt = AFMT_S16_LE;
	} else if (aSymbol == @symbol(S16_BE)) {
	    __fmt = AFMT_A_LAW;
	} else if (aSymbol == @symbol(MPEG)) {
	    __fmt = AFMT_MPEG;
	} else {
	    RETURN (false);
	}
    }

    if (ioctl(f, SNDCTL_DSP_SETFMT, &__fmt) >= 0) {
	__INST(audioFormat) = aSymbol;
	RETURN (true);
    }
    RETURN (false);
#endif
%}.
    ^ false

    "
     self writing setAudioFormat:#'MU_LAW'; close
    "
!

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

    |fd|

    fd := self fileDescriptor.
    fd isNil ifTrue:[
	self error.
	^ nil
    ].
%{
    int f = __intVal(fd);
    int __nCh = 0;

#if defined(DEV_AUDIO) && defined(LINUX)
    if (__isSmallInteger(nChannels)) {
	__nCh = __intVal(nChannels);
	if (ioctl(f, SOUND_PCM_WRITE_CHANNELS, &__nCh) >= 0) {
	    __INST(numberOfChannels) = nChannels;
	    RETURN (true);
	}
    }
    RETURN (false);
#endif
%}.
    ^ false

    "
     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 soundDrivers fragmentSize.
     Returns true if sucessfull - may fail with many sound devices."

    |fd|

    fd := self fileDescriptor.
    fd isNil ifTrue:[
	self error.
	^ nil
    ].
%{
    int f = __intVal(fd);
    int __blockSize = 0;

#if defined(DEV_AUDIO) && defined(LINUX)
    if (__isSmallInteger(blockSize)) {
	__blockSize = __intVal(blockSize);
	if (ioctl(f, SNDCTL_DSP_SETFRAGMENT, &__blockSize) >= 0) {
	    /* __INST(blockSize) = blockSize; */
	    RETURN (true);
	}
    }
    RETURN (false);
#endif
%}.
    ^ false
!

setSampleRate:hz
    "set the sample rate.
     Returns true if sucessfull - may fail with many sound devices."

    |fd|

    fd := self fileDescriptor.
    fd isNil ifTrue:[
	self error.
	^ nil
    ].
%{
    int f = __intVal(fd);
    int __rate = 0;
    int __rateWant;

#if defined(DEV_AUDIO) && defined(LINUX)
    if (__isSmallInteger(hz)) {
	__rate = __rateWant = __intVal(hz);
	if (ioctl(f, SOUND_PCM_WRITE_RATE, &__rate) >= 0) {
	    if (__rate != __rateWant) {
		fprintf(stderr, "SoundStream [warning]: actual rate is %d\n", __rate);
		hz = __MKSMALLINT(__rate);
	    }
	    __INST(sampleRate) = hz;
	    RETURN (true);
	}
    }
    RETURN (false);
#endif
%}.
    ^ false

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

!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:'mode setting'!

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

    ^ bitsPerSample
!

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

    bitsPerSample := aNumber
!

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

    ^ numberOfChannels
!

numberOfChannels:aNumber
    "set the number of channels"

    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'!

initialize 
    "initialize for least common mode"

    buffered := false.
    bitsPerSample := 8.
    audioFormat := #U8.
    numberOfChannels := 1.
    sampleRate := 8000.

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

    OperatingSystem getOSType = 'irix' ifTrue:[
	"no device, use special library calls"
	pathName := nil.
    ].

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

!SoundStream methodsFor:'redefined'!

close
    OperatingSystem getOSType = 'irix' ifTrue:[
	^ self closeFile
    ].

    super close

    "Created: 17.11.1995 / 17:27:26 / cg"
    "Modified: 17.11.1995 / 17:47:13 / cg"
!

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

%{
#ifdef IRIS_AUDIO
    ALcloseport(_ALportVal(__INST(filePointer)));
#endif
#if defined(DEV_AUDIO)
    OBJ fp;
    int fd;
    FILE *f;

    if ((fp = __INST(filePointer)) != nil) {
	f = __FILEVal(fp);
	__INST(filePointer) = 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
    }
#endif /* DEV_AUDIO */
%}
!

flush
    "wait until all sound has been played"

    |fd|

    fd := self fileDescriptor.
%{ 
#ifdef IRIS_AUDIO
    ALport p;

    if (__INST(filePointer) != nil) {
	p = _ALportVal(__INST(filePointer));
	while (ALgetfilled(p) > 0) {
	    sginap(1);
	}
    }
    RETURN(self);
#endif

#if defined(DEV_AUDIO) && defined(LINUX)
    if (__isSmallInteger(fd)) {
	int f = __intVal(fd);
	/* ... */
    }
#endif
%}.
    "dont know how to wait on non-iris systems"
    ^ self
!

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 IRIS_AUDIO
  {
    ALport p;
    int cnt, offs;
    int objSize;
    char *cp;

    if (__INST(filePointer) != nil) {
	if (__INST(mode) != _writeonly) {
	    if (__bothSmallInteger(count, start)) {
		cnt = _intVal(count);
		offs = _intVal(start) - 1;
		p = _ALportVal(__INST(filePointer));
		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))
			ALreadsamps(p, cp, cnt / 2);
		    else
			ALreadsamps(p, cp, cnt);
		    RETURN ( __MKSMALLINT(cnt) );
		}
	    }
	}
    }
  }
#endif
%}.
    OperatingSystem getOSType = 'irix' ifFalse:[
	^ super nextPutBytes:count from:anObject startingAt:start
    ].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    self primitiveFailed
!

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 dont know). Use with ByteArrays only."

%{
#ifdef IRIS_AUDIO
  {
    ALport p;
    int cnt, offs;
    int objSize;
    char *cp;

    if (__INST(filePointer) != nil) {
	if (__INST(mode) != @symbol(readonly)) {
	    if (__bothSmallInteger(count, start)) {
		cnt = _intVal(count);
		offs = _intVal(start) - 1;
		p = _ALportVal(__INST(filePointer));

		/*
		 * 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))
			ALwritesamps(p, cp, cnt / 2);
		    else
			ALwritesamps(p, cp, cnt);
		    RETURN ( count );
		}
	    }
	}
    }
  }
#endif

#if defined(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(filePointer)) != 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)) ) {
		    cp = (char *)__InstPtr(anObject) + OHDR_SIZE + offs;

# ifdef LINUX
		    sigsetmask(~0);
# endif
		    do {
			n = cnt;
			if (n > 4096) n = 4096;
			if (__INST(buffered) == true) {
			    n = fwrite(cp, 1, n, f);
			} else {
			    fd = fileno(f);
			    n = write(fd, cp, n);
			}
			if (n > 0) {
			    cp += n;
			    cnt -= n;
			}
		    } while (cnt);
# ifdef LINUX
		    sigsetmask(0);
# endif
		}
		RETURN (count);
	    }
	}
    }
#endif

%}.
    ^ super nextPutBytes:count from:anObject startingAt:start
!

openWithMode:aMode
    ((aMode = 'r') or:[aMode = 'w']) ifFalse:[
	self error:'invalid mode'.
	^ nil
    ].
%{
#ifdef IRIS_AUDIO
  {
    ALconfig config;
    ALport p;
    long params[] = {
	AL_INPUT_SOURCE, AL_INPUT_MIC,
	AL_INPUT_RATE, 8000,
	AL_OUTPUT_RATE, 8000,
    };

    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) {
	__INST(filePointer) = __MKEXTERNALADDRESS(p);
    } else {
	__INST(filePointer) = nil;
	RETURN (nil);
    }
    __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);
    RETURN (self);
  }
#endif
%}.
    "its a regular file open (i.e. /dev/audio) "
    ^ super openWithMode:aMode
! !

!SoundStream methodsFor:'sine wave generation'!

tuneTone:freq
    |buffer numSamples val scale oldFormat|

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

    "fill it with a sine wave"

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

    oldFormat := audioFormat.
    self setAudioFormat:#U8.
    1 to:3 do:[:s |
	self nextPutBytes:numSamples from:buffer startingAt:1
    ].
    self setAudioFormat:oldFormat.

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

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

    "Modified: / 12.12.1997 / 20:34:27 / cg"
!

tuneTone
    self tuneTone:440

    "
     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:20000; dumpSettings; close
    "

    "Modified: / 12.12.1997 / 20:34:42 / cg"
! !

!SoundStream class methodsFor:'documentation'!

version
^ '$Header: /cvs/stx/stx/libbasic2/SoundStream.st,v 1.28 1997-12-15 10:54:20 cg Exp $'! !