Safe Haskell | None |
---|
CustomPrelude
Contents
- module BasicPrelude
- module Control.Monad.Loops
- (<&>) :: Monad m => m (a -> b) -> m a -> m b
- (<@>) :: Monad m => (a -> b) -> m a -> m b
- splitWhen :: (a -> Bool) -> [a] -> [[a]]
- splitOn :: Eq a => a -> [a] -> [[a]]
- foldlStrict :: (a -> b -> a) -> a -> [b] -> a
- foldlMaybe :: (a -> b -> Maybe a) -> a -> [b] -> a
- foldlStrictMaybe :: (a -> b -> Maybe a) -> a -> [b] -> a
- (.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
- oo :: (c -> d) -> (a -> b -> c) -> a -> b -> d
- ooo :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e
- oooo :: (e -> f) -> (a -> b -> c -> d -> e) -> a -> b -> c -> d -> f
- bool :: a -> a -> Bool -> a
- whileIterateM :: Monad m => (a -> m Bool) -> (a -> m a) -> a -> m a
- ifM :: Monad m => m Bool -> m a -> m a -> m a
- nextPowerOf2 :: Int -> Int
Documentation
module BasicPrelude
module Control.Monad.Loops
Applicative operators for monads
Splitting variants
splitWhen :: (a -> Bool) -> [a] -> [[a]]Source
Split lists at delimiter specified by a condition
Drops empty groups (similar to words
)
splitOn :: Eq a => a -> [a] -> [[a]]Source
Split lists at the specified delimiter
Drops empty groups (similar to words
)
Fold variants
foldlStrict :: (a -> b -> a) -> a -> [b] -> aSource
A Standard strict version of foldl
foldlMaybe :: (a -> b -> Maybe a) -> a -> [b] -> aSource
Specialised foldl' with short circuit evaluation A Nothing stops processing for the rest of the list
foldlStrictMaybe :: (a -> b -> Maybe a) -> a -> [b] -> aSource
Strict version of specialised foldl' with short circuit evaluation
Points free programming
(.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> dSource
Seamless composition of a one and a two arg function
ooo :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> eSource
Seamless composition of a one and a three arg function
oooo :: (e -> f) -> (a -> b -> c -> d -> e) -> a -> b -> c -> d -> fSource
Seamless composition of a one and a four arg function
Misc
More Monad Loops
whileIterateM :: Monad m => (a -> m Bool) -> (a -> m a) -> a -> m aSource
whileIterateM b f a will execute action (f a) while (b a) is true and also feed the results back to the next iteration. NOTE: Suggestions for a better name are welcome!
Math
nextPowerOf2 :: Int -> IntSource
Computes the next power of two for integers Works only on a 32/64 bit machine (is there any other kind?)