1 /* sqUnixSoundNAS.c -- sound support for the Network Audio System
2  *
3  * Author: Lex Spoon <lex@cc.gatech.edu>
4  *
5  *   Copyright (C) 1996-2004 by Ian Piumarta and other authors/contributors
6  *                              listed elsewhere in this file.
7  *   All rights reserved.
8  *
9  *   This file is part of Unix Squeak.
10  *
11  *   Permission is hereby granted, free of charge, to any person obtaining a copy
12  *   of this software and associated documentation files (the "Software"), to deal
13  *   in the Software without restriction, including without limitation the rights
14  *   to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
15  *   copies of the Software, and to permit persons to whom the Software is
16  *   furnished to do so, subject to the following conditions:
17  *
18  *   The above copyright notice and this permission notice shall be included in
19  *   all copies or substantial portions of the Software.
20  *
21  *   THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
22  *   IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
23  *   FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
24  *   AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
25  *   LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
26  *   OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
27  *   SOFTWARE.
28  */
29 
30 #include "sq.h"
31 #include "sqaio.h"
32 
33 #include <audio/audiolib.h>
34 #include <assert.h>
35 
36 #ifdef DEBUG
37 # define debugf printf
38 #else
debugf(char * fmt,...)39   static void debugf(char *fmt, ...) {}
40 #endif
41 
42 
43 #ifdef WORDS_BIGENDIAN
44 # define AU_FORMAT	AuFormatLinearSigned16MSB
45 #else
46 # define AU_FORMAT	AuFormatLinearSigned16LSB
47 #endif
48 
49 
50 static int sound_Stop(void);
51 
52 /** routines for converting samples to different formats **/
53 
54 /* XXX actually, I don't think NAS will need conversion.  However,
55    SunOS could use it... */
56 
57 #define BYTES_PER_SAMPLE	2		/* Squeak always uses 16-bit samples */
58 
59 #ifdef HAS_MSB_FIRST
60 # define IS_BIGENDIAN 1
61 #else
62 # define IS_BIGENDIAN 0
63 #endif
64 
65 
66 /* specification of the output format.  (Squeak's format is fixed:
67    stereo, 16-bit, host-endian, signed) */
68 
69 static int fmtBytes=             2;  /* bytes per sample the device is using */
70 static int fmtSigned=            1;  /* whether the device uses signed samples */
71 static int fmtStereo=		 0;  /* whether the device is in stereo */
72 static int fmtIsBigendian=       0;  /* whether the device is big-endion */
73 
74 
75 /* whether the device is differently-ended than Squeak */
76 
77 #define auSwapBytes (fmtIsBigendian != IS_BIGENDIAN)
78 
79 
80 /* calculate number of bytes per frame, given the current mode */
81 
bytesPerPlayFrame(void)82 static int bytesPerPlayFrame(void)
83 {
84 #if 1		/* ikp doesn't understand why this ... */
85   int bytes= 1;
86   bytes *= fmtBytes;
87   if (fmtStereo)
88     bytes *= 2;
89   return bytes;
90 #else		/* ... doesn't look like this */
91   return fmtBytes * (fmtStereo ? 2 : 1);
92 #endif
93 }
94 
95 
96 #define FAIL(X) { success(false); return X; }
97 
98 static AuServer *server = NULL;   /* the audio server to write to */
99 static int recording=0;        /* whether this module is recording
100 				  or playing.  Only valid if
101 				  server!= NULL . */
102 static AuFlowID flow;          /* the NAS flow being used */
103 static int semaIndex;          /* the semaphore to signal Squeak with */
104 static int stereo;             /* whether Squeak sees stereo or not */
105 static sqInt bytesAvail;       /* current number of bytes that may be written
106 				  or read from the server */
107 static int sampleRate;         /* the sample rate of the device.
108 				  Currently not accurate. */
109 
110 
sound_AvailableSpace(void)111 static sqInt sound_AvailableSpace(void)
112 {
113   if (server == NULL)
114     return 0;
115 
116   return bytesAvail;
117 }
118 
sound_InsertSamplesFromLeadTime(sqInt frameCount,void * srcBufPtr,sqInt samplesOfLeadTime)119 static sqInt sound_InsertSamplesFromLeadTime(sqInt frameCount, void *srcBufPtr,
120 				  sqInt samplesOfLeadTime)
121 {
122   /* not possible, I don't think using NAS */
123   success(false);
124   return 0;
125 }
126 
127 
sound_Stop(void)128 static sqInt sound_Stop(void)
129 {
130   if (server != NULL) {
131     aioDisable(AuServerConnectionNumber(server));
132 
133     AuCloseServer(server);
134     server = NULL;
135   }
136 
137   return 0;
138 }
139 
140 
141 
142 
143 
sound_PlaySamplesFromAtLength(sqInt frameCount,void * srcBufPtr,sqInt startIndex)144 static sqInt sound_PlaySamplesFromAtLength(sqInt frameCount, void *srcBufPtr, sqInt startIndex)
145 {
146   int bytesToPlay;
147   int framesToPlay;
148   char *buf;   /* buffer to play from; it may not be srcBufPtr if a
149                   conversion is necessary */
150 
151   debugf("PlaySamples(frameCount=%d, srcBufPtr=%d, startIndex=%d\n", frameCount, srcBufPtr, startIndex);
152 
153   /* figure out how much to play */
154   bytesToPlay = frameCount * bytesPerPlayFrame();
155   if (bytesToPlay > bytesAvail)
156     bytesToPlay = bytesAvail;
157 
158   framesToPlay = bytesToPlay / bytesPerPlayFrame();
159 
160   /* convert the buffer when not in stereo; when playing back, Squeak
161      will send mono data as stereo, where the right channel is to be
162      ignored */
163   if (stereo)
164     {
165       buf= (char *) (srcBufPtr+ 4*startIndex);
166     }
167   else
168     {
169       int i;
170       short *sbuf;  /* the buffer, as short's instead of char's */
171 
172       debugf("converting\n");
173 
174       buf= malloc(2 * frameCount);
175       if (buf == NULL)
176 	{
177 	  fprintf(stderr, "out of memory\n");
178 	  return 0;
179 	}
180       sbuf= (short *) buf;
181 
182 
183       for(i=0; i<frameCount; i++)
184 	{
185 	  sbuf[i]= ((short *) (srcBufPtr + 4*startIndex)) [2*i];
186 	}
187     }
188 
189 
190   debugf("writing %d bytes (%d frames)\n", bytesToPlay, framesToPlay);
191   AuWriteElement(server, flow, 0,
192 		 bytesToPlay,
193 		 buf,
194 		 AuFalse,
195 		 NULL);
196   AuFlush(server);
197 
198 
199   bytesAvail -= bytesToPlay;
200 
201   if (!stereo)
202     {
203       free(buf);
204     }
205 
206   return framesToPlay;
207 }
208 
209 
210 /* Process audio events from the NAS server.  The same routine is used
211    whether we are recording or playing back */
handleAudioEvents(int fd,void * data,int flags)212 static void handleAudioEvents(int fd, void *data, int flags)
213 {
214   if (!server) {
215     debugf( "handleAudioEvents called while unconnected!\n");
216     return;
217   }
218 
219   /* read events once */
220   AuEventsQueued(server, AuEventsQueuedAfterReading);
221 
222   /* then loop through the read queue */
223   while(AuEventsQueued(server, AuEventsQueuedAlready)) {
224     AuEvent event;
225     AuNextEvent(server, AuTrue, &event);
226     debugf("event of type %d\n", event.type);
227 
228     switch(event.type) {
229     case 0:
230       {
231 	AuErrorEvent *errEvent = (AuErrorEvent *) &event;
232 	char errdesc[1000];
233 
234 	AuGetErrorText(server, errEvent->error_code, errdesc, sizeof(errdesc));
235 	fprintf(stderr, "audio error: %s\n", errdesc);
236 	sound_Stop();
237 	return;  /* return, not break, so that we don't
238 		    process the now-closed server any longer! */
239       }
240 
241 
242     case AuEventTypeElementNotify:
243       {
244 	AuElementNotifyEvent *enEvent = (AuElementNotifyEvent *)&event;
245 
246 	switch(enEvent->kind) {
247 	case AuElementNotifyKindLowWater:
248 	  debugf("low water event\n");
249 	  bytesAvail += enEvent->num_bytes;
250 	  break;
251 	case AuElementNotifyKindHighWater:
252 	  debugf("high water event\n");
253 	  bytesAvail += enEvent->num_bytes;
254 	  break;
255 	case AuElementNotifyKindState:
256 	  debugf("state change (%d->%d)\n", enEvent->prev_state, enEvent->cur_state);
257 	  bytesAvail += enEvent->num_bytes;
258 	  if (enEvent->cur_state == AuStatePause) {
259 	       /* if the flow has stopped, then arrange for it to get started again */
260 	       /* XXX there is probably a more intelligent place to do
261                   this, in case there is a real reason it has paused */
262 	       debugf("unpausing\n");
263 	       AuStartFlow(server, flow, NULL);
264 	       AuFlush(server);
265 	  }
266 
267 	  break;
268 	}
269       }
270     }
271   }
272 
273   if (bytesAvail > 0) {
274     debugf("bytesAvail: %d\n", bytesAvail);
275     signalSemaphoreWithIndex(semaIndex);
276   }
277 
278   aioHandle(fd, handleAudioEvents, flags & AIO_RW);
279 }
280 
sound_PlaySilence(void)281 static sqInt sound_PlaySilence(void)
282 {
283      return 0;
284 }
285 
286 
choose_nas_device(AuServer * server,int samplesPerSec,int stereo,int recording)287 static AuDeviceID choose_nas_device(AuServer *server, int samplesPerSec, int stereo, int recording)
288 {
289   int desiredDeviceKind=
290     recording ?
291        AuComponentKindPhysicalInput :
292        AuComponentKindPhysicalOutput;
293   int desired_channels= stereo ? 2 : 1;
294   int i;
295 
296   /* look for a physical device of the proper kind, with the proper number of channels */
297   for (i = 0; i < AuServerNumDevices(server); i++) {
298     if ((AuDeviceKind(AuServerDevice(server, i))
299 	==  desiredDeviceKind)
300        && (AuDeviceNumTracks(AuServerDevice(server, i))
301 	   ==  desired_channels))
302 	 return AuDeviceIdentifier(AuServerDevice(server, i));
303   }
304 
305 
306 
307   /* look for a physical device of the proper kind; ignore number of channels */
308   for (i = 0; i < AuServerNumDevices(server); i++) {
309     if (AuDeviceKind(AuServerDevice(server, i))
310        ==  desiredDeviceKind)
311 	 return AuDeviceIdentifier(AuServerDevice(server, i));
312   }
313 
314 
315 
316   return AuNone;
317 }
318 
sound_Start(sqInt frameCount,sqInt samplesPerSec,sqInt stereo0,sqInt semaIndex0)319 static sqInt sound_Start(sqInt frameCount, sqInt samplesPerSec, sqInt stereo0, sqInt semaIndex0)
320 {
321   AuElement elements[2];  /* first is a client element, second is
322 			     a device output element */
323   AuDeviceID device;        /* ID of the device to play to */
324 
325 
326   /* open the server */
327   debugf("opening server\n");
328   server = AuOpenServer(NULL, 0, NULL, 0, NULL, NULL);
329   if (server == NULL) {
330     debugf("failed to open audio server\n");
331     return false;
332   }
333 
334   /* XXX should check the protocol version! */
335 
336   /* record requested info */
337   semaIndex = semaIndex0;
338   stereo = stereo0;
339   sampleRate= samplesPerSec;
340 
341   /* pick a device to play to */
342   device = choose_nas_device(server, samplesPerSec, stereo, 0);
343   if (device == AuNone) {
344     debugf("no available device on the server!\n");
345     AuCloseServer(server);
346     server = NULL;
347     return false;
348   }
349 
350   /* set up output parameters */
351   fmtBytes=2;
352   fmtSigned=1;
353   fmtStereo=stereo;
354   fmtIsBigendian=0;
355   recording=0;
356 
357 
358 
359   /* create a flow to write on */
360   debugf("creating flow\n");
361   flow = AuCreateFlow(server, NULL);
362 
363 
364   /* create client and device elements to play with */
365   debugf("creating elements(%d,%d)\n", frameCount, frameCount / 4);
366   AuMakeElementImportClient(&elements[0],
367 			    samplesPerSec,
368 			    AuFormatLinearSigned16LSB,  /* XXX this should be chosen based on the platform */
369 			    stereo ? 2 : 1,
370 			    AuTrue,
371 			    2*frameCount,   /* max: 2 buffers */
372 			    frameCount,   /* low */
373 			    0, NULL);
374 
375   AuMakeElementExportDevice(&elements[1],
376 			    0,
377 			    device,
378 			    samplesPerSec,
379 			    AuUnlimitedSamples,
380 			    0, NULL);
381 
382   /* set up the flow with these elements */
383   AuSetElements(server,	flow,
384 		AuTrue,
385 		2, elements,
386 		NULL);
387 
388   /* start her up */
389   debugf("starting flow\n");
390   AuStartFlow(server, flow, NULL);
391   AuFlush(server);
392 
393 
394   /* initialize the space indication */
395   bytesAvail = 0;
396 
397 
398   /* arrange to be informed when events come in from the server */
399   aioEnable(AuServerConnectionNumber(server), 0, AIO_EXT);
400   aioHandle(AuServerConnectionNumber(server), handleAudioEvents, AIO_R);
401 
402 
403 
404   return true;
405 }
406 
407 
408 
409 /* StartRecording: open the device for recording.
410 
411    XXX this routine is almost identical to snd_Start().  The two should
412    be factored into a single function!
413 */
sound_StartRecording(sqInt desiredSamplesPerSec,sqInt stereo0,sqInt semaIndex0)414 static sqInt sound_StartRecording(sqInt desiredSamplesPerSec, sqInt stereo0, sqInt semaIndex0)
415 {
416   AuElement elements[2];  /* elements for the NAS flow to assemble:
417    			        element 0 = physical input
418 			        element 1 = client export */
419   AuDeviceID device;      /* physical device ID to use */
420 
421   debugf("StartRecording\n");
422 
423   sound_Stop();
424 
425   debugf("opening server\n");
426   server = AuOpenServer(NULL, 0, NULL, 0, NULL, NULL);
427   if (server == NULL) {
428     debugf("failed to open audio server\n");
429     return false;
430   }
431 
432   /* XXX check protocol version of the server */
433 
434   semaIndex= semaIndex0;
435   stereo= stereo0;
436   sampleRate= desiredSamplesPerSec;
437 
438   device= choose_nas_device(server, desiredSamplesPerSec, stereo, 1);
439   if (device == AuNone) {
440     debugf("no available device on the server!\n");
441     AuCloseServer(server);
442     server = NULL;
443     return false;
444   }
445 
446   /* record format info */
447   fmtBytes=2;
448   fmtSigned=1;
449   fmtStereo=stereo;
450   fmtIsBigendian=0;
451   recording=1;
452 
453 
454 
455 
456   /* create a flow to read from */
457   debugf("creating flow\n");
458   flow = AuCreateFlow(server, NULL);
459 
460 
461   /* create client and device elements to record with */
462   debugf("creating elements\n");
463 
464 
465   AuMakeElementImportDevice(&elements[0],
466 			    desiredSamplesPerSec,  /* XXX should use the actual sampling rate of device */
467 			    device,
468 			    AuUnlimitedSamples,
469 			    0, NULL);
470 
471   AuMakeElementExportClient(&elements[1],
472 			    0,
473 			    desiredSamplesPerSec,
474 			    AuFormatLinearSigned16LSB,  /* XXX this should be chosen based on the platform */
475 			    stereo ? 2 : 1,
476 			    AuTrue,
477 			    1000000,  /* was AuUnlimitedSamples */
478 			    1000, /* water mark: go ahead and send frequently! */
479 			    0, NULL);
480 
481 
482 
483   /* set up the flow with these elements */
484   AuSetElements(server,	flow,
485 		AuTrue,
486 		2, elements,
487 		NULL);
488 
489   /* start her up */
490   debugf("starting flow\n");
491   AuStartFlow(server, flow, NULL);
492   AuFlush(server);
493 
494 
495   /* initialize the space indication */
496   bytesAvail = 0;
497 
498 
499   /* arrange to be informed when events come in from the server */
500   aioEnable(AuServerConnectionNumber(server), NULL, AIO_EXT);
501   aioHandle(AuServerConnectionNumber(server), handleAudioEvents, AIO_W);
502 
503   return true;
504 }
505 
506 
sound_StopRecording(void)507 static sqInt sound_StopRecording(void)
508 {
509      return sound_Stop();
510 }
511 
512 
513 
sound_GetRecordingSampleRate(void)514 static double sound_GetRecordingSampleRate(void)
515 {
516   return sampleRate;
517 }
518 
519 
sound_RecordSamplesIntoAtLength(void * buf,sqInt startSliceIndex,sqInt bufferSizeInBytes)520 static sqInt sound_RecordSamplesIntoAtLength(void *buf, sqInt startSliceIndex,
521 				  sqInt bufferSizeInBytes)
522 {
523   int bytesToRead;
524   int sliceSize= (stereo ? 4 : 2);   /* a "slice" seems to be a "frame": one sample from each channel */
525 
526 
527   debugf("RecordSamplesIntoAtLength(buf=%d, startSliceIndex=%d, bufferSizeInBytes=%d\n",
528 	 buf, startSliceIndex, bufferSizeInBytes);
529 
530   /* sanity checks */
531   if (server==NULL || !recording) {
532     success(false);
533     return 0;
534   }
535 
536   if (bytesAvail <= 0)
537     return 0;
538 
539   /* figure out how much to read */
540   bytesToRead= bufferSizeInBytes - (startSliceIndex * sliceSize);
541   if (bytesToRead > bytesAvail)
542     bytesToRead= bytesAvail;
543 
544   debugf("reading %d bytes\n", bytesToRead);
545 
546   /* read it */
547   AuReadElement(server,
548 		flow,
549 		1,     /* element 1 is the client export */
550 		bytesToRead,
551 		(char *) (buf + startSliceIndex*sliceSize),
552 		NULL);
553 
554   bytesAvail -= bytesToRead;
555 
556   return bytesToRead/sliceSize;  /* return number of samples read (or slices?!) */
557 }
558 
559 
560 
561 
562 /* mixer settings */
sound_SetRecordLevel(sqInt level)563 static sqInt sound_SetRecordLevel(sqInt level)
564 {
565   return level;
566 }
567 
568 
569 
sound_Volume(double * left,double * right)570 static void sound_Volume(double *left, double *right)
571 {
572   return;
573 }
574 
575 
sound_SetVolume(double left,double right)576 static void sound_SetVolume(double left, double right)
577 {
578   return;
579 }
580 
sound_SetSwitch(sqInt id,sqInt captureFlag,sqInt parameter)581 static sqInt sound_SetSwitch(sqInt id, sqInt captureFlag, sqInt parameter)
582 {
583   return -1;
584 }
585 
sound_GetSwitch(sqInt id,sqInt captureFlag,sqInt channel)586 static sqInt sound_GetSwitch(sqInt id, sqInt captureFlag, sqInt channel)
587 {
588   return -1;
589 }
590 
sound_SetDevice(sqInt id,char * arg)591 static sqInt sound_SetDevice(sqInt id, char *arg)
592 {
593   return -1;
594 }
595 
596 #include "SqSound.h"
597 
598 SqSoundDefine(NAS);
599 
600 
601 #include "SqModule.h"
602 
sound_parseEnvironment(void)603 static void  sound_parseEnvironment(void) {}
604 
sound_parseArgument(int argc,char ** argv)605 static int   sound_parseArgument(int argc, char **argv)
606 {
607   if (!strcmp(argv[0], "-nas")) return 1;
608   return 0;
609 }
610 
sound_printUsage(void)611 static void  sound_printUsage(void) {}
sound_printUsageNotes(void)612 static void  sound_printUsageNotes(void) {}
sound_makeInterface(void)613 static void *sound_makeInterface(void) { return &sound_NAS_itf; }
614 
615 SqModuleDefine(sound, NAS);
616