SoundStream.st
author Claus Gittinger <cg@exept.de>
Mon, 06 Oct 1997 15:29:57 +0200
changeset 575 f1fc72870c72
parent 353 d1b7f731a331
child 592 7daa4b2db7eb
permissions -rw-r--r--
eliminate MKOBJ & MKCP (use MKEXTERNALADDRESS & externalAddressVal)

"
 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'
	classVariableNames:'RampOff'
	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
%}
! !

!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
"
    Interface to audio device.
    Currently works with PD sound-blaster driver and
    sun audio device. On iris default setup is 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.

    see companion classes VocBrowser and VocView in fileIn-directory for
    how to use this class.

    [author:]
	Claus Gittinger
"
! !

!SoundStream class methodsFor:'instance creation'!

reading
    |newStream|
    newStream := (self basicNew) initialize.
    newStream openForReading isNil ifTrue:[^nil].
    ^ newStream

    "SoundStream reading"
!

writing
    |newStream|

    OperatingSystem getCPUType = '386' ifTrue:[
	"soundblaster special kludge to avoid click"
	RampOff isNil ifTrue:[
	    self generateRamp
	]
    ].
    newStream := (self basicNew) initialize.
    newStream openForWriting isNil ifTrue:[^nil].
    ^ newStream

    "
     SoundStream writing
    "

    "Created: 17.11.1995 / 17:25:42 / 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' ifFalse:[
	self error:'unsupported audio mode'.
	^ nil
    ].
    newStream := (self basicNew) initialize.
    newStream bitsPerSample:16.
    newStream numberOfChannels:2.
    newStream openForWriting isNil ifTrue:[^nil].
    ^ newStream

    "SoundStream writing16BitStereo"
! !

!SoundStream class methodsFor:'conversion tables'!

uLawToLinear:uLawValue
    "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)
! !

!SoundStream class methodsFor:'default values'!

blockSize
    "a good chunk size to read soundstream.
     Some devices may force a specific size ..."

    ^ 2048 "about 1/4 of a second" 
!

defaultBitsPerSample
    "minimum, supported by all audio systems"

    ^ 8
!

defaultMode
    ^ #linear "planned is at least uLaw"
!

defaultNumberOfChannels
    "minimum, supported by all audio systems"

    ^ 1
!

defaultSampleRate
    "minimum, supported by all audio systems"

    ^ 8000
! !

!SoundStream class methodsFor:'playing'!

playSoundFile:aFilename
    |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 class methodsFor:'private'!

generateRamp
    "create ramp data (need to be played on soundblaster
     before closing device to prevent audible click-on/off).
     This method just fills a buffer with ramp data."

    |size div|

    size := 256.
    div := size // 128.
    RampOff := ByteArray new:size.
    1 to:size do:[:index |
       RampOff at:index put:(size - index // div)
    ]

    "SoundStream generateRamp"
! !

!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:'instance release'!

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

    OperatingSystem getOSType = 'irix' ifFalse:[
	^ super closeFile
    ].
%{ 
#ifdef IRIS_AUDIO
    ALcloseport(_ALportVal(__INST(filePointer)));
#endif
%}
! !

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

    OperatingSystem getCPUType = '386' ifTrue:[
	"assume sound-blaster device"
	"set sound blasters sample rate"

	sampleRate := aNumber.
	self ioctl:1 "DSP_IOCTL_SPEED" with:aNumber
    ].
    OperatingSystem getOSType = 'sunos' ifTrue:[
	"audio sample rate is fix"
	^ self "cannot change"
    ].
    OperatingSystem getOSType = 'irix' ifTrue:[
	"could change using ALibrary ...for now, it is fix"
	sampleRate := aNumber.
    ].
! !

!SoundStream methodsFor:'private'!

initialize 
    "initialize for least common mode"

    buffered := false.
    bitsPerSample := 8.
    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.
    ].

"/    OperatingSystem getCPUType = '386' ifTrue:[
"/        "this code assumes a PD sound-blaster driver .."
"/        pathName := '/dev/sbdsp'
"/    ]

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

!SoundStream methodsFor:'redefined'!

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

"/    (mode == #writeonly) ifTrue:[
"/        "special handling of close on sound blaster,
"/         turn off voice but continue playing a ramp
"/         to avoid audible click"
"/
"/        OperatingSystem getCPUType = '386' ifTrue:[
"/            "assume sound-blaster device"
"/            self ioctl:2 "DSP_IOCTL_VOICE" with:0.
"/
"/            "OperatingSystem sleep:3.      "
"/            "add a ramp to zero to prevent click-off"
"/            super nextPutBytes:(RampOff size) from:RampOff
"/        ]
"/    ].    
    super close

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

flush
    "wait until all sound has been played"

%{ 
#ifdef IRIS_AUDIO
    ALport p;

    if (__INST(filePointer) != nil) {
        p = _ALportVal(__INST(filePointer));
        while (ALgetfilled(p) > 0) {
            sginap(1);
        }
    }
    RETURN(self);
#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) != _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 ( __MKSMALLINT(cnt) );
		}
	    }
	}
    }
  }
#endif
%}
.
    OperatingSystem getOSType = 'irix' ifFalse:[
	^ super nextPutBytes:count from:anObject startingAt:start

    ].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #readonly) ifTrue:[^ self errorReadOnly].
    self primitiveFailed
!

openWithMode:aMode
    OperatingSystem getOSType = 'irix' ifFalse:[
	"its a regular file open"
	^ super 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);
  }
#endif
%}
.
    ^ self
! !

!SoundStream methodsFor:'sine wave generation'!

tuneTone
    |buffer numSamples val scale|

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

    "fill it with a sine wave"

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

    buffer inspect.

    1 to:3 do:[:s |
	self nextPutBytes:numSamples from:buffer
    ]

    "SoundStream writing tuneTone"
! !

!SoundStream class methodsFor:'documentation'!

version
^ '$Header: /cvs/stx/stx/libbasic2/SoundStream.st,v 1.25 1997-10-06 13:29:57 cg Exp $'! !