Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Net.Utils
Description
Various utilities used in the network protocol stack modules
Synopsis
- class Functor f => Container f where
- contents :: f a -> a
- replace :: Functor f => f a -> b -> f b
- emap :: (Functor f, Container f) => (t -> f a) -> f t -> f (f a)
- emap2 :: (Container f, Container f, Functor f) => (t -> f a) -> f (f t) -> f (f (f a))
- lift :: (Functor f, Container f) => f (f a) -> f (f a)
- lift2 :: (Container f, Container f, Functor f) => f (f (f a)) -> f (f (f a))
- doReq :: forall {c} {m} {v :: Type -> Type} {io} {a} {b}. (ChannelIO c m, MVarIO v m, MVarIO v io) => c a -> ((b -> io ()) -> a) -> m b
- foldlArray :: (IArray arr elem, Ix ix, Enum ix) => arr ix elem -> (elem -> a -> a) -> a -> a
- arraySize :: (Num a, IArray a e, Ix a) => a a e -> a
- checksum :: [Word16] -> Word16
- pairs :: a -> [a] -> [[a]]
- bytes_to_words_big :: [Word8] -> [Word16]
- bytes_to_words_lil :: [Word8] -> [Word16]
- words_to_bytes_big :: [Word16] -> [Word8]
- words_to_bytes_lil :: [Word16] -> [Word8]
Documentation
doReq :: forall {c} {m} {v :: Type -> Type} {io} {a} {b}. (ChannelIO c m, MVarIO v m, MVarIO v io) => c a -> ((b -> io ()) -> a) -> m b Source #
foldlArray :: (IArray arr elem, Ix ix, Enum ix) => arr ix elem -> (elem -> a -> a) -> a -> a Source #
pairs :: a -> [a] -> [[a]] Source #
Split a list into subcomponents of length 2. The first argument is what to append in case the list is of odd length.
bytes_to_words_big :: [Word8] -> [Word16] Source #
bytes_to_words_lil :: [Word8] -> [Word16] Source #
words_to_bytes_big :: [Word16] -> [Word8] Source #
words_to_bytes_lil :: [Word16] -> [Word8] Source #