Safe Haskell | None |
---|---|
Language | Haskell2010 |
- module Language.Parser
- class Generic a
- class ParseStreamType s => SerialStreamType s where
- type StreamBuilder s :: *
- class (SerialStreamType stream, ParseStream stream, StreamChar stream ~ Word8, Monoid (StreamBuilder stream)) => SerialStream stream where
- class SerialStream stream => Serializable stream t where
- class Serializable stream t => Format stream t where
- data Builder :: *
- bytesBuilder :: Bytes :<->: Builder
- chunkBuilder :: Chunk :<->: Builder
- serialize :: forall stream t. Serializable stream t => t -> stream
- serial :: (Format stream t, Serializable stream t') => Traversal t t' stream stream
- stringBytes :: String -> Bytes
- defaultEncode :: (Generic t, GenSerializable stream (Rep t)) => Proxy stream -> t -> StreamBuilder stream
- defaultDatum :: (Generic t, GenFormat stream (Rep t)) => Parser stream t
- encodeFree :: (Serializable stream (Forest f a), Serializable stream a) => Proxy stream -> Free f a -> StreamBuilder stream
- encodeCofree :: (Serializable stream (Coforest f a), Serializable stream a) => Proxy stream -> Cofree f a -> StreamBuilder stream
- datumFree :: (Format stream (Forest f a), Format stream a) => Parser stream (Free f a)
- datumCofree :: (Format stream (Coforest f a), Format stream a) => Parser stream (Cofree f a)
- word8 :: Word8 -> Builder
- data Word8 :: *
- data Word16 :: *
- data Word32 :: *
- data Word64 :: *
- newtype LittleEndian t = LittleEndian {
- fromLittleEndian :: t
- encodeAlt :: Serializable stream a => Proxy stream -> Word8 -> a -> StreamBuilder stream
- data FormatAlt stream a = Format stream b => FormatAlt (b -> a)
- datumOf :: SerialStream stream => [FormatAlt stream a] -> Parser stream a
- getChunk :: Int -> Parser Bytes Chunk
- writeSerial :: Serializable Bytes a => String -> a -> IO ()
- readFormat :: Format Bytes a => String -> IO a
- writeHSerial :: Serializable Bytes a => Handle -> a -> IO ()
- readHFormat :: Format Bytes a => Handle -> IO a
- runConnection :: (MonadIO io, Monoid m) => (a -> m) -> Bool -> Handle -> ((?write :: Bytes -> IO ()) => ParserT Bytes io a) -> io m
- runConnection_ :: MonadIO io => Bool -> Handle -> ((?write :: Bytes -> IO ()) => ParserT Bytes io a) -> io ()
- send :: (Serializable Bytes t, MonadIO m, ?write :: Bytes -> IO ()) => t -> m ()
- receive :: (Format stream t, Monad m) => ParserT stream m t
- data Proxy a = Proxy
- exchange :: (MonadIO m, ?write :: Bytes -> IO (), Format stream a, Serializable Bytes b) => (Proxy a -> b) -> ParserT stream m a
- sending :: (MonadIO m, ?write :: Bytes -> IO (), Serializable Bytes a) => Proxy a -> a -> m ()
- coerceEncode :: forall stream t t'. Serializable stream t => (t -> t') -> Proxy stream -> t' -> StreamBuilder stream
- coerceDatum :: forall stream t t'. Format stream t => (t -> t') -> Parser stream t'
You'll need this
module Language.Parser
Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.
Serialization
class ParseStreamType s => SerialStreamType s Source #
type StreamBuilder s :: * Source #
class (SerialStreamType stream, ParseStream stream, StreamChar stream ~ Word8, Monoid (StreamBuilder stream)) => SerialStream stream where Source #
encodeByte :: Proxy stream -> Word8 -> StreamBuilder stream Source #
toSerialStream :: StreamBuilder stream -> stream Source #
class SerialStream stream => Serializable stream t where Source #
encode :: Proxy stream -> t -> StreamBuilder stream Source #
encode :: (Generic t, GenSerializable stream (Rep t)) => Proxy stream -> t -> StreamBuilder stream Source #
class Serializable stream t => Format stream t where Source #
datum :: Parser stream t Source #
datum :: (Generic t, GenFormat stream (Rep t)) => Parser stream t Source #
SerialStream stream => Format stream Integer Source # | |
SerialStream stream => Format stream () Source # | |
SerialStream stream => Format stream Bool Source # | |
SerialStream stream => Format stream Int Source # | |
SerialStream stream => Format stream Word8 Source # | |
Format Bytes Char Source # | |
Format Bytes Double Source # | |
Format Bytes Float Source # | |
Format Bytes Word16 Source # | |
Format Bytes Word32 Source # | |
Format Bytes Word64 Source # | |
Format Bytes Bytes Source # | |
Format stream a => Format stream (Range a) Source # | |
(Ord a, Format stream a) => Format stream (Set a) Source # | |
Format stream a => Format stream [a] Source # | |
Format stream a => Format stream (Maybe a) Source # | |
SerialStream stream => Format stream (Proxy a) Source # | |
Format Bytes (LittleEndian Word16) Source # | |
Format Bytes (LittleEndian Word32) Source # | |
Format Bytes (LittleEndian Word64) Source # | |
(Format stream a, Format stream b) => Format stream ((:+:) a b) Source # | |
(Format stream a, Format stream b) => Format stream ((:*:) a b) Source # | |
(Ord a, Format stream a, Format stream e) => Format stream (Equiv e a) Source # | |
(Ord k, Ord a, Format stream k, Format stream a) => Format stream (Bimap k a) Source # | |
(Ord k, Format stream k, Format stream a) => Format stream (Map k a) Source # | |
(Ord k, Format stream k, Format stream a) => Format stream (Cofree (Map k) a) Source # | |
Format stream a => Format stream (Cofree [] a) Source # | |
Format stream a => Format stream (Cofree Maybe a) Source # | |
(Ord k, Format stream k, Format stream a) => Format stream (Free (Map k) a) Source # | |
Format stream a => Format stream (Free [] a) Source # | |
Format stream a => Format stream (Free Maybe a) Source # | |
(Format stream a, Format stream b, Format stream c) => Format stream (Union3 a b c) Source # | |
(Format stream a, Format stream b, Format stream c) => Format stream (a, b, c) Source # | |
(Ord a, Ord b, Format stream a, Format stream b, Format stream e) => Format stream (Relation e a b) Source # | |
Format stream (f (g a)) => Format stream ((:.:) f g a) Source # | |
(Format stream a, Format stream b, Format stream c, Format stream d) => Format stream (Union4 a b c d) Source # | |
(Format stream a, Format stream b, Format stream c, Format stream d) => Format stream (a, b, c, d) Source # | |
(Format stream a, Format stream b, Format stream c, Format stream d, Format stream e) => Format stream (Union5 a b c d e) Source # | |
(Format stream a, Format stream b, Format stream c, Format stream d, Format stream e) => Format stream (a, b, c, d, e) Source # | |
(Format stream a, Format stream b, Format stream c, Format stream d, Format stream e, Format stream f) => Format stream (Union6 a b c d e f) Source # | |
(Format stream a, Format stream b, Format stream c, Format stream d, Format stream e, Format stream f) => Format stream (Tuple6 a b c d e f) Source # | |
(Format stream a, Format stream b, Format stream c, Format stream d, Format stream e, Format stream f, Format stream g) => Format stream (Union7 a b c d e f g) Source # | |
(Format stream a, Format stream b, Format stream c, Format stream d, Format stream e, Format stream f, Format stream g) => Format stream (Tuple7 a b c d e f g) Source # | |
(Format stream a, Format stream b, Format stream c, Format stream d, Format stream e, Format stream f, Format stream g, Format stream h) => Format stream (Union8 a b c d e f g h) Source # | |
(Format stream a, Format stream b, Format stream c, Format stream d, Format stream e, Format stream f, Format stream g, Format stream h) => Format stream (Tuple8 a b c d e f g h) Source # | |
(Format stream a, Format stream b, Format stream c, Format stream d, Format stream e, Format stream f, Format stream g, Format stream h, Format stream i) => Format stream (Union9 a b c d e f g h i) Source # | |
(Format stream a, Format stream b, Format stream c, Format stream d, Format stream e, Format stream f, Format stream g, Format stream h, Format stream i) => Format stream (Tuple9 a b c d e f g h i) Source # | |
serialize :: forall stream t. Serializable stream t => t -> stream Source #
stringBytes :: String -> Bytes Source #
Convenience functions
defaultEncode :: (Generic t, GenSerializable stream (Rep t)) => Proxy stream -> t -> StreamBuilder stream Source #
encodeFree :: (Serializable stream (Forest f a), Serializable stream a) => Proxy stream -> Free f a -> StreamBuilder stream Source #
encodeCofree :: (Serializable stream (Coforest f a), Serializable stream a) => Proxy stream -> Cofree f a -> StreamBuilder stream Source #
datumCofree :: (Format stream (Coforest f a), Format stream a) => Parser stream (Cofree f a) Source #
8-bit unsigned integer type
16-bit unsigned integer type
32-bit unsigned integer type
64-bit unsigned integer type
newtype LittleEndian t Source #
encodeAlt :: Serializable stream a => Proxy stream -> Word8 -> a -> StreamBuilder stream Source #
writeSerial :: Serializable Bytes a => String -> a -> IO () Source #
writeHSerial :: Serializable Bytes a => Handle -> a -> IO () Source #
Bidirectional serialization
runConnection_ :: MonadIO io => Bool -> Handle -> ((?write :: Bytes -> IO ()) => ParserT Bytes io a) -> io () Source #
A proxy type to specify response types
exchange :: (MonadIO m, ?write :: Bytes -> IO (), Format stream a, Serializable Bytes b) => (Proxy a -> b) -> ParserT stream m a Source #
sending :: (MonadIO m, ?write :: Bytes -> IO (), Serializable Bytes a) => Proxy a -> a -> m () Source #
GND replacement for GHC 7.8 and up
coerceEncode :: forall stream t t'. Serializable stream t => (t -> t') -> Proxy stream -> t' -> StreamBuilder stream Source #
coerceDatum :: forall stream t t'. Format stream t => (t -> t') -> Parser stream t' Source #