| Safe Haskell | None |
|---|
Sound.SC3.Lang.Pattern.ID
Contents
Description
sclang pattern library functions.
See http://rd.slavepianos.org/?t=hsc3-texts for tutorial.
- data M
- data P a = P {}
- pappend' :: P a -> P a -> P a
- pappend :: P a -> P a -> P a
- (>>=*) :: P a -> (a -> P b) -> P b
- inf :: Int
- nan :: (Monad m, Floating a) => m a
- stP_join :: [M] -> M
- pextension :: [P a] -> [()]
- pextend :: [P a] -> [P a]
- ptranspose :: [P a] -> P [a]
- pflop' :: [P a] -> P [a]
- pflop :: [P a] -> P (P a)
- pflopJoin :: [P a] -> P a
- liftP :: ([a] -> [b]) -> P a -> P b
- liftP2 :: ([a] -> [b] -> [c]) -> P a -> P b -> P c
- liftP3 :: ([a] -> [b] -> [c] -> [d]) -> P a -> P b -> P c -> P d
- liftP4 :: ([a] -> [b] -> [c] -> [d] -> [e]) -> P a -> P b -> P c -> P d -> P e
- pnull :: P a -> Bool
- stp :: Int -> M
- stopping :: P a -> P a
- stoppingN :: Int -> P a -> P a
- continuing :: P a -> P a
- fromList :: [a] -> P a
- toP :: [a] -> P a
- fromList' :: [a] -> P a
- toP' :: [a] -> P a
- prepeat :: a -> P a
- pzipWith :: (a -> b -> c) -> P a -> P b -> P c
- pzipWith3 :: (a -> b -> c -> d) -> P a -> P b -> P c -> P d
- pzipWith4 :: (a -> b -> c -> d -> e) -> P a -> P b -> P c -> P d -> P e
- pzip :: P a -> P b -> P (a, b)
- pzip3 :: P a -> P b -> P c -> P (a, b, c)
- pzip4 :: P a -> P b -> P c -> P d -> P (a, b, c, d)
- punzip :: P (a, b) -> (P a, P b)
- padd :: Key -> P Value -> P Event -> P Event
- pbind' :: [Type] -> [Maybe Int] -> [Maybe Instrument] -> [(Key, P Value)] -> P Event
- pbind :: [(Key, P Value)] -> P Event
- pbrown' :: (Enum e, Random n, Num n, Ord n) => e -> P n -> P n -> P n -> Int -> P n
- pbrown :: (Enum e, Random n, Num n, Ord n) => e -> n -> n -> n -> Int -> P n
- pclutch :: P a -> P Bool -> P a
- pcollect :: (a -> b) -> P a -> P b
- pconst :: (Ord a, Num a) => a -> P a -> a -> P a
- pdegreeToKey :: RealFrac a => P a -> P [a] -> P a -> P a
- pdiff :: Num n => P n -> P n
- pdurStutter :: Fractional a => P Int -> P a -> P a
- pedit :: Key -> (Value -> Value) -> P Event -> P Event
- pexprand :: (Enum e, Random a, Floating a) => e -> a -> a -> Int -> P a
- pfinval :: Int -> P a -> P a
- pfold :: RealFrac n => P n -> n -> n -> P n
- pfuncn' :: RandomGen g => g -> (g -> (n, g)) -> Int -> P n
- pfuncn :: Enum e => e -> (StdGen -> (n, StdGen)) -> Int -> P n
- pgeom :: Num a => a -> a -> Int -> P a
- pif :: P Bool -> P a -> P a -> P a
- pinstr :: P Instrument -> P Event -> P Event
- pinstr_s :: P (String, Bool) -> P Event -> P Event
- pinstr_d :: P (Synthdef, Bool) -> P Event -> P Event
- pkey_m :: Key -> P Event -> P (Maybe Value)
- pkey :: Key -> P Event -> P Value
- place :: [[a]] -> Int -> P a
- pmono :: Instrument -> Int -> [(Key, P Value)] -> P Event
- pmono_d :: Synthdef -> Int -> [(Key, P Value)] -> P Event
- pmono_s :: String -> Int -> [(Key, P Value)] -> P Event
- pmul :: Key -> P Value -> P Event -> P Event
- pmul' :: Key -> P Value -> P Event -> P Event
- ppatlace :: [P a] -> Int -> P a
- pn :: P a -> Int -> P a
- pnormalizeSum :: Fractional n => P n -> P n
- prand' :: Enum e => e -> [P a] -> Int -> P (P a)
- prand :: Enum e => e -> [P a] -> Int -> P a
- preject :: (a -> Bool) -> P a -> P a
- prorate' :: Num a => Either a [a] -> a -> P a
- prorate :: Num a => P (Either a [a]) -> P a -> P a
- pselect :: (a -> Bool) -> P a -> P a
- pseq1 :: [P a] -> Int -> P a
- pseq :: [P a] -> Int -> P a
- pseqr :: (Int -> [P a]) -> Int -> P a
- pseqn :: [Int] -> [P a] -> Int -> P a
- pser1 :: [P a] -> Int -> P a
- pser :: [P a] -> Int -> P a
- pseries :: Num a => a -> a -> Int -> P a
- pshuf :: Enum e => e -> [a] -> Int -> P a
- pslide :: [a] -> Int -> Int -> Int -> Int -> Bool -> P a
- psplitAt :: Int -> P a -> (P a, P a)
- psplitPlaces' :: P Int -> P a -> P [a]
- psplitPlaces :: P Int -> P a -> P (P a)
- pstretch :: P Value -> P Event -> P Event
- pstutter :: P Int -> P a -> P a
- pswitch :: [P a] -> P Int -> P a
- pswitch1 :: [P a] -> P Int -> P a
- ptuple :: [P a] -> Int -> P [a]
- pwhite' :: (Enum e, Random n) => e -> P n -> P n -> P n
- pwhite :: (Random n, Enum e) => e -> n -> n -> Int -> P n
- pwhitei :: (RealFrac n, Random n, Enum e) => e -> n -> n -> Int -> P n
- pwrand :: Enum e => e -> [P a] -> [Double] -> Int -> P a
- pwrap :: (Ord a, Num a) => P a -> a -> a -> P a
- pxrand :: Enum e => e -> [P a] -> Int -> P a
- pconcat :: [P a] -> P a
- pempty :: P a
- pjoin :: P (P a) -> P a
- pjoin' :: P (P a) -> P a
- pcons :: a -> P a -> P a
- pcycle :: P a -> P a
- pdrop :: Int -> P a -> P a
- pfilter :: (a -> Bool) -> P a -> P a
- preplicate :: Int -> a -> P a
- pscanl :: (a -> b -> a) -> a -> P b -> P a
- ptail :: P a -> P a
- ptake :: Int -> P a -> P a
- pbool :: (Ord a, Num a) => P a -> P Bool
- pconcatReplicate :: Int -> P a -> P a
- pcountpost :: P Bool -> P Int
- pcountpre :: P Bool -> P Int
- pinterleave :: P a -> P a -> P a
- prsd :: Eq a => P a -> P a
- ptrigger :: P Bool -> P a -> P (Maybe a)
- ptmerge :: (Time, P Event) -> (Time, P Event) -> P Event
- pmerge :: P Event -> P Event -> P Event
- ptpar :: [(Time, P Event)] -> P Event
- ppar :: [P Event] -> P Event
- e_send :: Transport m => Time -> Int -> Event -> m ()
- e_tplay :: Transport m => Time -> [Int] -> [Event] -> m ()
- e_play :: Transport m => [Int] -> [Event] -> m ()
P type and instances
Pattern data type (opaque)
pappend' :: P a -> P a -> P aSource
A variant of pappend that preserves the continuation mode but
is strict in the right argument.
pappend :: P a -> P a -> P aSource
mappend variant to sequence two patterns.
Note that in order for mappend to be productive in
mconcat on an infinite list it cannot store the
right-hand stop/continue mode, see pappend'
toP [1,2] `pappend` toP [2,3] == toP [1,2,2,3] ptake 3 (prepeat 3 `pappend` prepeat 4) == toP' [3,3,3] ptake 3 (pconcat (cycle [prepeat 3])) == toP' [3,3,3] pempty `pappend` pempty == pempty
nan :: (Monad m, Floating a) => m aSource
Constant NaN (not a number) value for use as a rest indicator
at a frequency model input (not at a rest key).
Extension
pextension :: [P a] -> [()]Source
Extension of a set of patterns. If any patterns are stopping, the longest such pattern, else the longest of the continuing patterns.
pextension [toP [1,2],toP [3,4,5]] == [(),(),()] pextension [toP' [1,2],toP [3,4,5]] == [(),()]
pextend :: [P a] -> [P a]Source
Extend a set of patterns following pextension rule.
pextend [toP [1,2],toP [3,4,5]] == [toP' [1,2,1],toP' [3,4,5]]
pextend [toP' [1,2],toP [3,4,5]] == [toP' [1,2],toP' [3,4]]
ptranspose :: [P a] -> P [a]Source
Variant of transpose.
ptranspose [toP [1,2],toP [3,4,5]] == toP [[1,3],[2,4],[5]]
pflop' :: [P a] -> P [a]Source
Variant of pflop.
pflop' [toP [1,2],toP [3,4,5]] == toP' [[1,3],[2,4],[1,5]]
pflop :: [P a] -> P (P a)Source
Variant of ptranspose transforming the input patterns by
pextension.
pflop [toP [1,2],toP [3,4,5]] == toP' (map toP [[1,3],[2,4],[1,5]])
P lifting
liftP3 :: ([a] -> [b] -> [c] -> [d]) -> P a -> P b -> P c -> P dSource
Lift ternary list function to P.
liftP4 :: ([a] -> [b] -> [c] -> [d] -> [e]) -> P a -> P b -> P c -> P d -> P eSource
Lift quaternary list function to P.
P functions
continuing :: P a -> P aSource
Set pattern mode to Continue.
The basic list to pattern function. The pattern is continuing.
continuing (pseq [1,2,3] 1) == toP [1,2,3]
A variant from fromList to make stopping patterns.
pseq [1,2,3] 1 == toP' [1,2,3]
pzipWith :: (a -> b -> c) -> P a -> P b -> P cSource
Pattern variant of zipWith. Note that zipWith is truncating,
whereas the numerical instances are extending.
zipWith (*) [1,2,3] [5,6] == [5,12] pzipWith (*) (toP [1,2,3]) (toP [5,6]) == toP [5,12,15] toP [1,2,3] * toP [5,6] == toP [5,12,15]
Note that the list instance of applicative is combinatorial (ie. Monadic).
(pure (*) <*> [1,2,3] <*> [5,6]) == [5,6,10,12,15,18] (pure (*) <*> toP [1,2] <*> toP [5]) == toP [5,10]
pzipWith4 :: (a -> b -> c -> d -> e) -> P a -> P b -> P c -> P d -> P eSource
Pattern variant of zipWith4.
SC3 patterns
padd :: Key -> P Value -> P Event -> P EventSource
Add a value to an existing key, or set the key if it doesn't exist.
Padd(\freq,801,Pbind(\freq,100)).asStream.next(())
padd "freq" 801 (pbind [("freq",100)]) == pbind [("freq",901)]
pbind' :: [Type] -> [Maybe Int] -> [Maybe Instrument] -> [(Key, P Value)] -> P EventSource
A primitive form of the SC3 pbind pattern, with explicit type
and identifier inputs.
pbrown' :: (Enum e, Random n, Num n, Ord n) => e -> P n -> P n -> P n -> Int -> P nSource
A variant of pbrown where the l, r and s inputs are patterns.
pbrown' 'α' 1 700 (pseq [1,20] inf) 4 == toP' [415,419,420,428]
pbrown :: (Enum e, Random n, Num n, Ord n) => e -> n -> n -> n -> Int -> P nSource
SC3 pattern to generate psuedo-brownian motion.
pbrown 'α' 0 9 1 5 == toP' [4,4,5,4,3]
pclutch :: P a -> P Bool -> P aSource
SC3 sample and hold pattern. For true values in the control pattern, step the value pattern, else hold the previous value.
Pclutch(Pser([1,2,3,4,5],8),
Pseq([1,0,1,0,0,0,1,1],inf)).asStream.all
let {c = pbool (pseq [1,0,1,0,0,1,1] 1)
;r = toP' [1,1,2,2,2,3,4,5,5,1,1,1,2,3]}
in pclutch (pser [1,2,3,4,5] 8) c == r
Note the initialization behavior, nothing is generated until the first true value.
let {p = pseq [1,2,3,4,5] 1
;q = pbool (pseq [0,0,0,0,0,0,1,0,0,1,0,1] 1)}
in pclutch p q
pcollect :: (a -> b) -> P a -> P bSource
SC3 name for fmap, ie. patterns are functors.
Pcollect({arg i;i * 3},Pseq(#[1,2,3],inf)).asStream.nextN(9)
pcollect (* 3) (toP [1,2,3]) == toP [3,6,9]
Pseq(#[1,2,3],3).collect({arg i;i * 3}).asStream.nextN(9)
fmap (* 3) (toP [1,2,3]) == toP [3,6,9]
pconst :: (Ord a, Num a) => a -> P a -> a -> P aSource
SC3 pattern to constrain the sum of a numerical pattern. Is equal to p until the accumulated sum is within t of n. At that point, the difference between the specified sum and the accumulated sum concludes the pattern.
Pconst(10,Prand([1,2,0.5,0.1],inf),0.001).asStream.nextN(15,())
let p = pconst 10 (prand 'α' [1,2,0.5,0.1] inf) 0.001 in (p,Data.Foldable.sum p)
pdegreeToKey :: RealFrac a => P a -> P [a] -> P a -> P aSource
SC3 pattern to derive notes from an index into a scale.
let {p = pseq [0,1,2,3,4,3,2,1,0,2,4,7,4,2] 2
;q = return [0,2,4,5,7,9,11]
;r = [0,2,4,5,7,5,4,2,0,4,7,12,7,4,0,2,4,5,7,5,4,2,0,4,7,12,7,4]}
in pdegreeToKey p q (return 12) == toP' r
let {p = pseq [0,1,2,3,4,3,2,1,0,2,4,7,4,2] 2
;q = pseq (map return [[0,2,4,5,7,9,11],[0,2,3,5,7,8,11]]) 1
;r = [0,2,4,5,7,5,4,2,0,4,7,12,7,4,0,2,3,5,7,5,3,2,0,3,7,12,7,3]}
in pdegreeToKey p (pstutter 14 q) (return 12) == toP' r
This is the pattern variant of degree_to_key.
let s = [0,2,4,5,7,9,11] in map (P.degree_to_key s 12) [0,2,4,7,4,2,0] == [0,4,7,12,7,4,0]
pdiff :: Num n => P n -> P nSource
SC3 pattern to calculate adjacent element difference.
pdiff (toP [0,2,3,5,6,8,9]) == toP [-2,-1,-2,-1,-2,-1,7]
pdurStutter :: Fractional a => P Int -> P a -> P aSource
SC3 pattern to partition a value into n equal subdivisions.
Subdivides each duration by each stutter and yields that value
stutter times. A stutter of 0 will skip the duration value, a
stutter of 1 yields the duration value unaffected.
s = Pseq(#[1,1,1,1,1,2,2,2,2,2,0,1,3,4,0],inf); d = Pseq(#[0.5,1,2,0.25,0.25],inf); PdurStutter(s,d).asStream.nextN(24)
let {s = pseq [1,1,1,1,1,2,2,2,2,2,0,1,3,4,0] inf
;d = pseq [0.5,1,2,0.25,0.25] inf}
in ptake 24 (pdurStutter s d)
pexprand :: (Enum e, Random a, Floating a) => e -> a -> a -> Int -> P aSource
An SC3 pattern of random values that follow a exponential distribution.
Pexprand(0.0001,1,10).asStream.all pexprand 'α' 0.0001 1 10
pfinval :: Int -> P a -> P aSource
SC3 pattern to take the first n elements of the pattern. See
also ptake.
Pfinval(5,Pseq(#[1,2,3],inf)).asStream.nextN(5) pfinval 5 (pseq [1,2,3] inf) == toP' [1,2,3,1,2]
pfold :: RealFrac n => P n -> n -> n -> P nSource
SC3 pattern to fold values to lie within range (as opposed to
wrap and clip). This is not related to the Foldable
pattern instance.
pfold (toP [10,11,12,-6,-7,-8]) (-7) 11 == toP [10,11,10,-6,-7,-6]
The underlying primitive is the fold_ function.
let f n = fold_ n (-7) 11 in map f [10,11,12,-6,-7,-8] == [10,11,10,-6,-7,-6]
pfuncn' :: RandomGen g => g -> (g -> (n, g)) -> Int -> P nSource
Underlying form of haskell pfuncn pattern.
pfuncn :: Enum e => e -> (StdGen -> (n, StdGen)) -> Int -> P nSource
A variant of the SC3 pattern that evaluates a closure at each
step. The haskell variant function has a StdGen form.
pgeom :: Num a => a -> a -> Int -> P aSource
SC3 geometric series pattern.
Pgeom(3,6,5).asStream.nextN(5) pgeom 3 6 5 == toP' [3,18,108,648,3888] pgeom 1 2 10 == toP' [1,2,4,8,16,32,64,128,256,512]
Real numbers work as well.
pgeom 1.0 1.1 6
pif :: P Bool -> P a -> P a -> P aSource
SC3 pattern-based conditional expression.
var a = Pfunc({0.3.coin});
var b = Pwhite(0,9,in);
var c = Pwhite(10,19,inf);
Pif(a,b,c).asStream.nextN(9)
let {a = fmap (< 0.3) (pwhite 'α' 0.0 1.0 inf)
;b = pwhite 'β' 0 9 inf
;c = pwhite 'γ' 10 19 inf}
in ptake 9 (pif a b c) == toP' [11,3,6,11,11,15,17,4,7]
pinstr :: P Instrument -> P Event -> P EventSource
Pattern to assign Instruments to Events. An
Instrument is either a Synthdef or a String. In the
Synthdef case the instrument is asynchronously sent to the server
before processing the event, which has timing implications. In
general the instrument pattern ought to have a Synthdef for the
first occurence of the instrument, and a String for subsequent
occurences.
pinstr_s :: P (String, Bool) -> P Event -> P EventSource
Variant of pinstr which lifts the String pattern to an
Instrument pattern.
pinstr_d :: P (Synthdef, Bool) -> P Event -> P EventSource
Variant of pinstr which lifts the Synthdef pattern to an
Instrument pattern.
place :: [[a]] -> Int -> P aSource
SC3 interlaced embedding of subarrays.
Place([0,[1,2],[3,4,5]],3).asStream.all place [[0],[1,2],[3,4,5]] 3 == toP' [0,1,3,0,2,4,0,1,5]
Place(#[1,[2,5],[3,6]],2).asStream.nextN(6) place [[1],[2,5],[3,6]] 2 == toP' [1,2,3,1,5,6] place [[1],[2,5],[3,6..]] 4 == toP' [1,2,3,1,5,6,1,2,9,1,5,12]
pmono :: Instrument -> Int -> [(Key, P Value)] -> P EventSource
SC3 pattern that is a variant of pbind for controlling
monophonic (persistent) synthesiser nodes.
pmono_d :: Synthdef -> Int -> [(Key, P Value)] -> P EventSource
Variant of pmono that lifts Synthdef to Instrument.
pmono_s :: String -> Int -> [(Key, P Value)] -> P EventSource
Variant of pmono that lifts String to Instrument.
ppatlace :: [P a] -> Int -> P aSource
SC3 pattern to lace input patterns. Note that the current implementation stops late, it cycles the second series one place.
ppatlace [1,prand 'α' [2,3] inf] 5 == toP' [1,3,1,2,1,3,1,2,1,2]
SC3 pattern to repeats the enclosed pattern a number of times.
pn 1 4 == toP' [1,1,1,1] pn (toP [1,2,3]) 3 == toP' [1,2,3,1,2,3,1,2,3]
This is related to concat.replicate in standard list processing.
concat (replicate 4 [1]) == [1,1,1,1] concat (replicate 3 [1,2,3]) == [1,2,3,1,2,3,1,2,3]
There is a pconcatReplicate near-alias (reversed argument order).
pconcatReplicate 4 1 == toP' [1,1,1,1] pconcatReplicate 3 (toP [1,2]) == toP' [1,2,1,2,1,2]
This is productive over infinite lists.
concat (replicate inf [1]) pconcat (replicate inf 1) pconcatReplicate inf 1
pnormalizeSum :: Fractional n => P n -> P nSource
Pattern variant of normalizeSum.
prand :: Enum e => e -> [P a] -> Int -> P aSource
SC3 pattern to make n random selections from a list of patterns, the resulting pattern is flattened (joined).
Prand([1,Pseq([10,20,30]),2,3,4,5],6).asStream.all prand 'α' [1,toP [10,20],2,3,4,5] 4 == toP' [5,2,10,20,2]
preject :: (a -> Bool) -> P a -> P aSource
SC3 pattern to rejects values for which the predicate is true. reject f is equal to filter (not . f).
preject (== 1) (pseq [1,2,3] 2) == toP' [2,3,2,3] pfilter (not . (== 1)) (pseq [1,2,3] 2) == toP' [2,3,2,3]
Pwhite(0,255,20).reject({|x| x.odd}).asStream.all
preject odd (pwhite 'α' 0 255 10) == toP [32,158,62,216,240,20]
Pwhite(0,255,20).select({|x| x.odd}).asStream.all
pselect odd (pwhite 'α' 0 255 10) == toP [241,187,119,127]
prorate :: Num a => P (Either a [a]) -> P a -> P aSource
SC3 sub-dividing pattern.
Prorate(Pseq([0.35,0.5,0.8]),1).asStream.nextN(6) prorate (fmap Left (pseq [0.35,0.5,0.8] 1)) 1
Prorate(Pseq([0.35,0.5,0.8]),Prand([20,1],inf)).asStream.nextN(6) prorate (fmap Left (pseq [0.35,0.5,0.8] 1)) (prand 'α' [20,1] 3)
var l = [[1,2],[5,7],[4,8,9]]).collect(_.normalizeSum); Prorate(Pseq(l,1).asStream.nextN(8)
let l = map (Right . C.normalizeSum) [[1,2],[5,7],[4,8,9]] in prorate (toP l) 1
pselect :: (a -> Bool) -> P a -> P aSource
See pfilter.
pselect (< 3) (pseq [1,2,3] 2) == toP' [1,2,1,2]
pseq :: [P a] -> Int -> P aSource
SC3 pattern to cycle over a list of patterns. The repeats pattern gives the number of times to repeat the entire list.
pseq [return 1,return 2,return 3] 2 == toP' [1,2,3,1,2,3] pseq [1,2,3] 2 == toP' [1,2,3,1,2,3] pseq [1,pn 2 2,3] 2 == toP' [1,2,2,3,1,2,2,3]
There is an inf value for the repeats variable.
ptake 3 (pdrop 1000000 (pseq [1,2,3] inf)) == toP' [2,3,1]
pseqn :: [Int] -> [P a] -> Int -> P aSource
A variant of pseq to aid translating a common SC3 idiom where a
finite random pattern is included in a Pseq list. In the SC3
case, at each iteration a new computation is run. This idiom does
not directly translate to the declarative haskell pattern library.
Pseq([1,Prand([2,3],1)],5).asStream.all pseq [1,prand 'α' [2,3] 1] 5
Although the intended pattern can usually be expressed using an alternate construction:
Pseq([1,Prand([2,3],1)],5).asStream.all ppatlace [1,prand 'α' [2,3] inf] 5 == toP' [1,3,1,2,1,3,1,2,1,2]
the pseqn variant handles many common cases.
Pseq([Pn(8,2),Pwhite(9,16,1)],5).asStream.all pseqn [2,1] [8,pwhite 'α' 9 16 inf] 5
pser1 :: [P a] -> Int -> P aSource
Variant of pser that consumes sub-patterns one element per
iteration.
pser1 [1,pser [10,20] 3,3] 9 == toP' [1,10,3,1,20,3,1,10,3]
pser :: [P a] -> Int -> P aSource
SC3 pattern that is like pseq, however the repeats variable
gives the number of elements in the sequence, not the number of
cycles of the pattern.
pser [1,2,3] 5 == toP' [1,2,3,1,2] pser [1,pser [10,20] 3,3] 9 == toP' [1,10,20,10,3,1,10,20,10] pser [1,2,3] 5 * 3 == toP' [3,6,9,3,6]
pseries :: Num a => a -> a -> Int -> P aSource
SC3 arithmetric series pattern, see also pgeom.
pseries 0 2 10 == toP' [0,2,4,6,8,10,12,14,16,18] pseries 9 (-1) 10 == toP' [9,8 .. 0] pseries 1.0 0.2 3 == toP' [1.0,1.2,1.4]
pshuf :: Enum e => e -> [a] -> Int -> P aSource
SC3 pattern to return n repetitions of a shuffled sequence.
Pshuf([1,2,3,4],2).asStream.all pshuf 'α' [1,2,3,4] 2 == toP' [2,4,3,1,2,4,3,1]
pslide :: [a] -> Int -> Int -> Int -> Int -> Bool -> P aSource
SC3 pattern to slide over a list of values.
Pslide([1,2,3,4],inf,3,1,0).asStream.all pslide [1,2,3,4] 4 3 1 0 True == toP' [1,2,3,2,3,4,3,4,1,4,1,2] pslide [1,2,3,4,5] 3 3 (-1) 0 True == toP' [1,2,3,5,1,2,4,5,1]
psplitPlaces' :: P Int -> P a -> P [a]Source
Pattern variant of splitPlaces.
psplitPlaces :: P Int -> P a -> P (P a)Source
A variant of psplitPlaces' that joins the output pattern.
pstretch :: P Value -> P Event -> P EventSource
SC3 pattern to do time stretching. It is equal to pmul at
"stretch".
pstutter :: P Int -> P a -> P aSource
SC3 pattern to repeat each element of a pattern _n_ times.
pstutter 2 (toP [1,2,3]) == toP [1,1,2,2,3,3]
The count input may be a pattern.
let {p = pseq [1,2] inf
;q = pseq [1,2,3] 2}
in pstutter p q == toP' [1,2,2,3,1,1,2,3,3]
pstutter (toP [1,2,3]) (toP [4,5,6]) == toP [4,5,5,6,6,6]
pswitch :: [P a] -> P Int -> P aSource
SC3 pattern to select elements from a list of patterns by a pattern of indices.
switch l i = i >>= (l !!) pswitch [pseq [1,2,3] 2,pseq [65,76] 1,800] (toP [2,2,0,1])
pswitch1 :: [P a] -> P Int -> P aSource
SC3 pattern that uses a pattern of indices to select which
pattern to retrieve the next value from. Only one value is
selected from each pattern. This is in comparison to pswitch,
which embeds the pattern in its entirety.
Pswitch1([Pseq([1,2,3],inf),
Pseq([65,76],inf),
8],
Pseq([2,2,0,1],6)).asStream.all
pswitch1 [pseq [1,2,3] inf,pseq [65,76] inf,8] (pseq [2,2,0,1] 6)
ptuple :: [P a] -> Int -> P [a]Source
SC3 pattern to combine a list of streams to a stream of lists.
See also pflop.
Ptuple([Pseries(7,-1,8),
Pseq([9,7,7,7,4,4,2,2],1),
Pseq([4,4,4,2,2,0,0,-3],1)],1).asStream.nextN(8)
ptuple [pseries 7 (-1) 8
,pseq [9,7,7,7,4,4,2,2] 1
,pseq [4,4,4,2,2,0,0,-3] 1] 1
pwhite' :: (Enum e, Random n) => e -> P n -> P n -> P nSource
A variant of pwhite where the range inputs are patterns.
pwhite :: (Random n, Enum e) => e -> n -> n -> Int -> P nSource
SC3 pattern to generate a uniform linear distribution in given range.
pwhite 'α' 0 9 5 == toP [3,0,1,6,6]
It is important to note that this structure is not actually indeterminate, so that the below is zero.
let p = pwhite 'α' 0.0 1.0 3 in p - p == toP [0,0,0]
pwhitei :: (RealFrac n, Random n, Enum e) => e -> n -> n -> Int -> P nSource
A variant of pwhite that generates integral (rounded) values.
pwrand :: Enum e => e -> [P a] -> [Double] -> Int -> P aSource
SC3 pattern to embed values randomly chosen from a list. Returns one item from the list at random for each repeat, the probability for each item is determined by a list of weights which should sum to 1.0.
let w = C.normalizeSum [1,3,5] in pwrand 'α' [1,2,3] w 6 == toP [3,1,2,3,3,3]
Pwrand.new([1,2,Pseq([3,4],1)],[1,3,5].normalizeSum,6).asStream.nextN(6)
let w = C.normalizeSum [1,3,5] in pwrand 'α' [1,2,pseq [3,4] 1] w 6 == toP [3,4,1,2,3,4]
pwrap :: (Ord a, Num a) => P a -> a -> a -> P aSource
SC3 pattern to constrain the range of output values by wrapping.
See also pfold.
Pn(Pwrap(Pgeom(200,1.07,26),200,1000.0),inf).asStream.nextN(26) pwrap (pgeom 200 1.07 26) 200 1000
pxrand :: Enum e => e -> [P a] -> Int -> P aSource
SC3 pattern that is like prand but filters successive duplicates.
pxrand 'α' [1,toP [2,3],toP [4,5,6]] 15
Monoid aliases
Pattern variant for mempty, ie. the empty pattern.
pempty `pappend` pempty == pempty pempty `pappend` 1 == 1 `pappend` pempty
Monad aliases
Data.List functions
pcons :: a -> P a -> P aSource
Pattern variant of :.
pcons 'α' (pn (return 'β') 2) == fromList' "αββ"
Pattern variant of cycle.
ptake 5 (pcycle (toP [1,2,3])) == toP' [1,2,3,1,2] ptake 5 (pseq [1,2,3] inf) == toP' [1,2,3,1,2]
pdrop :: Int -> P a -> P aSource
Pattern variant of drop.
Pseries(1,1,20).drop(5).asStream.nextN(15)
pdrop 5 (pseries 1 1 10) == toP' [6,7,8,9,10] pdrop 1 pempty == pempty
preplicate :: Int -> a -> P aSource
ptake :: Int -> P a -> P aSource
Pattern variant of take, see also pfinval.
ptake 5 (pseq [1,2,3] 2) == toP' [1,2,3,1,2] ptake 5 (toP [1,2,3]) == toP' [1,2,3] ptake 5 (pseq [1,2,3] inf) == toP' [1,2,3,1,2] ptake 5 (pwhite 'α' 0 5 inf) == toP' [5,2,1,2,0]
Note that ptake does not extend the input pattern, unlike pser.
ptake 5 (toP [1,2,3]) == toP' [1,2,3] pser [1,2,3] 5 == toP' [1,2,3,1,2]
Non-SC3 patterns
pinterleave :: P a -> P a -> P aSource
Interleave elements from two patterns. If one pattern ends the other pattern continues until it also ends.
let {p = pseq [1,2,3] 2
;q = pseq [4,5,6,7] 1}
in pinterleave p q == toP' [1,4,2,5,3,6,1,7,2,4,3,5]
ptake 5 (pinterleave (pcycle 1) (pcycle 2)) == toP' [1,2,1,2,1] ptake 10 (pinterleave (pwhite 'α' 1 9 inf) (pseries 10 1 5))
prsd :: Eq a => P a -> P aSource
Pattern to remove successive duplicates.
prsd (pstutter 2 (toP [1,2,3])) == toP [1,2,3] prsd (pseq [1,2,3] 2) == toP' [1,2,3,1,2,3]
ptrigger :: P Bool -> P a -> P (Maybe a)Source
Pattern where the tr pattern determines the rate at which
values are read from the x pattern. For each sucessive true
value at tr the output is a `Just e` of each succesive element at
x. False values at tr generate Nothing values.
let {tr = pbool (toP [0,1,0,0,1,1])
;r = [Nothing,Just 1,Nothing,Nothing,Just 2,Just 3]}
in ptrigger tr (toP [1,2,3]) == fromList r