Skip to content

Commit

Permalink
finish AU recording implementation; cleanups, more API
Browse files Browse the repository at this point in the history
git-svn-id: svn://svn.rforge.net/audio/trunk@11 c7782a61-6e1a-441d-a674-af8e9783a5cd
  • Loading branch information
s-u committed Sep 8, 2008
1 parent d181f97 commit 1481cd6
Show file tree
Hide file tree
Showing 5 changed files with 339 additions and 232 deletions.
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
export(play, play.default, play.Sample, pause, resume, rewind, record, load.audio.driver)
export(load.wave, save.wave)
S3method(print, audioInstance)
S3method(print, audioSample)
exportPattern(".*\\.audioInstance")
exportPattern(".*\\.audioSample")
36 changes: 35 additions & 1 deletion R/api.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,22 @@ play <- function(x, ...) UseMethod("play")
pause <- function(x, ...) UseMethod("pause")
resume <- function(x, ...) UseMethod("resume")
rewind <- function(x, ...) UseMethod("rewind")
record <- function(x, ...) stop("recording is not yet supported")

record <- function(where, rate, channels) {
if (missing(rate)) {
rate <- attr(where, "rate", TRUE)
if (is.null(rate)) rate <- 44100
}
if (missing(channels))
channels <- if (is.null(dim(where))) 2 else dim(where)[1]
channels <- as.integer(channels)
if (length(channels) != 1 || (channels != 1 && channels != 2))
stop("channels must be 1 (mono) or 2 (stereo)")
if (length(where) == 1) where <- if (channels == 2) matrix(NA_real_, 2, where) else rep(NA_real_, where)
a <- .Call("audio_recorder", where, as.double(rate), as.integer(channels), PACKAGE="audio")
.Call("audio_start", a, PACKAGE="audio")
invisible(a)
}

pause.audioInstance <- function(x, ...)
invisible(.Call("audio_pause", x, PACKAGE="audio"))
Expand All @@ -24,3 +39,22 @@ play.default <- function(x, rate=44100, ...) {

play.Sample <- function(x, ...) play(x$sound, x$rate)

play.audioSample <- function(x, rate, ...) {
if (missing(rate)) rate <- attr(x, "rate", TRUE)
play.default(x, rate, ...)
}

`[.audioSample` <- function(x, ..., drop = FALSE) {
y <- NextMethod("[")
attr(y, "rate") <- attr(x, "rate", TRUE)
attr(y, "bits") <- attr(x, "bits", TRUE)
class(y) <- class(x)
y
}

play.audioInstance <- function(x, ...) stop("you cannot play an audio instance - try play(a$data) if a is a recorded instance")

`$.audioInstance` <- function(x, name) if (isTRUE(name == "data")) .Call("audio_instance_source", x) else NULL

`$.audioSample` <- function(x, name) attr(x, name)
`$<-.audioSample` <- function(x, name, value) .Primitive("attr<-")
9 changes: 9 additions & 0 deletions R/print.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,3 +4,12 @@ print.audioInstance <- function(x, ...) {
cat(info)
invisible(info)
}

print.audioSample <- function(x, ...) {
kind <- if (is.null(dim(x)) || dim(x)[1] != 2) 'mono' else 'stereo'
bits <- attr(x, "bits", TRUE)
bits <- if (is.null(bits)) '' else paste(", ", bits, "-bits", sep='')
cat("sample rate: ", attr(x,"rate"), "Hz, ", kind, bits, "\n", sep='')
attributes(x) <- NULL
print(x)
}
64 changes: 62 additions & 2 deletions src/au.c
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,11 @@ typedef struct au_instance {
AudioUnit outUnit;
AudioDeviceID inDev;
AudioStreamBasicDescription fmtOut, fmtIn;
#if defined(MAC_OS_X_VERSION_10_5) && (MAC_OS_X_VERSION_MIN_REQUIRED>=MAC_OS_X_VERSION_10_5)
AudioDeviceIOProcID inIOProcID;
#endif
float sample_rate;
double srFrac, srRun;
BOOL stereo, loop, done;
unsigned int position, length;
} au_instance_t;
Expand Down Expand Up @@ -152,14 +156,39 @@ static au_instance_t *audiounits_create_player(SEXP source, float rate, int flag
return ap;
}

static int audiounits_pause(void *usr);

static OSStatus inputRenderProc(AudioDeviceID inDevice,
const AudioTimeStamp*inNow,
const AudioBufferList*inInputData,
const AudioTimeStamp*inInputTime,
AudioBufferList*outOutputData,
const AudioTimeStamp*inOutputTime,
void*inClientData) {
printf("inputRenderProc, (bufs=%d, buf[0].chs=%d), buf=%p, size=%d\n", inInputData->mNumberBuffers, inInputData->mBuffers[0].mNumberChannels, inInputData->mBuffers[0].mData, inInputData->mBuffers[0].mDataByteSize);
float *s = (float*) inInputData->mBuffers[0].mData;
unsigned int len = inInputData->mBuffers[0].mDataByteSize / sizeof(float), i = 0, ichs = inInputData->mBuffers[0].mNumberChannels;
au_instance_t *ap = (au_instance_t*) inClientData;
/* Rprintf("inputRenderProc, (bufs=%d, buf[0].chs=%d), buf=%p, size=%d [%d samples]\n", inInputData->mNumberBuffers, inInputData->mBuffers[0].mNumberChannels, inInputData->mBuffers[0].mData, inInputData->mBuffers[0].mDataByteSize, len); */
if (TYPEOF(ap->source) == REALSXP) {
double *d = REAL(ap->source), srr = ap->srRun, srf = ap->srFrac;
unsigned int chs = ap->stereo ? 2 : 1;
/* FIXME: we're assuming that channels can only be 1 or 2 */
while (ap->position < ap->length && i < len) {
srr += srf;
if (srr >= 1.0) {
if (ichs > chs) d[ap->position++] = (s[i] + s[i + 1]) / 2;
else {
if (ichs < chs) d[ap->position++] = s[i];
d[ap->position++] = s[i];
}
srr -= 1.0;
};
i++;
}
ap->srRun = srr;
}
/* pause the unit when the recording is complete */
if (ap->position >= ap->length) audiounits_pause(ap);
return 0;
}

Expand Down Expand Up @@ -189,22 +218,43 @@ static au_instance_t *audiounits_create_recorder(SEXP source, float rate, int ch
Rf_error("unable to retrieve audio input format (%08x)", err);
}

printf(" recording - rate: %f, chs: %d, fpp: %d, bpp: %d, bpf: %d, flags: %x\n", ap->fmtIn.mSampleRate, ap->fmtIn.mChannelsPerFrame, ap->fmtIn.mFramesPerPacket, ap->fmtIn.mBytesPerPacket, ap->fmtIn.mBytesPerFrame, ap->fmtIn.mFormatFlags);
/* Rprintf(" recording format: %f, chs: %d, fpp: %d, bpp: %d, bpf: %d, flags: %x\n", ap->fmtIn.mSampleRate, ap->fmtIn.mChannelsPerFrame, ap->fmtIn.mFramesPerPacket, ap->fmtIn.mBytesPerPacket, ap->fmtIn.mBytesPerFrame, ap->fmtIn.mFormatFlags); */

ap->srFrac = 1.0;
if (ap->fmtIn.mSampleRate != ap->sample_rate) ap->srFrac = ap->sample_rate / ap->fmtIn.mSampleRate;
ap->srRun = 0.0;

#if defined(MAC_OS_X_VERSION_10_5) && (MAC_OS_X_VERSION_MIN_REQUIRED>=MAC_OS_X_VERSION_10_5)
err = AudioDeviceCreateIOProcID(ap->inDev, inputRenderProc, ap, &ap->inIOProcID );
#else
err = AudioDeviceAddIOProc(ap->inDev, inputRenderProc, ap);
#endif
if (err) {
free(ap);
Rf_error("unable to register recording callback (%08x)", err);
}
R_PreserveObject(ap->source);
Rf_setAttrib(ap->source, Rf_install("rate"), Rf_ScalarInteger(rate)); /* we adjust the rate */
Rf_setAttrib(ap->source, Rf_install("bits"), Rf_ScalarInteger(16)); /* we say it's 16 because we don't know - float is always 32-bit */
Rf_setAttrib(ap->source, Rf_install("class"), Rf_mkString("audioSample"));
if (ap->stereo) {
SEXP dim = Rf_allocVector(INTSXP, 2);
INTEGER(dim)[0] = 2;
INTEGER(dim)[1] = LENGTH(ap->source) / 2;
Rf_setAttrib(ap->source, R_DimSymbol, dim);
}
return ap;
}

