hsc3-lang-0.15: Haskell SuperCollider Language

Safe HaskellNone
LanguageHaskell98

Sound.SC3.Lang.Pattern.P.Base

Contents

Description

Synopsis

Math

inf :: Int Source

Type specialised maxBound, a pseudo-infinite value for use at pattern repeat counts.

inf == maxBound

nan :: Floating a => a Source

Constant NaN (not a number) value.

isNaN nan == True

A frequency value of NaN indicates a rest. This constant value can be used as a rest indicator at a frequency model input (not at a rest key).

audition (pbind [(K_dur,pseq [0.1,0.7] inf)
                ,(K_legato,0.2)
                ,(K_degree,pseq [0,2,return nan] inf)])

Data.List Patterns

pcons :: a -> P a -> P a Source

Pattern variant of :.

pcons 'α' (pn (return 'β') 2) == toP "αββ"

pnull :: P a -> Bool Source

Pattern variant of null.

pnull mempty == True
pnull (undecided 'a') == False
pnull (pure 'a') == False
pnull (return 'a') == False

prepeat :: a -> P a Source

Alias for pure, pattern variant of repeat.

ptake 5 (prepeat 3) == toP [3,3,3,3,3]
ptake 5 (pure 3) == toP [3,3,3,3,3]
take 5 (pure 3) == [3]

psplitAt :: Int -> P a -> (P a, P a) Source

Pattern variant of splitAt.

Data.List.Split

psplitPlaces' :: P Int -> P a -> P [a] Source

Pattern variant of splitPlaces.

psplitPlaces' (toP [1,2,3]) (pseries 1 1 6) == toP [[1],[2,3],[4,5,6]]
psplitPlaces' (toP [1,2,3]) (toP ['a'..]) == toP ["a","bc","def"]

psplitPlaces :: P Int -> P a -> P (P a) Source

fmap toP of psplitPlaces'.

psplitPlaces (toP [1,2,3]) (toP ['a'..]) == toP (map toP ["a","bc","def"])

ptake :: Int -> P a -> P a Source

Pattern variant of take_inf, 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]

pcycle :: P a -> P a Source

Type specialised mcycle.

ptake 5 (pcycle 1) == preplicate 5 1
ptake 5 (pcycle (pure 1)) == preplicate 5 1
ptake 5 (pcycle (return 1)) == preplicate 5 1

pfilter :: (a -> Bool) -> P a -> P a Source

Type specialised mfilter. Aliased to pselect. See also preject.

mfilter even (pseq [1,2,3] 2) == toP [2,2]
mfilter (< 3) (pseq [1,2,3] 2) == toP [1,2,1,2]

preplicate :: Int -> a -> P a Source

Pattern variant of replicate.

preplicate 4 1 == toP [1,1,1,1]

Compare to pn:

pn 1 4 == toP [1,1,1,1]
pn (toP [1,2]) 3 == toP [1,2,1,2,1,2]
preplicate 4 (toP [1,2]) :: P (P Int)

pscanl :: (a -> b -> a) -> a -> P b -> P a Source

Pattern variant of scanl. scanl is similar to foldl, but returns a list of successive reduced values from the left. pscanl is an accumulator, it provides a mechanism for state to be threaded through a pattern. It can be used to write a function to remove succesive duplicates from a pattern, to count the distance between occurences of an element in a pattern and so on.

F.foldl (\x y -> 2 * x + y) 4 (pseq [1,2,3] 1) == 43
pscanl (\x y -> 2 * x + y) 4 (pseq [1,2,3] 1) == toP [4,9,20,43]
F.foldl (flip (:)) [] (toP [1..3]) == [3,2,1]
pscanl (flip (:)) [] (toP [1..3]) == toP [[],[1],[2,1],[3,2,1]]
F.foldl (+) 0 (toP [1..5]) == 15
pscanl (+) 0 (toP [1..5]) == toP [0,1,3,6,10,15]

ptail :: P a -> P a Source

pdrop 1. Pattern variant of tail. Drops first element from pattern. Note that the haskell tail function is partial, although drop is not. ptake is equal to `pdrop 1`.

tail [] == _|_
drop 1 [] == []
ptail (toP [1,2]) == toP [2]
ptail mempty == mempty

ptranspose :: [P a] -> P [a] Source

Variant of transpose.

