| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Sound.SC3.Lang.Pattern.P.Core
Description
P type, instance and core functions.
- data P a = P {
- unP_either :: Either a [a]
- undecided :: a -> P a
- toP :: [a] -> P a
- unP :: P a -> [a]
- unP_repeat :: P a -> [a]
- liftP :: ([a] -> [b]) -> P a -> P b
- liftP2 :: ([a] -> [b] -> [c]) -> P a -> P b -> P c
- liftP2_repeat :: ([a] -> [b] -> [c]) -> P a -> P b -> P c
- liftP3 :: ([a] -> [b] -> [c] -> [d]) -> P a -> P b -> P c -> P d
- liftP3_repeat :: ([a] -> [b] -> [c] -> [d]) -> P a -> P b -> P c -> P d
- pzipWith :: (a -> b -> c) -> P a -> P b -> P c
- pzipWith3 :: (a -> b -> c -> d) -> P a -> P b -> P c -> P d
- pzip :: P a -> P b -> P (a, b)
- pzip3 :: P a -> P b -> P c -> P (a, b, c)
- punzip :: P (a, b) -> (P a, P b)
P
Patterns are opaque. P a is a pattern with elements of type
a. Patterns are constructed, manipulated and destructured using
the functions provided, ie. the pattern instances for return,
pure and toList, and the pattern specific functions
undecided and toP.
F.toList (toP [1,2,3] * 2) == [2,4,6]
Patterns are Functors. fmap applies a function to each element
of a pattern.
fmap (* 2) (toP [1,2,3,4,5]) == toP [2,4,6,8,10]
Patterns are Monoids. mempty is the empty pattern, and
mappend (<>) makes a sequence of two patterns.
1 <> mempty <> 2 == toP [1,2]
Patterns are Applicative. The pattern instance is pointwise &
truncating, as for ZipList. pure lifts a value into an
infinite pattern of itself, <*> applies a pattern of functions to
a pattern of values. This is distinct from the combinatorial
instance for ordinary lists, ie. where pure is return and <*>
is ap.
liftA2 (+) (toP [1,2]) (toP [3,4,5]) == toP [4,6] liftA2 (+) [1,2] [3,4,5] == [4,5,6,5,6,7]
Patterns are Monads, and therefore allow do notation.
let p = do {x <- toP [1,2]; y <- toP [3,4,5]; return (x,y)}
in p == toP [(1,3),(1,4),(1,5),(2,3),(2,4),(2,5)]Patterns are Numerical. The instances can be derived from the
Applicative instance.
1 + toP [2,3,4] == liftA2 (+) 1 (toP [2,3,4])
Constructors
| P | |
Fields
| |
Lift a value to a pattern deferring deciding if the constructor
ought to be pure or return to the consuming function. The
pattern instances for fromInteger and fromRational make
undecided patterns. In general horizontal functions (ie. <>)
resolve using return and vertical functions (ie. zip) resolve
using pure. In the documentation functions that resolve using
pure are annotated as implicitly repeating.
1 <> toP [2,3] == return 1 <> toP [2,3] toP [1,2] * 3 == toP [1,2] * pure 3
The basic list to pattern function, inverse is unP.
unP (toP "str") == "str"
There is a default sound, given by defaultSynthdef from Sound.SC3.
audition defaultSynthdef
If no instrument is specified we hear the default.
audition (pbind [(K_degree,pxrand 'α' [0,1,5,7] inf)
,(K_dur,toP [0.1,0.2,0.1])])> Pbind(\degree,(Pxrand([0,1,5,7],inf)) > ,\dur,Pseq([0.1,0.2,0.1],1)).play
The pattern above is finite, toP can sometimes be replaced with
pseq.
audition (pbind [(K_degree,pxrand 'α' [0,1,5,7] inf)
,(K_dur,pseq [0.1,0.2,0.1] inf)])unP_repeat :: P a -> [a] Source
Lift P
liftP2 :: ([a] -> [b] -> [c]) -> P a -> P b -> P c Source
Lift binary list function to pattern function.
liftP2 (zipWith (+)) (toP [1,2]) (toP [3,4,5]) == toP [4,6] liftA2 (+) (toP [1,2]) (toP [3,4,5]) == toP [4,6]
liftP2_repeat :: ([a] -> [b] -> [c]) -> P a -> P b -> P c Source
Lift binary list function to implicitly repeating pattern function.
liftP3 :: ([a] -> [b] -> [c] -> [d]) -> P a -> P b -> P c -> P d Source
Lift ternary list function to pattern function.
liftP3_repeat :: ([a] -> [b] -> [c] -> [d]) -> P a -> P b -> P c -> P d Source
Lift ternary list function to implicitly repeating pattern function.
Zip P
pzipWith :: (a -> b -> c) -> P a -> P b -> P c Source
An implicitly repeating pattern variant of zipWith.
zipWith (*) [1,2,3] [5,6] == [5,12] pzipWith (*) (toP [1,2,3]) (toP [5,6]) == toP [5,12]
It is the basis for lifting binary operators to patterns.
toP [1,2,3] * toP [5,6] == toP [5,12]
let p = pzipWith (,) (pseq [1,2] 2) (pseq [3,4] inf) in p == toP [(1,3),(2,4),(1,3),(2,4)]
zipWith (,) (return 0) (return 1) == return (0,1) pzipWith (,) 0 1 == undecided (0,1)
pzipWith3 :: (a -> b -> c -> d) -> P a -> P b -> P c -> P d Source
An implicitly repeating pattern variant of zipWith3.
pzip :: P a -> P b -> P (a, b) Source
An implicitly repeating pattern variant of zip.
zip (return 0) (return 1) == return (0,1) pzip (undecided 3) (undecided 4) == undecided (3,4) pzip 0 1 == undecided (0,1)
Note that pzip is otherwise like haskell zip, ie. truncating.
zip [1,2] [0] == [(1,0)] pzip (toP [1,2]) (return 0) == toP [(1,0)] pzip (toP [1,2]) (pure 0) == toP [(1,0),(2,0)] pzip (toP [1,2]) 0 == toP [(1,0),(2,0)]