Skip to content

Commit

Permalink
added spr and sprp
Browse files Browse the repository at this point in the history
  • Loading branch information
dktr0 committed Nov 15, 2024
1 parent 3a41d1b commit 252269c
Show file tree
Hide file tree
Showing 11 changed files with 209 additions and 190 deletions.
2 changes: 1 addition & 1 deletion CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ Other changes relative to 0.4.x

-available outputs are 'audio' 'blend' 'add' 'rgba' 'rgb' (previously existing outputs like 'hsv' 'red' 'splay' 'alpha' etc have been removed). Visual outputs behave in a layer fashion similar to image editing software. Earlier statements in a Punctual program with visual outputs are like lower/earlier layers in image editing. When a later/newer layer has an alpha component (blend or rgba), that alpha value is used to determine how much of the combined result comes from the previous layer (alpha = 0) versus the new/current layer (alpha = 1). With "add" (which is RGB) the RGB of the previous and new layer are added together, and the result has an alpha of 1 everywhere. With "rgb", the result is simply the provided rgb data with an alpha of 1 everywhere.

-'step' has been replaced with 'seq'
-'step' has been re-implemented as 'spr' (for spread), with support for multi-channel results and a pairwise variant (sprp). 'seq' has also been introduced - while spr/sprp require a second, bipolar argument, seq is instead driven directly by the prevailing metre.

-introduction of 'slow' 'fast' 'early' and 'late' for time-shifting/stretching of arbitrary punctual expressions

Expand Down
4 changes: 3 additions & 1 deletion REFERENCE.md
Original file line number Diff line number Diff line change
Expand Up @@ -164,7 +164,9 @@ bipolar [graph] -- input is rescaled as if input range was unipolar (0,1) and ou

[centre] +- [offsetRatio] [input] -- bipolar (-1,1) input rescaled to range centre +- (offsetRatio * centre), e.g. a +- 0.5 ranges from 0.5a to 1.5a (combinatorial, for pairwise use +-:)

step [graph,graph,graph,...] [graph] -- given a list of graphs and a second, final, "modulating" graph, output the value of a selected graph from the list according to the second argument (drive with lfsaw to produce a simple step sequencer-like behaviour).
spr [graph,graph,graph,...] [graph] -- given a list of graphs and a second, final, "modulating" graph, output the value of a selected graph from the list according to the second argument (drive with lfsaw to produce a simple step sequencer-like behaviour).

seq [graph] -- given a list of graphs, outputs the value of the selected graph in such a way that it's spread over a single cycle of the metre

mono [graph] -- takes multi-channel graphs down to a single channel by summing/mixing

Expand Down
355 changes: 178 additions & 177 deletions punctual.js

Large diffs are not rendered by default.

2 changes: 1 addition & 1 deletion src/AudioWorklet.purs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ import Data.Tuple (Tuple(..))
import Data.List.NonEmpty (length,zipWith)
import Data.Unfoldable1 (range)
import Data.Foldable (fold)
import Effect.Class.Console (log)
-- import Effect.Class.Console (log)

import Signal (Signal)
import WebAudio (WebAudioContext,WebAudioNode)
Expand Down
2 changes: 1 addition & 1 deletion src/AudioZone.purs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ import Data.Newtype (unwrap)
import Data.Nullable (null,notNull)
import Effect.Class.Console (log)

import SharedResources (SharedResources,activateAudioInput,disactivateAudioInput)
import SharedResources (SharedResources, activateAudioInput)
import Program (Program)
import AudioWorklet (AudioWorklet,runWorklet,stopWorklet)
import Action (Action,actionTimesAsAudioTime,actionHasAudioInput)
Expand Down
5 changes: 5 additions & 0 deletions src/FragmentShader.purs
Original file line number Diff line number Diff line change
Expand Up @@ -428,6 +428,11 @@ signalToExprs (Mix Combinatorial x y a) = do
let f (Tuple xx yy) aa = mixFloat xx yy aa
traverse assign $ combine f Combinatorial xys a'

signalToExprs (Spr mm x y) = do
xs <- (signalToExprs x :: G (Matrix Float)) >>= semiFlatten >>> fromNonEmptyList >>> pure-- :: one-dimensional Matrix (NonEmptyList Float)
ys <- (signalToExprs y :: G (Matrix Float)) >>= map unipolar >>> pure -- :: Matrix Float
traverse assign $ mapRows castExprs $ combine (flip seq) mm xs ys