L.transpose [[1,2],[3,4,5]] == [[1,3],[2,4],[5]]
ptranspose [toP [1,2],toP [3,4,5]] == toP [[1,3],[2,4],[5]]
let p = ptranspose [pseq [1,2] inf,pseq [4,5] inf]
in ptake 2 (pdrop (2^16) p) == toP [[1,4],[2,5]]

ptranspose_st_repeat :: [P a] -> P [a] Source

An implicitly repeating pattern variant of transpose_st.

Non-SC3 Patterns

pbool :: (Ord a, Num a) => P a -> P Bool Source

Type specialised fbool.

phold :: P a -> P a Source

Lifted hold.

pinterleave2 :: P a -> P a -> P a Source

Lifted interleave2.

let p = pinterleave2 (pwhite 'α' 1 9 inf) (pseries 10 1 5)
in [3,10,9,11,2,12,9,13,4,14] `L.isPrefixOf` unP p

pinterleave :: [P a] -> P a Source

Lifted interleave.

pinterleave [pwhitei 'α' 0 4 3,pwhitei 'β' 5 9 3] == toP [2,7,0,5,3,6]

pisPrefixOf :: Eq a => P a -> P a -> Bool Source

Lifted isPrefixOf.

prsd :: Eq a => P a -> P a Source

Lifted rsd.

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

Lifted trigger.

let {tr = pbool (toP [0,1,0,0,1,1])
    ;p = ptrigger tr (toP [1,2,3])
    ;r = [Nothing,Just 1,Nothing,Nothing,Just 2,Just 3]}
in p == toP r

Aliases

pappend :: P a -> P a -> P a Source

Type specialised mappend, sequences two patterns, ie. ++.

1 <> mempty <> 2 == toP [1,2]
let {p = prand 'α' [0,1] 3
    ;q = prand 'β' [5,7] 3}
in audition (pbind [(K_degree,pappend p q),(K_dur,0.15)])

pconcat :: [P a] -> P a Source

Type specialised mconcat (or equivalently msum or concat).

mconcat [pseq [1,2] 1,pseq [3,4] 2] == toP [1,2,3,4,3,4]
msum [pseq [1,2] 1,pseq [3,4] 2] == toP [1,2,3,4,3,4]

pempty :: P a Source

Type specialised mempty, ie. 'Data.List.[]'.

pfoldr :: (a -> b -> b) -> b -> P a -> b Source

Type specialised foldr.

> (Pser([1,2,3],5) + Pseq([0,10],3)).asStream.all == [1,12,3,11,2]
let p = pser [1,2,3] 5 + pseq [0,10] 3
in F.foldr (:) [] p == [1,12,3,11,2]

Indefinte patterns may be folded.

take 3 (F.foldr (:) [] (prepeat 1)) == [1,1,1]

The Foldable module includes functions for product, sum, any, elem etc.

F.product (toP [1,3,5]) == 15
floor (F.sum (ptake 100 (pwhite 'α' 0.25 0.75 inf))) == 51
F.any even (toP [1,3,5]) == False
F.elem 5 (toP [1,3,5]) == True

pjoin :: P (P a) -> P a Source

Type specialised join.

join (replicate 2 [1,2]) == [1,2,1,2]
join (preplicate 2 (toP [1,2])) == toP [1,2,1,2]

pjoin_repeat :: P (P a) -> P a Source

join that pushes an outer undecided inward.

join (undecided (undecided 1)) == undecided 1
join (undecided (return 1)) == return 1
pjoin_repeat (undecided (return 1)) == pure 1 == _|_

pmap :: (a -> b) -> P a -> P b Source

Type specialised fmap, ie. map.

pmbind :: P a -> (a -> P b) -> P b Source

Type specialised >>=.

(return 1 >>= return . id) == [1]
(undecided 1 >>= undecided . id) == undecided 1
(pseq [1,2] 1 >>= \x ->
  pseq [3,4,5] 1 >>= \y ->
   return (x,y)) == toP [(1,3),(1,4),(1,5),(2,3),(2,4),(2,5)]

ppure :: a -> P a Source

Type specialised pure.

preturn :: a -> P a Source

Type specialised return.

ptraverse :: Applicative f => (a -> f b) -> P a -> f (P b) Source

Type specialised traverse.

let {f i e = (i + e,e * 2)
    ;(r,p) = T.mapAccumL f 0 (toP [1,3,5])}
in (r,p) == (9,toP [2,6,10])