Maintainer | Simon Meier <iridcode@gmail.com> |
---|---|
Safe Haskell | Safe-Infered |
Functions that could/should have made it into the Prelude or one of the base libraries
- implies :: Bool -> Bool -> Bool
- singleton :: a -> [a]
- unique :: Eq a => [a] -> Bool
- sortednub :: Ord a => [a] -> [a]
- sortednubBy :: (a -> a -> Ordering) -> [a] -> [a]
- sortednubOn :: Ord b => (a -> b) -> [a] -> [a]
- nubOn :: Eq b => (a -> b) -> [a] -> [a]
- groupOn :: Eq b => (a -> b) -> [a] -> [[a]]
- sortOn :: Ord b => (a -> b) -> [a] -> [a]
- sortOnMemo :: Ord b => (a -> b) -> [a] -> [a]
- groupSortOn :: Ord b => (a -> b) -> [a] -> [[a]]
- eqClasses :: (Eq b, Ord b) => (a -> b) -> [a] -> [[a]]
- eqClassesBy :: (b -> b -> Ordering) -> (a -> b) -> [a] -> [[a]]
- splitBy :: (a -> Bool) -> [a] -> [[a]]
- choose :: Int -> [a] -> [[a]]
- leaveOneOut :: [a] -> [[a]]
- keepFirst :: (a -> a -> Bool) -> [a] -> [a]
- swap :: (a, b) -> (b, a)
- sortPair :: Ord a => (a, a) -> (a, a)
- isRight :: Either a b -> Bool
- isLeft :: Either a b -> Bool
- type Named a = (String, a)
- flushRightBy :: [a] -> Int -> [a] -> [a]
- flushRight :: Int -> String -> String
- flushLeftBy :: [a] -> Int -> [a] -> [a]
- flushLeft :: Int -> String -> String
- warning :: String -> String
- putErr :: String -> IO ()
- putErrLn :: String -> IO ()
- oneOfList :: Alternative f => [a] -> f a
- oneOfSet :: Alternative f => Set a -> f a
- oneOfMap :: Alternative f => Map k v -> f (k, v)
- ifM :: Monad m => m Bool -> m a -> m a -> m a
- errorFree :: MonadPlus m => [m a] -> m [a]
- errorFree1 :: MonadPlus m => [m a] -> m [a]
- unreachable :: String -> a
Documentation
sortednubBy :: (a -> a -> Ordering) -> [a] -> [a]Source
Sort a list according to a user-defined comparison function and remove duplicates.
sortednubOn :: Ord b => (a -> b) -> [a] -> [a]Source
O(n*log n). Sort list and remove duplicates with respect to a projection.
nubOn :: Eq b => (a -> b) -> [a] -> [a]Source
Keep only the first element of elements having the same projected value
sortOnMemo :: Ord b => (a -> b) -> [a] -> [a]Source
sort on a projection of the data to sort, memorizing the results of the projection in order to avoid recomputation.
groupSortOn :: Ord b => (a -> b) -> [a] -> [[a]]Source
sort and group on a projection
eqClasses :: (Eq b, Ord b) => (a -> b) -> [a] -> [[a]]Source
partition the given set into equality classes with respect to the representative given by the projection function
eqClassesBy :: (b -> b -> Ordering) -> (a -> b) -> [a] -> [[a]]Source
splitBy :: (a -> Bool) -> [a] -> [[a]]Source
split a list into sublists whenever the predicate identifies an element as a separator. Note that the separator is not retained and a separator at the very end is ignored.
choose :: Int -> [a] -> [[a]]Source
the list of all permutations of a given list permutations :: [a] -> [[a]] permutations [] = [[]] permutations zs = aux zs [] where aux [] _ = [] aux (x:xs) ys = [x:p | p <- permutations (xs++ys)] ++ aux xs (x:ys)
the list of all combinations of n elements of a list. E.g. choose 2 [1,2,3] = [[1,2],[1,3],[2,3]]
leaveOneOut :: [a] -> [[a]]Source
build the list of lists each leaving another element out. (From left to right)
keepFirst :: (a -> a -> Bool) -> [a] -> [a]Source
An element masks another element if the predicate is true. This function keeps only the elements not masked by a previous element in the list.
swap :: (a, b) -> (b, a)Source
These functions were inspired by the ML library accompanying the Isabelle theorem prover (http://isabelle.in.tum.de/)
swap the elements of a pair
flushRightBy :: [a] -> Int -> [a] -> [a]Source
Extend a list with the given separators to be flushed right.
flushRight :: Int -> String -> StringSource
Extend a string with spaces to be flushed right.
flushLeftBy :: [a] -> Int -> [a] -> [a]Source
Extend a list with the given separators to be flushed left.
oneOfList :: Alternative f => [a] -> f aSource
Inject the elements of a list as alternatives.
oneOfSet :: Alternative f => Set a -> f aSource
Inject the elements of a set as alternatives.
oneOfMap :: Alternative f => Map k v -> f (k, v)Source
Inject the elements of a map as alternatives.
errorFree1 :: MonadPlus m => [m a] -> m [a]Source
Gather all error free computations and ensure that at least one was error free.
unreachable :: String -> aSource
Mark a part of the code as unreachable.