Skip to content

Commit

Permalink
setOutputChannelCount pathway completed
Browse files Browse the repository at this point in the history
  • Loading branch information
dktr0 committed Nov 20, 2024
1 parent 67906d8 commit 02f5980
Show file tree
Hide file tree
Showing 9 changed files with 249 additions and 214 deletions.
5 changes: 5 additions & 0 deletions exolang.js
Original file line number Diff line number Diff line change
Expand Up @@ -44,3 +44,8 @@ Punctual.prototype.setAudioOutput = function(webAudioNode) {
Punctual.prototype.setBrightness = function(b) {
return P.setBrightness(this.punctual)(b)();
}

Punctual.prototype.setOutputChannelCount = function(n) {
console.log("punctual setOutputChannelCount " + n);
return P.setOutputChannelCount(this.punctual)(n)();
}
374 changes: 187 additions & 187 deletions punctual.js

Large diffs are not rendered by default.

2 changes: 1 addition & 1 deletion src/AST.purs
Original file line number Diff line number Diff line change
Expand Up @@ -258,7 +258,7 @@ ifThenElse = do
pure $ IfThenElse p i t e

output :: P Expression
output = choice $ map reservedName ["audio","blend","rgba","add","mul","rgb"]
output = choice $ map reservedName ["audio","aout","blend","rgba","add","mul","rgb"]



Expand Down
19 changes: 9 additions & 10 deletions src/AudioWorklet.purs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ import Data.Foldable (fold)
import Signal (Signal)
import WebAudio (WebAudioContext,WebAudioNode)
import W
import AudioPanning (splay)
import AudioPanning (aout)

type AudioWorklet = {
name :: String,
Expand All @@ -27,10 +27,10 @@ type AudioWorklet' = {
audioWorkletNode :: Nullable WebAudioNode
}

runWorklet :: WebAudioContext -> Nullable WebAudioNode -> WebAudioNode -> String -> Signal -> Number -> Number -> Effect AudioWorklet
runWorklet ctx ain aout name signal fInStart fInDur = do
let code = generateWorkletCode signal name fInStart fInDur
audioWorklet' <- _runWorklet ctx ain aout name code 2
runWorklet :: WebAudioContext -> Nullable WebAudioNode -> WebAudioNode -> String -> Signal -> Int -> Int -> Number -> Number -> Effect AudioWorklet
runWorklet ctx ain aout name signal nOutputChnls channelOffset fInStart fInDur = do
let code = generateWorkletCode signal nOutputChnls channelOffset name fInStart fInDur
audioWorklet' <- _runWorklet ctx ain aout name code nOutputChnls
pure { name, signal, code, audioWorklet' }

foreign import _runWorklet :: WebAudioContext -> Nullable WebAudioNode -> WebAudioNode -> String -> String -> Int -> Effect AudioWorklet'
Expand All @@ -46,11 +46,10 @@ stopWorklet w fOutStart fOutDur = do

foreign import setWorkletParamValue :: WebAudioNode -> String -> Number -> Effect Unit


generateWorkletCode :: Signal -> String -> Number -> Number -> String
generateWorkletCode s name fInStart fInDur = prefix <> classHeader <> getParameterDescriptors <> constructor <> innerLoopPrefix <> fadeCalculations <> wState.code <> outputs <> restOfClass <> registerProcessor
generateWorkletCode :: Signal -> Int -> Int -> String -> Number -> Number -> String
generateWorkletCode s nOutputChnls channelOffset name fInStart fInDur = prefix <> classHeader <> getParameterDescriptors <> constructor <> innerLoopPrefix <> fadeCalculations <> wState.code <> outputs <> restOfClass <> registerProcessor
where
Tuple frame wState = runW $ signalToFrame s >>= splay 2
Tuple frame wState = runW $ signalToFrame s >>= aout nOutputChnls nOutputChnls channelOffset
prefix = """'use strict';
function clamp(min,max,x) { return Math.max(Math.min(max,x),min); }
Expand Down Expand Up @@ -130,7 +129,7 @@ const tri = this.tri;
"""
fadeCalculations = "const fIn = clamp(0,1,(t-" <> show fInStart <> ")/" <> show fInDur <> ");\nconst fade = Math.min(fIn,fOut);\n"
outputIndices = range 0 (length frame - 1)
outputF i x = "output[" <> show i <> "][n] = " <> showSample x <> "*fade;\n"
outputF i x = "if(output[" <> show i <> "]!=null){output[" <> show i <> "][n] = " <> showSample x <> "*fade};\n"
outputs = fold $ zipWith outputF outputIndices frame
restOfClass = """}
this.framesOut += blockSize;
Expand Down
18 changes: 10 additions & 8 deletions src/AudioZone.purs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module AudioZone where

import Prelude (Unit,map,bind,(/=),pure,($),discard,otherwise,(+),(<$>),(<>),show,(==),unit,max,(>=),(-),(<<<),(/))
import Prelude (Unit,map,bind,pure,($),discard,otherwise,(+),(<$>),(<>),show,(==),unit,max,(>=),(-),(<<<),(/))
import Data.Maybe (Maybe(..))
import Data.List (List(..),zipWith,length)
import Effect (Effect)
Expand All @@ -15,11 +15,11 @@ import Data.Newtype (unwrap)
import Data.Nullable (null,notNull)
import Effect.Class.Console (log)

import SharedResources (SharedResources, activateAudioInput)
import SharedResources (SharedResources, activateAudioInput, getOutputChannelCount)
import Program (Program)
import AudioWorklet (AudioWorklet,runWorklet,stopWorklet)
import Action (Action,actionTimesAsAudioTime,actionHasAudioInput)
import Output (Output(..))
import Output (isAudioOutput,audioOutputChannels,audioOutputOffset)
import WebAudio (resumeWebAudioContext,currentTime)

type AudioZone = {
Expand All @@ -40,10 +40,9 @@ newAudioZone sharedResources p = do

justAudioActions :: Maybe Action -> Maybe Action
justAudioActions Nothing = Nothing
justAudioActions (Just x)
| x.output /= Audio = Nothing
| otherwise = Just x

justAudioActions (Just x)
| isAudioOutput x.output = Just x
| otherwise = Nothing

addOrRemoveWorklet :: SharedResources -> DateTime -> Number -> Maybe AudioWorklet -> Maybe Action -> Effect (Maybe AudioWorklet)
addOrRemoveWorklet _ _ _ Nothing Nothing = pure Nothing
Expand Down Expand Up @@ -77,7 +76,10 @@ addWorklet sharedResources action t1 t2 = do
false -> do
log "worklet does not have audio input"
pure null
runWorklet sharedResources.webAudioContext nAin sharedResources.internalAudioOutputNode ("W" <> show i) action.signal t1 (t2-t1)
maxChnls <- getOutputChannelCount sharedResources
let nOutputChnls = audioOutputChannels maxChnls action.output
let channelOffset = audioOutputOffset action.output
runWorklet sharedResources.webAudioContext nAin sharedResources.internalAudioOutputNode ("W" <> show i) action.signal nOutputChnls channelOffset t1 (t2-t1)

-- to convert audio to POSIX, add clockdiff; to convert POSIX to audio, subtract clockdiff
calculateClockDiff :: SharedResources -> Effect Number
Expand Down
2 changes: 2 additions & 0 deletions src/Main.purs
Original file line number Diff line number Diff line change
Expand Up @@ -178,6 +178,8 @@ setAudioOutput punctual n = SharedResources.setAudioOutput punctual.sharedResour
setBrightness :: Punctual -> Number -> Effect Unit
setBrightness punctual b = SharedResources.setBrightness punctual.sharedResources b

setOutputChannelCount :: Punctual -> Int -> Effect Unit
setOutputChannelCount punctual n = SharedResources.setOutputChannelCount punctual.sharedResources n

-- below this line are functions that are not directly part of the exolang API

Expand Down
17 changes: 15 additions & 2 deletions src/Output.purs
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,8 @@ import Data.Generic.Rep (class Generic)
import Data.Show.Generic (genericShow)

data Output =
Audio |
AOut Int Int | -- first argument is number of channels, second argument is channel offset
Audio | -- splayed over all available outputs, which might be different in number in different Estuary clients (for example)
AOut Int Int | -- first argument is channel offset second argument is number of channels (stereo is a synonym for AOut 0 2)
Blend |
RGBA |
Add |
Expand All @@ -18,3 +18,16 @@ derive instance Generic Output _
instance Show Output where
show = genericShow

isAudioOutput :: Output -> Boolean
isAudioOutput Audio = true
isAudioOutput (AOut _ _) = true
isAudioOutput _ = false

audioOutputChannels :: Int -> Output -> Int
audioOutputChannels maxChnls Audio = maxChnls
audioOutputChannels _ (AOut _ n) = n
audioOutputChannels _ _ = 0

audioOutputOffset :: Output -> Int
audioOutputOffset (AOut o _) = o
audioOutputOffset _ = 0
16 changes: 14 additions & 2 deletions src/SharedResources.purs
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,8 @@ type SharedResources = {
inputAnalyser :: AudioAnalyser,
outputAnalyser :: AudioAnalyser,
audioWorkletCount :: Ref Int,
brightness :: Ref Number
brightness :: Ref Number,
outputChannelCount :: Ref Int
}

newSharedResources :: Maybe WebAudioContext -> Effect SharedResources
Expand All @@ -60,6 +61,7 @@ newSharedResources mWebAudioContext = do
outputAnalyser <- newAudioAnalyser webAudioContext internalAudioOutputNode
audioWorkletCount <- new 0
brightness <- new 1.0
outputChannelCount <- new 2
pure {
tempo,
mWebcamElementRef,
Expand All @@ -75,7 +77,8 @@ newSharedResources mWebAudioContext = do
inputAnalyser,
outputAnalyser,
audioWorkletCount,
brightness
brightness,
outputChannelCount
}

updateAudioInputAndAnalysers :: SharedResources -> forall r. { ain::Disj Boolean, ifft::Disj Boolean, ilo::Disj Boolean, imid::Disj Boolean, ihi::Disj Boolean, fft::Disj Boolean, lo::Disj Boolean, mid::Disj Boolean, hi::Disj Boolean | r } -> Effect Unit
Expand Down Expand Up @@ -235,3 +238,12 @@ setBrightness sr b = write b sr.brightness

getBrightness :: SharedResources -> Effect Number
getBrightness sr = read sr.brightness


-- number of audio output channels

setOutputChannelCount :: SharedResources -> Int -> Effect Unit
setOutputChannelCount sr b = write b sr.outputChannelCount

getOutputChannelCount :: SharedResources -> Effect Int
getOutputChannelCount sr = read sr.outputChannelCount
10 changes: 6 additions & 4 deletions src/TokenParser.purs
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,8 @@ functionsWithNoArgumentsDef :: Array String
functionsWithNoArgumentsDef = [
"pi","mic","audioin","cps","time","beat","etime","ebeat","rnd",
"fx","fy","fxy","px","py","pxy","frt","fr","ft","aspect",
"lo","mid","hi","ilo","imid","ihi","fft","ifft","fb","cam"
"lo","mid","hi","ilo","imid","ihi","fft","ifft","fb","cam",
"audio","blend","rgba","add","mul","rgb"
]

functionsWithArgumentsDef :: Array String
Expand Down Expand Up @@ -63,13 +64,14 @@ functionsWithArgumentsDef = [
"rep",
"img","vid",
"mix","mixp",
"import"
"import",
"aout"
]

otherReservedNamesDef :: Array String
otherReservedNamesDef = [
"if","then","else",
"audio","aout","blend","rgba","add","mul","rgb"
"if","then","else"
-- "audio","aout","blend","rgba","add","mul","rgb"
]

reservedNamesDef :: Array String
Expand Down

0 comments on commit 02f5980

Please sign in to comment.