Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Miscellaneous helper functions used internally
Synopsis
- debug :: Show a => a -> b -> b
- swap :: (a, b) -> (b, a)
- pairs :: [a] -> [(a, a)]
- pairsWith :: (a -> a -> b) -> [a] -> [b]
- sum' :: Num a => [a] -> a
- interleave :: [a] -> [a] -> [a]
- evens :: [a] -> [a]
- odds :: [a] -> [a]
- productInterleaved :: [Integer] -> Integer
- productFromTo :: Integral a => a -> a -> Integer
- productFromToStride2 :: Integral a => a -> a -> Integer
- equating :: Eq b => (a -> b) -> a -> a -> Bool
- reverseOrdering :: Ordering -> Ordering
- reverseComparing :: Ord b => (a -> b) -> a -> a -> Ordering
- reverseCompare :: Ord a => a -> a -> Ordering
- reverseSort :: Ord a => [a] -> [a]
- groupSortBy :: (Eq b, Ord b) => (a -> b) -> [a] -> [[a]]
- nubOrd :: Ord a => [a] -> [a]
- isWeaklyIncreasing :: Ord a => [a] -> Bool
- isStrictlyIncreasing :: Ord a => [a] -> Bool
- isWeaklyDecreasing :: Ord a => [a] -> Bool
- isStrictlyDecreasing :: Ord a => [a] -> Bool
- mapWithLast :: (Bool -> a -> b) -> [a] -> [b]
- mapWithFirst :: (Bool -> a -> b) -> [a] -> [b]
- mapWithFirstLast :: (Bool -> Bool -> a -> b) -> [a] -> [b]
- mkLinesUniformWidth :: [String] -> [String]
- mkBlocksUniformHeight :: [[String]] -> [[String]]
- mkUniformBlocks :: [[String]] -> [[String]]
- hConcatLines :: [[String]] -> [String]
- vConcatLines :: [[String]] -> [String]
- count :: Eq a => a -> [a] -> Int
- histogram :: (Eq a, Ord a) => [a] -> [(a, Int)]
- fromJust :: Maybe a -> a
- intToBool :: Int -> Bool
- boolToInt :: Bool -> Int
- nest :: Int -> (a -> a) -> a -> a
- unfold1 :: (a -> Maybe a) -> a -> [a]
- unfold :: (b -> (a, Maybe b)) -> b -> [a]
- unfoldEither :: (b -> Either c (b, a)) -> b -> (c, [a])
- unfoldM :: Monad m => (b -> m (a, Maybe b)) -> b -> m [a]
- mapAccumM :: Monad m => (acc -> x -> m (acc, y)) -> acc -> [x] -> m (acc, [y])
- longZipWith :: a -> b -> (a -> b -> c) -> [a] -> [b] -> [c]
- type Rand g = RandT g Identity
- runRand :: Rand g a -> g -> (a, g)
- flipRunRand :: Rand s a -> s -> (s, a)
- newtype RandT g m a = RandT (StateT g m a)
- runRandT :: RandT g m a -> g -> m (a, g)
- flipRunRandT :: Monad m => RandT s m a -> s -> m (s, a)
- rand :: (g -> (a, g)) -> Rand g a
- randRoll :: (RandomGen g, Random a) => Rand g a
- randChoose :: (RandomGen g, Random a) => (a, a) -> Rand g a
- randProxy1 :: Rand g (f n) -> Proxy n -> Rand g (f n)
debugging
pairs
lists
interleave :: [a] -> [a] -> [a] Source #
multiplication
productInterleaved :: [Integer] -> Integer Source #
Product of list of integers, but in interleaved order (for a list of big numbers, it should be faster than the linear order)
productFromTo :: Integral a => a -> a -> Integer Source #
Faster implementation of product [ i | i <- [a+1..b] ]
productFromToStride2 :: Integral a => a -> a -> Integer Source #
Faster implementation of product [ i | i <- [a+1,a+3,..b] ]
equality and ordering
reverseOrdering :: Ordering -> Ordering Source #
reverseComparing :: Ord b => (a -> b) -> a -> a -> Ordering Source #
reverseCompare :: Ord a => a -> a -> Ordering Source #
reverseSort :: Ord a => [a] -> [a] Source #
groupSortBy :: (Eq b, Ord b) => (a -> b) -> [a] -> [[a]] Source #
increasing / decreasing sequences
isWeaklyIncreasing :: Ord a => [a] -> Bool Source #
isStrictlyIncreasing :: Ord a => [a] -> Bool Source #
isWeaklyDecreasing :: Ord a => [a] -> Bool Source #
isStrictlyDecreasing :: Ord a => [a] -> Bool Source #
first / last
mapWithLast :: (Bool -> a -> b) -> [a] -> [b] Source #
The boolean argument will True
only for the last element
mapWithFirst :: (Bool -> a -> b) -> [a] -> [b] Source #
mapWithFirstLast :: (Bool -> Bool -> a -> b) -> [a] -> [b] Source #
older helpers for ASCII drawing
mkLinesUniformWidth :: [String] -> [String] Source #
extend lines with spaces so that they have the same line
mkBlocksUniformHeight :: [[String]] -> [[String]] Source #
mkUniformBlocks :: [[String]] -> [[String]] Source #
hConcatLines :: [[String]] -> [String] Source #
vConcatLines :: [[String]] -> [String] Source #
counting
maybe
bool
iteration
unfoldEither :: (b -> Either c (b, a)) -> b -> (c, [a]) Source #
long zipwith
longZipWith :: a -> b -> (a -> b -> c) -> [a] -> [b] -> [c] Source #
random
flipRunRand :: Rand s a -> s -> (s, a) Source #
The Rand monad transformer
flipRunRandT :: Monad m => RandT s m a -> s -> m (s, a) Source #
This may be occasionally useful