Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Common core functions.
Synopsis
- type Fn1 a b = a -> b
- type Fn2 a b c = a -> b -> c
- type Fn3 a b c d = a -> b -> c -> d
- type Fn4 a b c d e = a -> b -> c -> d -> e
- type Fn5 a b c d e f = a -> b -> c -> d -> e -> f
- type Fn6 a b c d e f g = a -> b -> c -> d -> e -> f -> g
- type Fn10 a b c d e f g h i j k = a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k
- 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
- iter :: Int -> (a -> a) -> a -> a
- fvoid :: Functor f => f a -> f ()
- reads_exact :: Read a => String -> Maybe a
- string_split_at_char :: Char -> String -> [String]
- data Case_Rule
- string_op :: (String -> String -> t) -> Case_Rule -> String -> String -> t
- string_eq :: Case_Rule -> String -> String -> Bool
- string_cmp :: Case_Rule -> String -> String -> Ordering
- rlookup_str :: Case_Rule -> String -> [(a, String)] -> Maybe a
- parse_enum :: (Show t, Enum t, Bounded t) => Case_Rule -> String -> Maybe t
- compose_l :: [t -> t] -> t -> t
- compose_r :: [t -> t] -> t -> t
- d_dx :: Num a => [a] -> [a]
- d_dx' :: Num n => [n] -> [n]
- dx_d :: Num n => [n] -> [n]
- dx_d' :: Num n => [n] -> [n]
- lookup_by :: (a -> t -> Bool) -> a -> [(t, b)] -> Maybe b
- lookup_by_note :: String -> (a -> t -> Bool) -> a -> [(t, b)] -> b
- lookup_by_err :: (a -> t -> Bool) -> a -> [(t, b)] -> b
- rlookup_by :: (b -> b -> Bool) -> b -> [(a, b)] -> Maybe a
- pcn_triples :: [a] -> [(Maybe a, a, Maybe a)]
- sep_first :: [t] -> Maybe (t, [t])
- sep_last :: [t] -> Maybe ([t], t)
- equal_length_p :: [[a]] -> Bool
- histogram :: Ord a => [a] -> [(a, Int)]
- at_with_error_message :: String -> [t] -> Int -> t
- concat_intersperse :: [a] -> [[a]] -> [a]
- list_split_at_elem :: Eq t => t -> [t] -> [[t]]
- sort_on :: Ord b => (a -> b) -> [a] -> [a]
- insertBy_post :: (a -> a -> Ordering) -> a -> [a] -> [a]
- insert_post :: Ord t => t -> [t] -> [t]
- at_last :: (a -> b) -> (a -> b) -> [a] -> [b]
- p4_zip :: (a, b, c, d) -> (e, f, g, h) -> ((a, e), (b, f), (c, g), (d, h))
- type T2 a = (a, a)
- type T3 a = (a, a, a)
- type T4 a = (a, a, a, a)
- dup2 :: t -> T2 t
- dup3 :: t -> T3 t
- dup4 :: t -> T4 t
- mk_duples :: (a -> c) -> (b -> c) -> [(a, b)] -> [c]
- mk_duples_l :: (Int -> c) -> (a -> c) -> (b -> c) -> [(a, [b])] -> [c]
- mk_triples :: (a -> d) -> (b -> d) -> (c -> d) -> [(a, b, c)] -> [d]
- t2_from_list :: [t] -> T2 t
- t3_from_list :: [t] -> (t, t, t)
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
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
Ci = Case insensitive, Cs = case sensitive, Sci = separator & case insensitive
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
rlookup_str :: Case_Rule -> String -> [(a, String)] -> Maybe a Source #
rlookup_by
of string_eq
.
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]
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.0]
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,0.5,1.0]
lookup_by_note :: String -> (a -> t -> Bool) -> a -> [(t, b)] -> b Source #
Erroring variant, with message.
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
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'..])
[(1,'a'),(2,'b'),(3,'x'),(3,'c'),(4,'d'),(5,'e')]
>>>
insertBy_post (compare `on` fst) (3,'x') (zip [1..5] ['a'..])
[(1,'a'),(2,'b'),(3,'c'),(3,'x'),(4,'d'),(5,'e')]
insert_post :: Ord t => t -> [t] -> [t] Source #
insertBy_post
using compare
.
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.
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)