Safe Haskell | None |
---|---|
Language | Haskell2010 |
Miscellaneous general functions and Show, Eq, and Ord instances for PortID
- mergesortM :: Monad m => (a -> a -> m Ordering) -> [a] -> m [a]
- mergesortM' :: Monad m => (a -> a -> m Ordering) -> [[a]] -> m [a]
- merge_pairsM :: Monad m => (a -> a -> m Ordering) -> [[a]] -> m [[a]]
- mergeM :: Monad m => (a -> a -> m Ordering) -> [a] -> [a] -> m [a]
- wrap :: a -> [a]
- shuffle :: [a] -> IO [a]
- loop :: (Functor m, Monad m) => m (Maybe a) -> m [a]
- untilSuccess :: (MonadError e m, Error e) => (a -> m b) -> [a] -> m b
- untilSuccess' :: MonadError e m => e -> (a -> m b) -> [a] -> m b
- whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
- liftIOE :: (MonadIO m, Exception e, Exception e') => (e -> e') -> IO a -> m a
- updateAssocs :: Eq k => k -> v -> [(k, v)] -> [(k, v)]
- bitOr :: (Num a, Bits a) => [a] -> a
- (<.>) :: Text -> Text -> Text
- true1 :: Label -> Document -> Bool
- byteStringHex :: ByteString -> String
- byteHex :: Word8 -> String
Documentation
mergesortM :: Monad m => (a -> a -> m Ordering) -> [a] -> m [a] Source
A monadic sort implementation derived from the non-monadic one in ghc's Prelude
mergesortM' :: Monad m => (a -> a -> m Ordering) -> [[a]] -> m [a] Source
merge_pairsM :: Monad m => (a -> a -> m Ordering) -> [[a]] -> m [[a]] Source
loop :: (Functor m, Monad m) => m (Maybe a) -> m [a] Source
Repeatedy execute action, collecting results, until it returns Nothing
untilSuccess :: (MonadError e m, Error e) => (a -> m b) -> [a] -> m b Source
Apply action to elements one at a time until one succeeds. Throw last error if all fail. Throw strMsg
error if list is empty.
untilSuccess' :: MonadError e m => e -> (a -> m b) -> [a] -> m b Source
Apply action to elements one at a time until one succeeds. Throw last error if all fail. Throw given error if list is empty
liftIOE :: (MonadIO m, Exception e, Exception e') => (e -> e') -> IO a -> m a Source
lift IOE monad to ErrorT monad over some MonadIO m
updateAssocs :: Eq k => k -> v -> [(k, v)] -> [(k, v)] Source
Change or insert value of key in association list
(<.>) :: Text -> Text -> Text Source
Concat first and second together with period in between. Eg. "hello" <.> "world" = "hello.world"
true1 :: Label -> Document -> Bool Source
Is field's value a 1 or True (MongoDB use both Int and Bools for truth values). Error if field not in document or field not a Num or Bool.
byteStringHex :: ByteString -> String Source
Hexadecimal string representation of a byte string. Each byte yields two hexadecimal characters.