-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Various small helper functions for Lists, Maybes, Tuples, Functions -- -- Various small helper functions for Lists, Maybes, Tuples, Functions. -- Some of these functions are improved implementations of standard -- functions. They have the same name as their standard counterparts. The -- package only contains functions that do not require packages other -- than the base package. Thus you do not risk a dependency avalanche by -- importing it. However, further splitting the base package might -- invalidate this statement. @package utility-ht @version 0.0.5.1 module Text.Show.HT -- | Show a value using an infix operator. showsInfixPrec :: (Show a, Show b) => String -> Int -> Int -> a -> b -> ShowS module Text.Read.HT -- | Parse a string containing an infix operator. readsInfixPrec :: (Read a, Read b) => String -> Int -> Int -> (a -> b -> c) -> ReadS c -- | Compose two parsers sequentially. (.>) :: ReadS (b -> c) -> ReadS b -> ReadS c readMany :: Read a => String -> [a] maybeRead :: Read a => String -> Maybe a module Data.Strictness.HT arguments1 :: (a -> x) -> a -> x arguments2 :: (a -> b -> x) -> a -> b -> x arguments3 :: (a -> b -> c -> x) -> a -> b -> c -> x arguments4 :: (a -> b -> c -> d -> x) -> a -> b -> c -> d -> x arguments5 :: (a -> b -> c -> d -> e -> x) -> a -> b -> c -> d -> e -> x module Control.Monad.HT -- | Also present in newer versions of the base package. (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> (a -> m c) -- | Monadic List.repeat. repeat :: Monad m => m a -> m [a] -- | repeat action until result fulfills condition untilM :: Monad m => (a -> Bool) -> m a -> m a until :: Monad m => (a -> Bool) -> m a -> m a -- | parameter order equal to that of nest iterateLimitM :: Monad m => Int -> (a -> m a) -> a -> m [a] iterateLimit :: Monad m => Int -> (a -> m a) -> a -> m [a] -- | Lazy monadic conjunction. That is, when the first action returns -- False, then False is immediately returned, without -- running the second action. andLazy :: Monad m => m Bool -> m Bool -> m Bool -- | Lazy monadic disjunction. That is, when the first action returns -- True, then True is immediately returned, without -- running the second action. orLazy :: Monad m => m Bool -> m Bool -> m Bool module Data.Tuple.HT -- | Cf. '(Control.Arrow.***)'. -- -- Apply two functions on corresponding values in a pair, where the -- pattern match on the pair constructor is lazy. This is crucial in -- recursions such as the of partition. mapPair :: (a -> c, b -> d) -> (a, b) -> (c, d) -- | Control.Arrow.first mapFst :: (a -> c) -> (a, b) -> (c, b) -- | Control.Arrow.second mapSnd :: (b -> c) -> (a, b) -> (a, c) swap :: (a, b) -> (b, a) forcePair :: (a, b) -> (a, b) fst3 :: (a, b, c) -> a snd3 :: (a, b, c) -> b thd3 :: (a, b, c) -> c curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d uncurry3 :: (a -> b -> c -> d) -> ((a, b, c) -> d) module Data.Maybe.HT -- | Returns Just if the precondition is fulfilled. toMaybe :: Bool -> a -> Maybe a -- | This is an infix version of fmap for writing -- Data.Bool.HT.select style expressions using test functions, -- that produce Maybes. -- -- The precedence is chosen to be higher than '(:)', in order to allow: -- --
-- alternatives default $ -- checkForA ?-> (\a -> f a) : -- checkForB ?-> (\b -> g b) : -- [] ---- -- The operation is left associative in order to allow to write -- --
-- checkForA ?-> f ?-> g ---- -- which is equivalent to -- --
-- checkForA ?-> g . f ---- -- due to the functor law. (?->) :: Maybe a -> (a -> b) -> Maybe b alternatives :: a -> [Maybe a] -> a module Data.Function.HT nest :: Int -> (a -> a) -> a -> a powerAssociative :: (a -> a -> a) -> a -> a -> Integer -> a -- | Known as on in newer versions of the base package. compose2 :: (b -> b -> c) -> (a -> b) -> (a -> a -> c) -- | Variant of Data.List functions like Data.List.group, -- Data.List.sort where the comparison is performed on a key -- computed from the list elements. In principle these functions could be -- replaced by e.g. sortBy (compare on f), but -- f will be re-computed for every comparison. If the evaluation -- of f is expensive, our functions are better, since they -- buffer the results of f. module Data.List.Key nub :: Eq b => (a -> b) -> [a] -> [a] sort :: Ord b => (a -> b) -> [a] -> [a] -- | argmin minimum :: Ord b => (a -> b) -> [a] -> a -- | argmax maximum :: Ord b => (a -> b) -> [a] -> a -- | Divides a list into sublists such that the members in a sublist share -- the same key. It uses semantics of Data.List.HT.groupBy, not -- that of Data.List.groupBy. group :: Eq b => (a -> b) -> [a] -> [[a]] merge :: Ord b => (a -> b) -> [a] -> [a] -> [a] module Data.Ord.HT comparing :: Ord b => (a -> b) -> a -> a -> Ordering -- | limit (lower,upper) x restricts x to the range from -- lower to upper. Don't expect a sensible result for -- lower>upper. limit :: Ord a => (a, a) -> a -> a -- | limit (lower,upper) x checks whether x is in the -- range from lower to upper. Don't expect a sensible -- result for lower>upper. inRange :: Ord a => (a, a) -> a -> Bool module Data.Eq.HT equating :: Eq b => (a -> b) -> a -> a -> Bool module Data.Bool.HT -- | if-then-else as function. -- -- Example: -- --
-- if' (even n) "even" $ -- if' (isPrime n) "prime" $ -- "boring" --if' :: Bool -> a -> a -> a select :: a -> [(Bool, a)] -> a -- | Like the ? operator of the C progamming language. Example: -- bool ?: (yes, no). (?:) :: Bool -> (a, a) -> a -- | Logical operator for implication. -- -- Funnily because of the ordering of Bool it holds implies == -- (<=). implies :: Bool -> Bool -> Bool module Data.List.HT -- | This function is lazier than the one suggested in the Haskell 98 -- report. It is inits undefined = [] : undefined, in contrast -- to Data.List.inits undefined = undefined. inits :: [a] -> [[a]] -- | This function is lazier than the one suggested in the Haskell 98 -- report. It is tails undefined = ([] : undefined) : undefined, -- in contrast to Data.List.tails undefined = undefined. tails :: [a] -> [[a]] -- | This function compares adjacent elements of a list. If two adjacent -- elements satisfy a relation then they are put into the same sublist. -- Example: -- --
-- groupBy (<) "abcdebcdef" == ["abcde","bcdef"] ---- -- In contrast to that Data.List.groupBy compares the head of -- each sublist with each candidate for this sublist. This yields -- --
-- List.groupBy (<) "abcdebcdef" == ["abcdebcdef"] ---- -- The second b is compared with the leading -- a. Thus it is put into the same sublist as -- a. -- -- The sublists are never empty. Thus the more precise result type would -- be [(a,[a])]. groupBy :: (a -> a -> Bool) -> [a] -> [[a]] group :: Eq a => [a] -> [[a]] -- | Like standard unzip but more lazy. It is Data.List.unzip -- undefined == undefined, but unzip undefined == (undefined, -- undefined). unzip :: [(a, b)] -> ([a], [b]) -- | Data.List.partition of GHC 6.2.1 fails on infinite lists. But -- this one does not. partition :: (a -> Bool) -> [a] -> ([a], [a]) span :: (a -> Bool) -> [a] -> ([a], [a]) -- | It is Data.List.span f undefined = undefined, whereas -- span f undefined = (undefined, undefined). break :: (a -> Bool) -> [a] -> ([a], [a]) -- | Split the list at the occurrences of a separator into sub-lists. -- Remove the separators. This is a generalization of words. chop :: (a -> Bool) -> [a] -> [[a]] -- | Like break, but splits after the matching element. breakAfter :: (a -> Bool) -> [a] -> ([a], [a]) -- | Split the list after each occurence of a terminator. Keep the -- terminator. There is always a list for the part after the last -- terminator. It may be empty. segmentAfter :: (a -> Bool) -> [a] -> [[a]] -- | Split the list before each occurence of a leading character. Keep -- these characters. There is always a list for the part before the first -- leading character. It may be empty. segmentBefore :: (a -> Bool) -> [a] -> [[a]] -- | removeEach xs represents a list of sublists of xs, -- where each element of xs is removed and the removed element -- is separated. It seems to be much simpler to achieve with zip xs -- (map (flip List.delete xs) xs), but the implementation of -- removeEach does not need the Eq instance and thus can -- also be used for lists of functions. removeEach :: [a] -> [(a, [a])] splitEverywhere :: [a] -> [([a], a, [a])] -- | It holds splitLast xs == (init xs, last xs), but -- splitLast is more efficient if the last element is accessed -- after the initial ones, because it avoids memoizing list. splitLast :: [a] -> ([a], a) -- | Should be prefered to head and tail. viewL :: [a] -> Maybe (a, [a]) -- | Should be prefered to init and last. viewR :: [a] -> Maybe ([a], a) -- | Should be prefered to head and tail. switchL :: b -> (a -> [a] -> b) -> [a] -> b -- | Should be prefered to init and last. switchR :: b -> ([a] -> a -> b) -> [a] -> b -- | Remove the longest suffix of elements satisfying p. In contrast to -- reverse . dropWhile p . reverse this works for infinite -- lists, too. dropWhileRev :: (a -> Bool) -> [a] -> [a] -- | Alternative version of reverse . takeWhile p . reverse. takeWhileRev :: (a -> Bool) -> [a] -> [a] -- | maybePrefixOf xs ys is Just zs if xs is a -- prefix of ys, where zs is ys without the -- prefix xs. Otherwise it is Nothing. maybePrefixOf :: Eq a => [a] -> [a] -> Maybe [a] -- | Partition a list into elements which evaluate to Just or -- Nothing by f. -- -- It holds mapMaybe f == fst . partitionMaybe f and -- partition p == partitionMaybe ( x -> toMaybe (p x) x). partitionMaybe :: (a -> Maybe b) -> [a] -> ([b], [a]) -- | This is the cousin of takeWhile analogously to catMaybes -- being the cousin of filter. -- -- Example: Keep the heads of sublists until an empty list occurs. -- --
-- takeWhileJust $ map (fmap fst . viewL) xs --takeWhileJust :: [Maybe a] -> [a] unzipEithers :: [Either a b] -> ([a], [b]) sieve :: Int -> [a] -> [a] sliceHorizontal :: Int -> [a] -> [[a]] sliceVertical :: Int -> [a] -> [[a]] search :: Eq a => [a] -> [a] -> [Int] replace :: Eq a => [a] -> [a] -> [a] -> [a] multiReplace :: Eq a => [([a], [a])] -> [a] -> [a] -- | Transform -- --
-- [[00,01,02,...], [[00], -- [10,11,12,...], --> [10,01], -- [20,21,22,...], [20,11,02], -- ...] ...] ---- -- With concat . shear you can perform a Cantor diagonalization, -- that is an enumeration of all elements of the sub-lists where each -- element is reachable within a finite number of steps. It is also -- useful for polynomial multiplication (convolution). shear :: [[a]] -> [[a]] -- | Transform -- --
-- [[00,01,02,...], [[00], -- [10,11,12,...], --> [01,10], -- [20,21,22,...], [02,11,20], -- ...] ...] ---- -- It's like shear but the order of elements in the sub list is -- reversed. Its implementation seems to be more efficient than that of -- shear. If the order does not matter, better choose -- shearTranspose. shearTranspose :: [[a]] -> [[a]] -- | Operate on each combination of elements of the first and the second -- list. In contrast to the list instance of Monad.liftM2 in -- holds the results in a list of lists. It holds concat -- (outerProduct f xs ys) == liftM2 f xs ys outerProduct :: (a -> b -> c) -> [a] -> [b] -> [[c]] -- | Take while first predicate holds, then continue taking while second -- predicate holds, and so on. takeWhileMulti :: [a -> Bool] -> [a] -> [a] rotate :: Int -> [a] -> [a] -- | Given two lists that are ordered (i.e. p x y holds for -- subsequent x and y) mergeBy them into a list -- that is ordered, again. mergeBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] allEqual :: Eq a => [a] -> Bool isAscending :: Ord a => [a] -> Bool isAscendingLazy :: Ord a => [a] -> [Bool] -- | This function combines every pair of neighbour elements in a list with -- a certain function. mapAdjacent :: (a -> a -> b) -> [a] -> [b] -- | Enumerate without Enum context. For Enum equivalent to enumFrom. range :: Num a => Int -> [a] padLeft :: a -> Int -> [a] -> [a] padRight :: a -> Int -> [a] -> [a] -- | For an associative operation op this computes -- iterateAssociative op a = iterate (op a) a but it is even -- faster than map (powerAssociative op a a) [0..] since it -- shares temporary results. -- -- The idea is: From the list map (powerAssociative op a a) -- [0,(2*n)..] we compute the list map (powerAssociative op a a) -- [0,n..], and iterate that until n==1. iterateAssociative :: (a -> a -> a) -> a -> [a] -- | This is equal to iterateAssociative. The idea is the following: -- The list we search is the fixpoint of the function: Square all -- elements of the list, then spread it and fill the holes with -- successive numbers of their left neighbour. This also preserves -- log n applications per value. However it has a space leak, because for -- the value with index n all elements starting at div n -- 2 must be kept. iterateLeaky :: (a -> a -> a) -> a -> [a] module Data.Record.HT -- | Lexicographically compare a list of attributes of two records. -- -- Example: -- --
-- compare [comparing fst, comparing snd] --compare :: [a -> a -> Ordering] -> a -> a -> Ordering -- | Check whether a selected set of fields of two records is equal. -- -- Example: -- --
-- equal [equating fst, equating snd] --equal :: [a -> a -> Bool] -> a -> a -> Bool module Data.String.HT -- | remove leading and trailing spaces trim :: String -> String module Data.List.Match -- | Make a list as long as another one take :: [b] -> [a] -> [a] -- | Drop as many elements as the first list is long drop :: [b] -> [a] -> [a] splitAt :: [b] -> [a] -> ([a], [a]) replicate :: [a] -> b -> [b] -- | Compare the length of two lists over different types. It is equivalent -- to (compare (length xs) (length ys)) but more efficient. compareLength :: [a] -> [b] -> Ordering -- | lessOrEqualLength x y is almost the same as compareLength -- x y <= EQ, but lessOrEqualLength [] undefined = True, -- whereas compareLength [] undefined <= EQ = undefined. lessOrEqualLength :: [a] -> [b] -> Bool -- | Returns the shorter one of two lists. It works also for infinite lists -- as much as possible. E.g. shortList (shorterList (repeat 1) -- (repeat 2)) [1,2,3] can be computed. The trick is, that the -- skeleton of the resulting list is constructed using zipWith -- without touching the elements. The contents is then computed (only) if -- requested. shorterList :: [a] -> [a] -> [a]