Skip to content

Commit

Permalink
sweptsine
Browse files Browse the repository at this point in the history
  • Loading branch information
edwbaker committed Jul 17, 2020
1 parent 5f813ba commit cb33b9d
Show file tree
Hide file tree
Showing 7 changed files with 106 additions and 11 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Expand Up @@ -15,7 +15,7 @@ Imports:
License: GPL-3
Encoding: UTF-8
LazyData: true
RoxygenNote: 7.0.2
RoxygenNote: 7.1.0
Language: en-GB
Suggests:
testthat,
Expand Down
2 changes: 2 additions & 0 deletions NAMESPACE
Expand Up @@ -44,6 +44,7 @@ export(soundSpeed_cramer1993)
export(specStats)
export(ste)
export(subtractSpectra)
export(sweptsine)
export(tSamples)
export(validateIsWave)
export(windowing)
Expand All @@ -62,6 +63,7 @@ importFrom(graphics,title)
importFrom(jsonlite,fromJSON)
importFrom(seewave,duration)
importFrom(seewave,meanspec)
importFrom(seewave,savewav)
importFrom(seewave,sfm)
importFrom(seewave,sh)
importFrom(stats,approx)
Expand Down
24 changes: 16 additions & 8 deletions R/googleSpeech.R
Expand Up @@ -6,7 +6,7 @@
#' @param bucket Storage bucket on Google Cloud for larger files
#' @param ... Additional arguments to pass to gl_speech()
#' @importFrom tuneR readWave
#' @importFrom seewave duration
#' @importFrom seewave duration savewav
#' @export
#' @return A gs_transcribe object containing details of the transcription
#' @examples
Expand All @@ -16,10 +16,17 @@
#'
gs_transcribe <- function(filename, bucket=NULL,...) {
if (package.installed("googleCloudStorageR") & package.installed("googleLanguageR")) {
max_d <- 3 #Max duration for objects not in Cloud Storage
max_d <- 3000 #Max duration for objects not in Cloud Storage
max_samp_rate = 48000
wave <- readWave(filename)
if (wave@samp.rate > max_samp_rate) {
print("Downsampling to 48kHz")
savewav(wave, f=max_samp_rate, filename="temp.wav", extensible = FALSE)
filename <- "temp.wav"
wave@samp.rate <- max_samp_rate
}
if (duration(wave) < max_d) {
return(gs_transcribe_execute(filename,...))
return(gs_transcribe_execute(filename, ...))
} else {
#Upload
upload_try <- googleCloudStorageR::gcs_upload(filename, bucket=bucket, name="temp")
Expand All @@ -31,16 +38,17 @@ gs_transcribe <- function(filename, bucket=NULL,...) {
}
}

gs_transcribe_execute <- function(object,...) {
gs_transcribe_execute <- function(object, ...) {
object
async <- googleLanguageR::gl_speech(object, asynch=TRUE,...)
result <- googleLanguageR::gl_speech_op(async)
async <- googleLanguageR::gl_speech_op(async)
tries <- 1
while (is.null(result$transcript)) {
while (TRUE) {
Sys.sleep(exponential_backoff(tries))
result <- googleLanguageR::gl_speech_op(async)
async <- googleLanguageR::gl_speech_op(async)
tries <- tries + 1
}
return(gs_preprocess_transcript(result))
return(gs_preprocess_transcript(async))
}

gs_preprocess_transcript <- function(transcript, offset=0) {
Expand Down
40 changes: 40 additions & 0 deletions R/sweptsine.R
@@ -0,0 +1,40 @@
#' Generate a frequency-swept sine wave
#'
#' Generates a frequency swept sine wave and returns it as a Wave object or vector.
#'
#' @param f0 Start frequency
#' @param f1 End frequency
#' @param sweep.time Duration of swept wave
#' @param A Amplitude of wave
#' @param samp.rate Sample rate of swept wave
#' @param output "wave" for a Wave object, or "vector"
#' @param ... Additional arguments to pass to data2Wave
#' @export
#' @return A swept wave object of the type specified in output.
#' @examples
#' sweptsine()
#'
sweptsine <- function(f0=100, f1=2500, sweep.time=1, A=1, samp.rate=44100, output="wave", ...) {
f <- f0
phi <- 0 #Phase accumulator
delta <- 2 * pi * f / samp.rate
f_delta <- (f1 - f0) / (samp.rate * sweep.time)

w <- vector(mode="numeric", length=samp.rate*sweep.time)

i <- 1
while (i < samp.rate*sweep.time) {
w[i] <- A * sin(phi)
phi <- phi + delta
f <- f + f_delta
delta <- 2 * pi * f / samp.rate
i <- i+1
}
if (output == "vector") {
return(w)
}
if (output == "wave") {
return(data2Wave(w, samp.rate=samp.rate, ...))
}

}
4 changes: 3 additions & 1 deletion man/STP.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 3 additions & 1 deletion man/sheepFrequencyStats.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

41 changes: 41 additions & 0 deletions man/sweptsine.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

0 comments on commit cb33b9d

Please sign in to comment.