signalToExprs (Seq steps) = do
steps' <- semiFlatten <$> signalToExprs steps -- :: NonEmptyList (NonEmptyList Float)
b <- get >>= _.beat >>> fract >>> pure
Expand Down
2 changes: 2 additions & 0 deletions src/Parser.purs
Original file line number Diff line number Diff line change
Expand Up @@ -297,6 +297,8 @@ parseReserved p "ilines" = lift $ signalSignalSignal p $ ILines Combinatorial
parseReserved p "ilinesp" = lift $ signalSignalSignal p $ ILines Pairwise
parseReserved p "mesh" = lift $ signalSignalSignal p $ Mesh Combinatorial
parseReserved p "meshp" = lift $ signalSignalSignal p $ Mesh Pairwise
parseReserved p "spr" = lift $ signalSignalSignal p $ Spr Combinatorial
parseReserved p "sprp" = lift $ signalSignalSignal p $ Spr Pairwise
parseReserved p "seq" = pure $ signalSignal p Seq
parseReserved p "fit" = lift $ signalSignalSignal p fit
parseReserved p "iline" = lift $ signalSignalSignalSignal p $ ILine Combinatorial
Expand Down
16 changes: 10 additions & 6 deletions src/Signal.purs
Original file line number Diff line number Diff line change
@@ -1,19 +1,19 @@
module Signal where

import Prelude (class Eq, class Show, mempty, negate, ($), (<>), pure, (*), map, (+), max, (/), (-), (<=), otherwise, (==), show)
import Prelude (class Eq, class Show, map, max, mempty, negate, otherwise, pure, show, ($), (*), (+), (-), (/), (<=), (<>))
import Data.Generic.Rep (class Generic)
import Data.Show.Generic (genericShow)
-- import Data.Show.Generic (genericShow)
import Data.List (List(..),(:))
import Data.List.NonEmpty (NonEmptyList,length,toList,fromList)
import Data.Foldable (foldMap,intercalate,fold)
import Data.List.NonEmpty (fromList, length)
import Data.Foldable (fold, foldMap)
import Data.Unfoldable (replicate)
import Data.Set (Set,singleton)
import Data.Monoid.Disj (Disj)
import Data.Semigroup.Foldable (foldl1)
import Data.Maybe (Maybe(..))

import MultiMode
import Channels
import MultiMode (MultiMode(..))
import Channels (class Channels, channels)

