Skip to content

Commit

Permalink
low-level aout functionality in module AudioPanning (with no integrat…
Browse files Browse the repository at this point in the history
…ion into worklet compilation)
  • Loading branch information
dktr0 committed Nov 19, 2024
1 parent 87ddf62 commit 67906d8
Show file tree
Hide file tree
Showing 4 changed files with 121 additions and 108 deletions.
198 changes: 99 additions & 99 deletions punctual.js

Large diffs are not rendered by default.

24 changes: 18 additions & 6 deletions src/AudioPanning.purs
Original file line number Diff line number Diff line change
@@ -1,31 +1,43 @@
module AudioPanning where

import Prelude ((>),($),pure,otherwise,(*),(<>),(/),(>>=),bind,(-),(+),(<=),map,(==),(<$>))
import Data.Maybe (Maybe(..))
import Data.Int (toNumber)
import Data.Number (pi,cos)
import Data.Ord (abs)
import Data.Either (Either(..))
import Data.List.NonEmpty (head, length, zipWith)
import Data.List (take)
import Data.List.NonEmpty (head, length, zipWith, NonEmptyList, fromList, toList)
import Data.Unfoldable1 (iterateN)
import Data.Unfoldable (replicate)
import Data.Traversable (traverse,sequence)
import Data.Tuple (Tuple(..))

import W (W,Sample,Frame,assign,product,sumChannels)
import W (W,Sample,Frame,assign,product,sumChannels,zero)
import W as W
import Matrix (fromNonEmptyList,flatten)

splay :: Int -> Frame -> W Frame
splay :: Int -> Frame -> W (NonEmptyList Sample)
splay nOutputChnls xs
| nOutputChnls <= 1 = pure <$> W.sum xs
| length (flatten xs) == 1 = pan nOutputChnls (Left 0.5) (head $ flatten xs)
| length (flatten xs) == 1 = flatten <$> pan nOutputChnls (Left 0.5) (head $ flatten xs)
| otherwise = do
let xs' = flatten xs
let nInputChnls = length xs'
let stepSize = 1.0 / toNumber (nInputChnls - 1)
let inputPositions = map Left $ iterateN nInputChnls (_ + stepSize) 0.0
xss <- sequence $ zipWith (pan nOutputChnls) inputPositions xs' -- :: NonEmptyList Frame -- one Frame per input, each Frame has nOutputChnls Samples
sumChannels xss

flatten <$> sumChannels xss

aout :: Int -> Int -> Int -> Frame -> W (NonEmptyList Sample)
aout totalOutputChnls nOutputChnls channelOffset xs = do
let a = replicate channelOffset zero -- :: List Sample
b <- toList <$> splay nOutputChnls xs -- :: List Sample
let c = replicate (totalOutputChnls - channelOffset - nOutputChnls) zero -- :: List Sample
case fromList (take totalOutputChnls $ a <> b <> c) of
Just x -> pure x
Nothing -> pure $ pure zero -- only possible with meaningless input (totalOutputChnls or nOutputChnls < 1)

pan :: Int -> Sample -> Sample -> W Frame
pan nOutputChnls pos i
| nOutputChnls <= 1 = pure $ pure i
Expand Down
4 changes: 1 addition & 3 deletions src/AudioWorklet.purs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,6 @@ import Signal (Signal)
import WebAudio (WebAudioContext,WebAudioNode)
import W
import AudioPanning (splay)
import Matrix (flatten)

type AudioWorklet = {
name :: String,
Expand Down Expand Up @@ -51,8 +50,7 @@ foreign import setWorkletParamValue :: WebAudioNode -> String -> Number -> Effec
generateWorkletCode :: Signal -> String -> Number -> Number -> String
generateWorkletCode s name fInStart fInDur = prefix <> classHeader <> getParameterDescriptors <> constructor <> innerLoopPrefix <> fadeCalculations <> wState.code <> outputs <> restOfClass <> registerProcessor
where
Tuple frameMulti wState = runW $ signalToFrame s >>= splay 2
frame = flatten frameMulti
Tuple frame wState = runW $ signalToFrame s >>= splay 2
prefix = """'use strict';
function clamp(min,max,x) { return Math.max(Math.min(max,x),min); }
Expand Down
3 changes: 3 additions & 0 deletions src/W.purs
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,9 @@ showSample :: Sample -> String
showSample (Left x) = Number.showNumber x
showSample (Right x) = x

zero :: Sample
zero = Left 0.0

assign :: String -> W Sample
assign x = do
f <- allocateFloat
Expand Down

0 comments on commit 67906d8

Please sign in to comment.