Copyright | 2013-2016 Franz-Benjamin Mocnik |
---|---|
License | MIT |
Maintainer | mail@mocnik-science.net |
Stability | stable |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
- (.*) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
- (.**) :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e
- (.***) :: (e -> f) -> (a -> b -> c -> d -> e) -> a -> b -> c -> d -> f
- curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d
- uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
- curry4 :: ((a, b, c, d) -> e) -> a -> b -> c -> d -> e
- uncurry4 :: (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
- curry5 :: ((a, b, c, d, e) -> f) -> a -> b -> c -> d -> e -> f
- uncurry5 :: (a -> b -> c -> d -> e -> f) -> (a, b, c, d, e) -> f
- appendFst :: a -> b -> (a, b)
- appendSnd :: b -> a -> (a, b)
- appendFst3 :: a -> (b, c) -> (a, b, c)
- appendSnd3 :: b -> (a, c) -> (a, b, c)
- appendThd3 :: c -> (a, b) -> (a, b, c)
- removeFst3 :: (a, b, c) -> (b, c)
- removeSnd3 :: (a, b, c) -> (a, c)
- removeThd3 :: (a, b, c) -> (a, b)
- appendFst4 :: a -> (b, c, d) -> (a, b, c, d)
- appendSnd4 :: b -> (a, c, d) -> (a, b, c, d)
- appendThd4 :: c -> (a, b, d) -> (a, b, c, d)
- appendFth4 :: d -> (a, b, c) -> (a, b, c, d)
- removeFst4 :: (a, b, c, d) -> (b, c, d)
- removeSnd4 :: (a, b, c, d) -> (a, c, d)
- removeThd4 :: (a, b, c, d) -> (a, b, d)
- removeFth4 :: (a, b, c, d) -> (a, b, c)
- appendFst5 :: a -> (b, c, d, e) -> (a, b, c, d, e)
- appendSnd5 :: b -> (a, c, d, e) -> (a, b, c, d, e)
- appendThd5 :: c -> (a, b, d, e) -> (a, b, c, d, e)
- appendFourth5 :: d -> (a, b, c, e) -> (a, b, c, d, e)
- appendFifth5 :: e -> (a, b, c, d) -> (a, b, c, d, e)
- removeFst5 :: (a, b, c, d, e) -> (b, c, d, e)
- removeSnd5 :: (a, b, c, d, e) -> (a, c, d, e)
- removeThd5 :: (a, b, c, d, e) -> (a, b, d, e)
- removeFourth5 :: (a, b, c, d, e) -> (a, b, c, e)
- removeFifth5 :: (a, b, c, d, e) -> (a, b, c, d)
- make2 :: a -> (a, a)
- make3 :: a -> (a, a, a)
- make4 :: a -> (a, a, a, a)
- make5 :: a -> (a, a, a, a, a)
- fst3 :: (a, b, c) -> a
- snd3 :: (a, b, c) -> b
- thd3 :: (a, b, c) -> c
- fst4 :: (a, b, c, d) -> a
- snd4 :: (a, b, c, d) -> b
- thd4 :: (a, b, c, d) -> c
- fth4 :: (a, b, c, d) -> d
- fst5 :: (a, b, c, d, e) -> a
- snd5 :: (a, b, c, d, e) -> b
- thd5 :: (a, b, c, d, e) -> c
- fourth5 :: (a, b, c, d, e) -> d
- fifth5 :: (a, b, c, d, e) -> e
- tupleToList2 :: (a, a) -> [a]
- listToTuple2 :: [a] -> Maybe (a, a)
- tupleToList3 :: (a, a, a) -> [a]
- listToTuple3 :: [a] -> Maybe (a, a, a)
- tupleToList4 :: (a, a, a, a) -> [a]
- listToTuple4 :: [a] -> Maybe (a, a, a, a)
- tupleToList5 :: (a, a, a, a, a) -> [a]
- listToTuple5 :: [a] -> Maybe (a, a, a, a, a)
- map12 :: (a -> a') -> (a, a) -> (a', a')
- map21 :: (a -> a', a -> a'') -> a -> (a', a'')
- map22 :: (a -> a', b -> b') -> (a, b) -> (a', b')
- map13 :: (a -> a') -> (a, a, a) -> (a', a', a')
- map31 :: (a -> a', a -> a'', a -> a''') -> a -> (a', a'', a''')
- map33 :: (a -> a', b -> b', c -> c') -> (a, b, c) -> (a', b', c')
- map14 :: (a -> a') -> (a, a, a, a) -> (a', a', a', a')
- map41 :: (a -> a', a -> a'', a -> a''', a -> a'''') -> a -> (a', a'', a''', a'''')
- map44 :: (a -> a', b -> b', c -> c', d -> d') -> (a, b, c, d) -> (a', b', c', d')
- map15 :: (a -> a') -> (a, a, a, a, a) -> (a', a', a', a', a')
- map51 :: (a -> a', a -> a'', a -> a''', a -> a'''', a -> a''''') -> a -> (a', a'', a''', a'''', a''''')
- map55 :: (a -> a', b -> b', c -> c', d -> d', e -> e') -> (a, b, c, d, e) -> (a', b', c', d', e')
- mapFst :: (a -> a') -> (a, b) -> (a', b)
- mapSnd :: (b -> b') -> (a, b) -> (a, b')
- sequence2 :: (Functor m, Monad m) => (m a, m a) -> m (a, a)
- (<<) :: Monad m => m b -> m a -> m b
- compareUsing :: Eq a => [a] -> a -> a -> Ordering
- vanishes :: (Num a, Eq a) => a -> Bool
- equaling :: Eq b => (a -> b) -> a -> a -> Bool
- sortAndGroup :: Ord a => [a] -> [[a]]
- sortAndGroupBy :: Ord b => (a -> b) -> [a] -> [[a]]
- sortAndGroupLookupBy :: Ord b => (a -> b) -> [a] -> [(b, [a])]
- notNull :: [a] -> Bool
- takeWhileList :: ([a] -> Bool) -> [a] -> [a]
- takeUntilList :: ([a] -> Bool) -> [a] -> [a]
- takeToFirst :: (a -> Bool) -> [a] -> [a]
- splitOnFirst :: Eq a => a -> [a] -> ([a], Maybe [a])
- nubOrd :: Ord a => [a] -> [a]
- nubOrdBy' :: Ord b => (a -> b) -> [a] -> [a]
- zipWithDefault :: a -> (a -> a -> c) -> [a] -> [a] -> [c]
- subset :: Eq a => [a] -> [a] -> Bool
- subsets :: [a] -> [[a]]
- findIndicesTuples :: (a -> Bool) -> [a] -> [([a], Int)]
- replaceInList :: Int -> [a] -> [a] -> [a]
- replaceElementInList :: Eq a => a -> [a] -> [a] -> [a]
- removeFromList :: Int -> [a] -> [a]
- stripPostfix :: Eq a => [a] -> [a] -> Maybe [a]
- applyToList :: Int -> (a -> a) -> [a] -> [a]
- mapFoldl :: (Maybe c -> a -> (c, b)) -> [a] -> [b]
- reverseMap :: [a -> b] -> a -> [b]
- count :: (a -> Bool) -> [a] -> Int
- deleteAll :: Eq a => a -> [a] -> [a]
- deleteAlls :: Eq a => [a] -> [a] -> [a]
- cartesian :: [a] -> [b] -> [(a, b)]
- xor :: Bool -> Bool -> Bool
- xnor :: Bool -> Bool -> Bool
- average :: [Double] -> Double
- justifyLeft :: Int -> Char -> String -> String
- justifyRight :: Int -> Char -> String -> String
- mapJust :: (a -> b) -> Maybe a -> Maybe b
- onJustUse :: (a -> b -> b) -> Maybe a -> b -> b
- mapLeft :: (a -> c) -> Either a b -> Either c b
- mapRight :: (b -> c) -> Either a b -> Either a c
- fromLeft :: Either a b -> a
- fromRight :: Either a b -> b
- data Either3 a b c
Applicative
(.**) :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e infixr 8 Source
f . g a b $ c = (f .** g) a b c
(.***) :: (e -> f) -> (a -> b -> c -> d -> e) -> a -> b -> c -> d -> f infixr 8 Source
f . g a b c $ d = (f .** g) a b c d
Tuples
Generating Tuples
appendFst3 :: a -> (b, c) -> (a, b, c) Source
append a first argument for making a 3-tuple
appendSnd3 :: b -> (a, c) -> (a, b, c) Source
append a second argument for making a 3-tuple
appendThd3 :: c -> (a, b) -> (a, b, c) Source
append a third argument for making a 3-tuple
removeFst3 :: (a, b, c) -> (b, c) Source
remove first argument of a 3-tuple
removeSnd3 :: (a, b, c) -> (a, c) Source
remove second argument of a 3-tuple
removeThd3 :: (a, b, c) -> (a, b) Source
remove third argument of a 3-tuple
appendFst4 :: a -> (b, c, d) -> (a, b, c, d) Source
append a first argument for making a 4-tuple
appendSnd4 :: b -> (a, c, d) -> (a, b, c, d) Source
append a second argument for making a 4-tuple
appendThd4 :: c -> (a, b, d) -> (a, b, c, d) Source
append a third argument for making a 4-tuple
appendFth4 :: d -> (a, b, c) -> (a, b, c, d) Source
append a fourth argument for making a 4-tuple
removeFst4 :: (a, b, c, d) -> (b, c, d) Source
remove first argument of a 4-tuple
removeSnd4 :: (a, b, c, d) -> (a, c, d) Source
remove second argument of a 4-tuple
removeThd4 :: (a, b, c, d) -> (a, b, d) Source
remove third argument of a 4-tuple
removeFth4 :: (a, b, c, d) -> (a, b, c) Source
remove fourth argument of a 4-tuple
appendFst5 :: a -> (b, c, d, e) -> (a, b, c, d, e) Source
append a first argument for making a 5-tuple
appendSnd5 :: b -> (a, c, d, e) -> (a, b, c, d, e) Source
append a second argument for making a 5-tuple
appendThd5 :: c -> (a, b, d, e) -> (a, b, c, d, e) Source
append a third argument for making a 5-tuple
appendFourth5 :: d -> (a, b, c, e) -> (a, b, c, d, e) Source
append a fourth argument for making a 5-tuple
appendFifth5 :: e -> (a, b, c, d) -> (a, b, c, d, e) Source
append a fifth argument for making a 5-tuple
removeFst5 :: (a, b, c, d, e) -> (b, c, d, e) Source
remove first argument of a 5-tuple
removeSnd5 :: (a, b, c, d, e) -> (a, c, d, e) Source
remove second argument of a 5-tuple
removeThd5 :: (a, b, c, d, e) -> (a, b, d, e) Source
remove third argument of a 5-tuple
removeFourth5 :: (a, b, c, d, e) -> (a, b, c, e) Source
remove fourth argument of a 5-tuple
removeFifth5 :: (a, b, c, d, e) -> (a, b, c, d) Source
remove fifth argument of a 5-tuple
Retrieving the Tuples' Components
Modifying Tuples
tupleToList2 :: (a, a) -> [a] Source
convert a 2-tuple to a list
listToTuple2 :: [a] -> Maybe (a, a) Source
convert a 2-tuple to a list
tupleToList3 :: (a, a, a) -> [a] Source
convert a 3-tuple to a list
listToTuple3 :: [a] -> Maybe (a, a, a) Source
convert a 3-tuple to a list
tupleToList4 :: (a, a, a, a) -> [a] Source
convert a 4-tuple to a list
listToTuple4 :: [a] -> Maybe (a, a, a, a) Source
convert a 4-tuple to a list
tupleToList5 :: (a, a, a, a, a) -> [a] Source
convert a 5-tuple to a list
listToTuple5 :: [a] -> Maybe (a, a, a, a, a) Source
convert a 5-tuple to a list
Applying Functions to Tuples
map31 :: (a -> a', a -> a'', a -> a''') -> a -> (a', a'', a''') Source
apply a 3-tuple of functions to a value
map33 :: (a -> a', b -> b', c -> c') -> (a, b, c) -> (a', b', c') Source
apply a 3-tuple of functions to a 3-tuple
map41 :: (a -> a', a -> a'', a -> a''', a -> a'''') -> a -> (a', a'', a''', a'''') Source
apply a 4-tuple of functions to a value
map44 :: (a -> a', b -> b', c -> c', d -> d') -> (a, b, c, d) -> (a', b', c', d') Source
apply a 4-tuple of functions to a 4-tuple
map51 :: (a -> a', a -> a'', a -> a''', a -> a'''', a -> a''''') -> a -> (a', a'', a''', a'''', a''''') Source
apply a 5-tuple of functions to a value
map55 :: (a -> a', b -> b', c -> c', d -> d', e -> e') -> (a, b, c, d, e) -> (a', b', c', d', e') Source
apply a 5-tuple of functions to a 5-tuple
Monads and Tuples
Ordering
compareUsing :: Eq a => [a] -> a -> a -> Ordering Source
compare function that uses the order in a given list
e.g. compareUsing [1,3,2]
will state 1 < 2
and 3 < 2
Comparing and Sorting
sortAndGroup :: Ord a => [a] -> [[a]] Source
sort and group
sortAndGroupBy :: Ord b => (a -> b) -> [a] -> [[a]] Source
sort and than group, non-overloaded version
sortAndGroupLookupBy :: Ord b => (a -> b) -> [a] -> [(b, [a])] Source
sort and than group to a lookup table
List Operations
takeWhileList :: ([a] -> Bool) -> [a] -> [a] Source
like takeWhile
but the function p
takes the whole list as argument
takeUntilList :: ([a] -> Bool) -> [a] -> [a] Source
similar takeWhileList
but returns the the sublist such that p
is met the first time
takeToFirst :: (a -> Bool) -> [a] -> [a] Source
takeToFirst
p xs
returns the suffix until (and inclusive) the first occurance where p xs
splitOnFirst :: Eq a => a -> [a] -> ([a], Maybe [a]) Source
like splitOn
but splits only at the first occurance
zipWithDefault :: a -> (a -> a -> c) -> [a] -> [a] -> [c] Source
like zipWith
but with a default value such that the resulting list is as long as the longest input list
subset :: Eq a => [a] -> [a] -> Bool Source
test whether the first list is a subset of the second one
findIndicesTuples :: (a -> Bool) -> [a] -> [([a], Int)] Source
like findIndices
but results a list of tuples (x, i) where x is the list and i the index
replaceInList :: Int -> [a] -> [a] -> [a] Source
replace the element at the given position by a given list of elements
for just removing the j-th element of a list, use the following function
replaceInList j []
for replacing the j-th element of a list by an element a
, use the following function
replaceInList j [a]
replaceElementInList :: Eq a => a -> [a] -> [a] -> [a] Source
replace all appearances of an element in a list by a given list of elements
removeFromList :: Int -> [a] -> [a] Source
remove the j-th element from a list
stripPostfix :: Eq a => [a] -> [a] -> Maybe [a] Source
like stripPrefix
but for postfixes
applyToList :: Int -> (a -> a) -> [a] -> [a] Source
apply a function to the element at the given position in a given list of elements
mapFoldl :: (Maybe c -> a -> (c, b)) -> [a] -> [b] Source
map a function f
to a list; the function results a result value b
as well as a value c
which can be used for the computation of the next element (i.e. the next f a
)
reverseMap :: [a -> b] -> a -> [b] Source
map an array of functions to a value
deleteAlls :: Eq a => [a] -> [a] -> [a] Source
delete all occurances of a sublist in a list
Boolean Operations
Number Operations
String Operations
justifyLeft :: Int -> Char -> String -> String Source
append a char as often as needed in order to return a string of given length where the given string ist justified left
justifyRight :: Int -> Char -> String -> String Source
append a char as often as needed in order to return a string of given length where the given string ist justified right
Maybe Operations
onJustUse :: (a -> b -> b) -> Maybe a -> b -> b Source
uses an endomorphism parametrised by a Just
value