data Signal =
Constant Number |
Expand Down Expand Up @@ -114,6 +114,7 @@ data Signal =
Lines MultiMode Signal Signal |
ILines MultiMode Signal Signal |
Mesh MultiMode Signal Signal |
Spr MultiMode Signal Signal |
Seq Signal |
Mix MultiMode Signal Signal Signal |
ILine MultiMode Signal Signal Signal |
Expand Down Expand Up @@ -279,6 +280,7 @@ showIndented i (Chain mm x y) = indent i <> "Chain " <> show mm <> "\n" <> showI
showIndented i (Lines mm x y) = indent i <> "Lines " <> show mm <> "\n" <> showIndented (i+1) x <> showIndented (i+1) y
showIndented i (ILines mm x y) = indent i <> "ILines " <> show mm <> "\n" <> showIndented (i+1) x <> showIndented (i+1) y
showIndented i (Mesh mm x y) = indent i <> "Mesh " <> show mm <> "\n" <> showIndented (i+1) x <> showIndented (i+1) y
showIndented i (Spr mm x y) = indent i <> "Spr " <> show mm <> "\n" <> showIndented (i+1) x <> showIndented (i+1) y
showIndented i (Seq x) = indent i <> "Seq\n" <> showIndented (i+1) x
showIndented i (Mix mm x y z) = indent i <> "Mix " <> show mm <> "\n" <> showIndented (i+1) x <> showIndented (i+1) y <> showIndented (i+1) z
showIndented i (ILine mm x y z) = indent i <> "ILine " <> show mm <> "\n" <> showIndented (i+1) x <> showIndented (i+1) y <> showIndented (i+1) z
Expand Down Expand Up @@ -541,6 +543,7 @@ subSignals (Chain _ x y) = x:y:Nil
subSignals (Lines _ x y) = x:y:Nil
subSignals (ILines _ x y) = x:y:Nil
subSignals (Mesh _ x y) = x:y:Nil
subSignals (Spr _ x y) = x:y:Nil
subSignals (Seq steps) = steps:Nil
subSignals (ILine _ x y z) = x:y:z:Nil
subSignals (Line _ x y z) = x:y:z:Nil
Expand Down Expand Up @@ -674,6 +677,7 @@ dimensions (Chain mm xy w) = binaryFunctionDimensions mm (chainChannels $ channe
dimensions (Lines mm x y) = binaryFunctionDimensions mm (nPer 1 4 $ channels x) (channels y)
dimensions (ILines mm x y) = binaryFunctionDimensions mm (nPer 1 4 $ channels x) (channels y)
dimensions (Mesh mm xy w) = binaryFunctionDimensions mm (meshChannels $ channels xy) (channels w)
dimensions (Spr mm x y) = binaryFunctionDimensions mm (channels y) (dimensions x).rows
dimensions (Seq x) = { rows: 1, columns: (dimensions x).rows }
dimensions (Mix mm x y z) = binaryFunctionDimensions mm (max (channels x) (channels y)) (channels z)
dimensions (ILine mm xy1 xy2 w) = binaryFunctionDimensions mm (binaryFunctionChannels mm (nPer 1 2 $ channels xy1) (nPer 1 2 $ channels xy2)) (channels w)
Expand Down
2 changes: 1 addition & 1 deletion src/TokenParser.purs
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,7 @@ functionsWithArgumentsDef = [
"chain","chainp","lines","linesp","ilines","ilinesp","mesh","meshp",
"zip",
"fit","min","max","minp","maxp",
"clip","clipp","between","betweenp","smoothstep","smoothstepp","gate","gatep","when","seq",
"clip","clipp","between","betweenp","smoothstep","smoothstepp","gate","gatep","when","spr","sprp","seq",
"setfx","setfy","setfxy","zoom","zoomxy","zoomx","zoomy","move","tile","tilexy","tilex","tiley","spin",
"early","late","slow","fast",
"lpf","lpfp","hpf","hpfp","bpf","bpfp","delay",
Expand Down
2 changes: 1 addition & 1 deletion src/Value.purs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ import Data.Map (Map)
import Signal (Signal(..))
import Action (Action,signalToAction)
import Output (Output)
import MultiMode (MultiMode(..))
import MultiMode (MultiMode)

type Library = Map.Map String Value

Expand Down
7 changes: 6 additions & 1 deletion src/W.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ module W where

-- A monad and associated functions for generating the code of a WebAudio audio worklet.

import Prelude (Unit, bind, discard, map, pure, show, ($), (*), (+), (-), (/), (/=), (<), (<$>), (<<<), (<=), (<>), (==), (>), (>=), (>>=), negate)
import Prelude (Unit, bind, discard, map, pure, show, ($), (*), (+), (-), (/), (/=), (<), (<$>), (<<<), (<=), (<>), (==), (>), (>=), (>>=), negate, (>>>))
import Prelude as Prelude
import Control.Monad.State (State,get,put,runState,modify_)
import Data.List.NonEmpty (NonEmptyList, fromList, length, zipWith)
Expand Down Expand Up @@ -353,6 +353,11 @@ signalToFrame (Clip mm x y) = binaryFunctionWithRange clip mm x y
signalToFrame (Between mm x y) = binaryFunctionWithRange between mm x y
signalToFrame (SmoothStep mm x y) = binaryFunctionWithRange smoothStep mm x y

signalToFrame (Spr mm x y) = do
xs <- signalToFrame x >>= semiFlatten >>> fromNonEmptyList >>> pure -- :: one-dimensional Matrix (NonEmptyList Sample)
ys <- signalToFrame y >>= traverse unipolar -- :: Matrix Sample
sequence $ combine seq mm xs ys

signalToFrame (Seq s) = do
xs <- semiFlatten <$> signalToFrame s -- :: NonEmptyList Frame
b <- (_.beat <$> get) >>= fract
Expand Down

0 comments on commit 252269c

Please sign in to comment.