hsc3-0.20: Haskell SuperCollider
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.Sc3.Common.Base

Description

Common core functions.

Synopsis

Function

type Fn1 a b = a -> b Source #

Unary function.

type Fn2 a b c = a -> b -> c Source #

Binary function.

type Fn3 a b c d = a -> b -> c -> d Source #

Ternary function.

type Fn4 a b c d e = a -> b -> c -> d -> e Source #

Quaternary function.

type Fn5 a b c d e f = a -> b -> c -> d -> e -> f Source #

5-parameter function.

type Fn6 a b c d e f g = a -> b -> c -> d -> e -> f -> g Source #

6-parameter function.

type Fn10 a b c d e f g h i j k = a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k Source #

10-parameter function.

type Fn11 a b c d e f g h i j k l = a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l Source #

11-parameter function.

iter :: Int -> (a -> a) -> a -> a Source #

Apply f n times, ie. iterate f x !! n

iter 3 (* 2) 1 == 8
iterate (* 2) 1 !! 3 == 8

Functor

fvoid :: Functor f => f a -> f () Source #

This is the same function as Control.Monad.void, which however hugs does not know of.

Read

reads_exact :: Read a => String -> Maybe a Source #

Variant of reads requiring exact match.

String

string_split_at_char :: Char -> String -> [String] Source #

Similar to Data.List.Split.splitOn, which however hugs doesn't know of.

string_split_at_char ':' "/usr/local/bin:/usr/bin:/bin" == ["/usr/local/bin","/usr/bin","/bin"]
string_split_at_char ':' "/usr/local/bin" == ["/usr/local/bin"]

String / Case

data Case_Rule Source #

Ci = Case insensitive, Cs = case sensitive, Sci = separator & case insensitive

Constructors

Ci 
Cs 
Sci 

Instances

Instances details
Eq Case_Rule Source # 
Instance details

Defined in Sound.Sc3.Common.Base

string_eq :: Case_Rule -> String -> String -> Bool Source #

String equality with Case_Rule.

string_eq Ci "sinOsc" "SinOsc" == True
string_eq Sci "sin-osc" "SinOsc" == True

parse_enum :: (Show t, Enum t, Bounded t) => Case_Rule -> String -> Maybe t Source #

Enum parser with Case_Rule.

parse_enum Ci "false" == Just False

List

compose_l :: [t -> t] -> t -> t Source #

Left to right composition of a list of functions.

compose_l [(* 2),(+ 1)] 3 == 7

compose_r :: [t -> t] -> t -> t Source #

Right to left composition of a list of functions.

compose_r [(* 2),(+ 1)] 3 == 8

d_dx :: Num a => [a] -> [a] Source #

SequenceableCollection.differentiate

> [3,4,1,1].differentiate == [3,1,-3,0]
d_dx [3,4,1,1] == [3,1,-3,0]
d_dx [0,1,3,6] == [0,1,2,3]

d_dx' :: Num n => [n] -> [n] Source #

Variant that does not prepend zero to input, ie. tail of d_dx.

d_dx' [3,4,1,1] == [1,-3,0]
d_dx' [0,1,3,6] == [1,2,3]

dx_d :: Num n => [n] -> [n] Source #

SequenceableCollection.integrate

> [3,4,1,1].integrate == [3,7,8,9]
dx_d [3,4,1,1] == [3,7,8,9]
dx_d (d_dx [0,1,3,6]) == [0,1,3,6]
dx_d [0.5,0.5] == [0.5,1]

dx_d' :: Num n => [n] -> [n] Source #

Variant pre-prending zero to output.

dx_d' [3,4,1,1] == [0,3,7,8,9]
dx_d' (d_dx' [0,1,3,6]) == [0,1,3,6]
dx_d' [0.5,0.5] == [0,0.5,1]

lookup_by :: (a -> t -> Bool) -> a -> [(t, b)] -> Maybe b Source #

lookup with equality function.

lookup_by_err :: (a -> t -> Bool) -> a -> [(t, b)] -> b Source #

Erroring variant.

rlookup_by :: (b -> b -> Bool) -> b -> [(a, b)] -> Maybe a Source #

Reverse lookup with equality function.

pcn_triples :: [a] -> [(Maybe a, a, Maybe a)] Source #

(prev,cur,next) triples.

pcn_triples [1..3] == [(Nothing,1,Just 2),(Just 1,2,Just 3),(Just 2,3,Nothing)]

sep_first :: [t] -> Maybe (t, [t]) Source #

Separate first list element.

sep_first "astring" == Just ('a',"string")

sep_last :: [t] -> Maybe ([t], t) Source #

Separate last list element.

sep_last "stringb" == Just ("string",'b')

equal_length_p :: [[a]] -> Bool Source #

Are lists of equal length?

equal_length_p ["t1","t2"] == True
equal_length_p ["t","t1","t2"] == False

histogram :: Ord a => [a] -> [(a, Int)] Source #

Histogram

at_with_error_message :: String -> [t] -> Int -> t Source #

!! with localised error message

concat_intersperse :: [a] -> [[a]] -> [a] Source #

concat of intersperse. This is the same function as intercalate, which hugs doesn't know of.

list_split_at_elem :: Eq t => t -> [t] -> [[t]] Source #

Similar to Data.List.Split.splitOn, which however hugs doesn't know of.

list_split_at_elem ' ' "a sequence of words" == ["a","sequence","of","words"]

sort_on :: Ord b => (a -> b) -> [a] -> [a] Source #

Data.List.sortOn, which however hugs does not know of.

sort_on snd [('a',1),('b',0)] == [('b',0),('a',1)]

insertBy_post :: (a -> a -> Ordering) -> a -> [a] -> [a] Source #

Inserts at the first position where it compares less but not equal to the next element.

import Data.Function 
insertBy (compare `on` fst) (3,'x') (zip [1..5] ['a'..])
insertBy_post (compare `on` fst) (3,'x') (zip [1..5] ['a'..])

insert_post :: Ord t => t -> [t] -> [t] Source #

at_last :: (a -> b) -> (a -> b) -> [a] -> [b] Source #

Apply f at all but last element, and g at last element.

at_last (* 2) negate [1..4] == [2,4,6,-4]

Tuples

p4_zip :: (a, b, c, d) -> (e, f, g, h) -> ((a, e), (b, f), (c, g), (d, h)) Source #

Zip two 4-tuples.

type T2 a = (a, a) Source #

Two-tuple.

type T3 a = (a, a, a) Source #

Three-tuple.

type T4 a = (a, a, a, a) Source #

Four-tuple.

dup2 :: t -> T2 t Source #

t -> (t,t)

dup3 :: t -> T3 t Source #

t -> (t,t,t)

dup4 :: t -> T4 t Source #

t -> (t,t,t,t)

mk_duples :: (a -> c) -> (b -> c) -> [(a, b)] -> [c] Source #

concatMap of f at x and g at y.

mk_duples_l :: (Int -> c) -> (a -> c) -> (b -> c) -> [(a, [b])] -> [c] Source #

Length prefixed list variant of mk_duples.

mk_triples :: (a -> d) -> (b -> d) -> (c -> d) -> [(a, b, c)] -> [d] Source #

concatMap of f at x and g at y and h at z.

t2_from_list :: [t] -> T2 t Source #

x,y
-> (x,y)

t3_from_list :: [t] -> (t, t, t) Source #

x,y,z
-> (x,y,z)