| Copyright | No rights reserved |
|---|---|
| License | MIT |
| Maintainer | jprupp@protonmail.ch |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Haskoin.Util.Helpers
Description
This module defines various utility functions used across the library.
Synopsis
- bsToInteger :: ByteString -> Integer
- integerToBS :: Integer -> ByteString
- hexEncoding :: ByteString -> Encoding
- hexBuilder :: ByteString -> Builder
- encodeHex :: ByteString -> Text
- encodeHexLazy :: ByteString -> Text
- decodeHex :: Text -> Maybe ByteString
- decodeHexLazy :: Text -> Maybe ByteString
- getBits :: Int -> ByteString -> ByteString
- eitherToMaybe :: Either a b -> Maybe b
- maybeToEither :: b -> Maybe a -> Either b a
- liftEither :: MonadError e m => Either e a -> m a
- liftMaybe :: Monad m => b -> Maybe a -> ExceptT b m a
- updateIndex :: Int -> [a] -> (a -> a) -> [a]
- matchTemplate :: [a] -> [b] -> (a -> b -> Bool) -> [Maybe a]
- convertBits :: Bool -> Int -> Int -> [Word] -> ([Word], Bool)
- fst3 :: (a, b, c) -> a
- snd3 :: (a, b, c) -> b
- lst3 :: (a, b, c) -> c
- dropFieldLabel :: Int -> Options
- dropSumLabels :: Int -> Int -> String -> Options
- putList :: MonadPut m => (a -> m ()) -> [a] -> m ()
- getList :: MonadGet m => m a -> m [a]
- putMaybe :: MonadPut m => (a -> m ()) -> Maybe a -> m ()
- getMaybe :: MonadGet m => m a -> m (Maybe a)
- putLengthBytes :: MonadPut m => ByteString -> m ()
- getLengthBytes :: MonadGet m => m ByteString
- putInteger :: MonadPut m => Integer -> m ()
- getInteger :: MonadGet m => m Integer
- putInt32be :: MonadPut m => Int32 -> m ()
- getInt32be :: MonadGet m => m Int32
- putInt64be :: MonadPut m => Int64 -> m ()
- getInt64be :: MonadGet m => m Int64
- getIntMap :: MonadGet m => m Int -> m a -> m (IntMap a)
- putIntMap :: MonadPut m => (Int -> m ()) -> (a -> m ()) -> IntMap a -> m ()
- getTwo :: MonadGet m => m a -> m b -> m (a, b)
- putTwo :: MonadPut m => (a -> m ()) -> (b -> m ()) -> (a, b) -> m ()
- prepareContext :: (Ctx -> SpecWith a) -> SpecWith a
- customCerealID :: Eq a => Get a -> Putter a -> a -> Bool
- readTestFile :: FromJSON a => FilePath -> IO a
- readTestFileParser :: (Value -> Parser a) -> FilePath -> IO a
ByteString Helpers
bsToInteger :: ByteString -> Integer Source #
Decode a big endian Integer from a ByteString.
integerToBS :: Integer -> ByteString Source #
Encode an Integer to a ByteString as big endian.
hexEncoding :: ByteString -> Encoding Source #
hexBuilder :: ByteString -> Builder Source #
encodeHex :: ByteString -> Text Source #
encodeHexLazy :: ByteString -> Text Source #
Encode as string of human-readable hex characters.
decodeHexLazy :: Text -> Maybe ByteString Source #
Decode string of human-readable hex characters.
getBits :: Int -> ByteString -> ByteString Source #
Obtain Int bits from beginning of ByteString. Resulting ByteString
will be smallest required to hold that many bits, padded with zeroes to the
right.
Maybe & Either Helpers
eitherToMaybe :: Either a b -> Maybe b Source #
maybeToEither :: b -> Maybe a -> Either b a Source #
liftEither :: MonadError e m => Either e a -> m a #
Lifts an into any Either e.MonadError e
do { val <- liftEither =<< action1; action2 }where action1 returns an Either to represent errors.
Since: mtl-2.2.2
Other Helpers
Arguments
| :: Int | index of the element to change |
| -> [a] | list of elements |
| -> (a -> a) | function to apply |
| -> [a] | result with one element changed |
Applies a function to only one element of a list defined by its index. If the index is out of the bounds of the list, the original list is returned.
Arguments
| :: [a] | input list |
| -> [b] | list to serve as a template |
| -> (a -> b -> Bool) | comparison function |
| -> [Maybe a] |
Use the list [b] as a template and try to match the elements of [a]
against it. For each element of [b] return the (first) matching element of
[a], or Nothing. Output list has same size as [b] and contains results
in same order. Elements of [a] can only appear once.
convertBits :: Bool -> Int -> Int -> [Word] -> ([Word], Bool) Source #
Convert from one power-of-two base to another, as long as it fits in a
Word.
Triples
JSON Utilities
dropFieldLabel :: Int -> Options Source #
Field label goes lowercase and first n characters get removed.
dropSumLabels :: Int -> Int -> String -> Options Source #
Transformation from dropFieldLabel is applied with argument f, plus
constructor tags are lowercased and first c characters removed. tag is
used as the name of the object field name that will hold the transformed
constructor tag as its value.
Serialization Helpers
putLengthBytes :: MonadPut m => ByteString -> m () Source #
getLengthBytes :: MonadGet m => m ByteString Source #
putInteger :: MonadPut m => Integer -> m () Source #
getInteger :: MonadGet m => m Integer Source #
putInt32be :: MonadPut m => Int32 -> m () Source #
getInt32be :: MonadGet m => m Int32 Source #
putInt64be :: MonadPut m => Int64 -> m () Source #
getInt64be :: MonadGet m => m Int64 Source #
getIntMap :: MonadGet m => m Int -> m a -> m (IntMap a) Source #
Read as a list of pairs of int and element.