static int audiounits_start(void *usr) {
au_instance_t *ap = (au_instance_t*) usr;
OSStatus err;
if (ap->kind == AI_RECORDER) {
#if defined(MAC_OS_X_VERSION_10_5) && (MAC_OS_X_VERSION_MIN_REQUIRED>=MAC_OS_X_VERSION_10_5)
err = AudioDeviceStart(ap->inDev, ap->inIOProcID);
#else
err = AudioDeviceStart(ap->inDev, inputRenderProc);
#endif
if (err) Rf_error("unable to start recording (%08x)", err);
} else {
AURenderCallbackStruct renderCallback = { outputRenderProc, usr };
Expand All @@ -225,8 +275,13 @@ static int audiounits_start(void *usr) {

static int audiounits_pause(void *usr) {
au_instance_t *p = (au_instance_t*) usr;
#if defined(MAC_OS_X_VERSION_10_5) && (MAC_OS_X_VERSION_MIN_REQUIRED>=MAC_OS_X_VERSION_10_5)
if (p->kind == AI_RECORDER)
return AudioDeviceStop(p->inDev, p->inIOProcID) ? 0 : 1;
#else
if (p->kind == AI_RECORDER)
return AudioDeviceStop(p->inDev, inputRenderProc) ? 0 : 1;
#endif
return AudioOutputUnitStop(p->outUnit) ? 0 : 1;
}

Expand All @@ -244,14 +299,19 @@ static int audiounits_resume(void *usr) {
static int audiounits_close(void *usr) {
au_instance_t *p = (au_instance_t*) usr;
p->done = YES;
Rprintf(" closing audiounit %p\n", usr);
if (p->outUnit) {
AudioOutputUnitStop(p->outUnit);
AudioUnitUninitialize(p->outUnit);
CloseComponent(p->outUnit);
p->outUnit = 0;
}
if (p->inDev) {
#if defined(MAC_OS_X_VERSION_10_5) && (MAC_OS_X_VERSION_MIN_REQUIRED>=MAC_OS_X_VERSION_10_5)
AudioDeviceDestroyIOProcID(p->inDev, p->inIOProcID);
#else
AudioDeviceRemoveIOProc(p->inDev, inputRenderProc);
#endif
p->inDev = 0;
}
return 1;
Expand Down
Loading

0 comments on commit 1481cd6

Please sign in to comment.