Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Network.DNS.StateBinary
Synopsis
- data PState = PState {
- psDomain :: IntMap Domain
- psPosition :: Int
- psInput :: ByteString
- psAtTime :: Int64
- initialState :: Int64 -> ByteString -> PState
- type SPut = State WState Builder
- runSPut :: SPut -> ByteString
- put8 :: Word8 -> SPut
- put16 :: Word16 -> SPut
- put32 :: Word32 -> SPut
- putInt8 :: Int -> SPut
- putInt16 :: Int -> SPut
- putInt32 :: Int -> SPut
- putByteString :: ByteString -> SPut
- putReplicate :: Int -> Word8 -> SPut
- type SGet = StateT PState (Parser ByteString)
- failSGet :: String -> SGet a
- fitSGet :: Int -> SGet a -> SGet a
- runSGet :: SGet a -> ByteString -> Either DNSError (a, PState)
- runSGetAt :: Int64 -> SGet a -> ByteString -> Either DNSError (a, PState)
- runSGetWithLeftovers :: SGet a -> ByteString -> Either DNSError ((a, PState), ByteString)
- runSGetWithLeftoversAt :: Int64 -> SGet a -> ByteString -> Either DNSError ((a, PState), ByteString)
- get8 :: SGet Word8
- get16 :: SGet Word16
- get32 :: SGet Word32
- getInt8 :: SGet Int
- getInt16 :: SGet Int
- getInt32 :: SGet Int
- getNByteString :: Int -> SGet ByteString
- sGetMany :: String -> Int -> SGet a -> SGet [a]
- getPosition :: SGet Int
- getInput :: SGet ByteString
- getAtTime :: SGet Int64
- wsPop :: Domain -> State WState (Maybe Int)
- wsPush :: Domain -> Int -> State WState ()
- wsPosition :: WState -> Int
- addPositionW :: Int -> State WState ()
- push :: Int -> Domain -> SGet ()
- pop :: Int -> SGet (Maybe Domain)
- getNBytes :: Int -> SGet [Int]
- getNoctets :: Int -> SGet [Word8]
- skipNBytes :: Int -> SGet ()
- parseLabel :: Word8 -> ByteString -> Either DNSError (ByteString, ByteString)
- unparseLabel :: Word8 -> ByteString -> ByteString
Documentation
Constructors
PState | |
Fields
|
initialState :: Int64 -> ByteString -> PState Source #
runSPut :: SPut -> ByteString Source #
putByteString :: ByteString -> SPut Source #
runSGetWithLeftovers :: SGet a -> ByteString -> Either DNSError ((a, PState), ByteString) Source #
runSGetWithLeftoversAt Source #
Arguments
:: Int64 | Reference time for DNS clock arithmetic |
-> SGet a | Parser |
-> ByteString | Encoded message |
-> Either DNSError ((a, PState), ByteString) |
getNByteString :: Int -> SGet ByteString Source #
Arguments
:: String | element type for error messages |
-> Int | input buffer length |
-> SGet a | element parser |
-> SGet [a] |
Parse a list of elements that takes up exactly a given number of bytes. In order to avoid infinite loops, if an element parser succeeds without moving the buffer offset forward, an error will be returned.
getPosition :: SGet Int Source #
wsPosition :: WState -> Int Source #
addPositionW :: Int -> State WState () Source #
skipNBytes :: Int -> SGet () Source #
parseLabel :: Word8 -> ByteString -> Either DNSError (ByteString, ByteString) Source #
Decode a domain name in A-label form to a leading label and a tail with the remaining labels, unescaping backlashed chars and decimal triples along the way. Any U-label conversion belongs at the layer above this code.
unparseLabel :: Word8 -> ByteString -> ByteString Source #
Convert a wire-form label to presentation-form by escaping the separator, special and non-printing characters. For simple labels with no bytes that require escaping we get back the input bytestring asis with no copying or re-construction.
Note: the separator is required to be either '.' or '@', but this constraint is the caller's responsibility and is not checked here.