ONC-RPC-0.1: ONC RPC (aka Sun RPC) and XDR library

Safe HaskellNone
LanguageHaskell2010

Network.ONCRPC.XDR.Serial

Description

XDR Serialization

Synopsis

Documentation

class XDR a where Source #

An XDR type that can be (de)serialized.

Minimal complete definition

xdrType, xdrPut, xdrGet

Methods

xdrType :: a -> String Source #

XDR identifier/type descriptor; argument value is ignored.

xdrPut :: a -> Put Source #

xdrGet :: Get a Source #

Instances

XDR Bool Source # 
XDR Double Source # 
XDR Float Source # 
XDR () Source # 

Methods

xdrType :: () -> String Source #

xdrPut :: () -> Put Source #

xdrGet :: Get () Source #

XDR UnsignedHyper Source # 
XDR Hyper Source # 
XDR UnsignedInt Source # 
XDR Int Source # 
XDR Authsys_parms Source # 
XDR Rejected_reply Source # 
XDR Accepted_reply_data Source # 
XDR Accepted_reply Source # 
XDR Reply_body Source # 
XDR Call_body Source # 
XDR Rpc_msg_body Source # 
XDR Rpc_msg Source # 
XDR Auth_stat Source # 
XDR Reject_stat Source # 
XDR Accept_stat Source # 
XDR Reply_stat Source # 
XDR Msg_type Source # 
XDR Opaque_auth Source # 
XDR Auth_flavor Source # 
XDR Call_result Source # 
XDR Call_args Source # 
XDR Pmap Source # 
XDR Mapping Source # 
XDR Netbuf Source # 
XDR Rpcb_stat Source # 
XDR Rpcbs_rmtcalllist Source # 
XDR Rpcbs_addrlist Source # 
XDR Rpcb_entry_list Source # 
XDR Rpcb_entry Source # 
XDR Rpcb_rmtcallres Source # 
XDR Rpcb_rmtcallargs Source # 
XDR Rp__list Source # 
XDR Rpcb Source # 
XDR Auth Source # 
XDR a => XDR (Optional a) Source # 
XDR a => XDR (Reply a) Source # 
(XDR a, XDR b) => XDR (a, b) Source # 

Methods

xdrType :: (a, b) -> String Source #

xdrPut :: (a, b) -> Put Source #

xdrGet :: Get (a, b) Source #

(XDR a, XDR r) => XDR (Msg a r) Source # 

Methods

xdrType :: Msg a r -> String Source #

xdrPut :: Msg a r -> Put Source #

xdrGet :: Get (Msg a r) Source #

XDR a => XDR (Call a r) Source # 

Methods

xdrType :: Call a r -> String Source #

xdrPut :: Call a r -> Put Source #

xdrGet :: Get (Call a r) Source #

(XDR a, XDR b, XDR c) => XDR (a, b, c) Source # 

Methods

xdrType :: (a, b, c) -> String Source #

xdrPut :: (a, b, c) -> Put Source #

xdrGet :: Get (a, b, c) Source #

KnownNat n => XDR (LengthArray LT n ByteString) Source # 
(KnownNat n, XDR a) => XDR (LengthArray LT n (Vector a)) Source # 
(KnownNat n, XDR a) => XDR (LengthArray LT n [a]) Source # 
KnownNat n => XDR (LengthArray EQ n ByteString) Source # 
(KnownNat n, XDR a) => XDR (LengthArray EQ n (Vector a)) Source # 
(KnownNat n, XDR a) => XDR (LengthArray EQ n [a]) Source # 
(XDR a, XDR b, XDR c, XDR d) => XDR (a, b, c, d) Source # 

Methods

xdrType :: (a, b, c, d) -> String Source #

xdrPut :: (a, b, c, d) -> Put Source #

xdrGet :: Get (a, b, c, d) Source #

class (XDR a, Enum a) => XDREnum a where Source #

An XDR type defined with "enum". Note that the XDREnum Int value is not (necessarily) the same as the Enum Int value. The Enum instance is derived automatically to allow succ, etc. to work usefully in Haskell, whereas the XDREnum reflects the XDR-defined values.

Minimal complete definition

xdrFromEnum, xdrToEnum

Methods

xdrFromEnum :: a -> Int Source #

xdrToEnum :: Monad m => Int -> m a Source #

xdrToEnum' :: XDREnum a => Int -> a Source #

Version of xdrToEnum that fails at runtime for invalid values: fromMaybe undefined . xdrToEnum.

xdrPutEnum :: XDREnum a => a -> Put Source #

Default implementation of xdrPut for XDREnum.

xdrGetEnum :: XDREnum a => Get a Source #

Default implementation of xdrGet for XDREnum.

class (XDR a, XDREnum (XDRDiscriminant a)) => XDRUnion a where Source #

An XDR type defined with "union"

Minimal complete definition

xdrSplitUnion, xdrGetUnionArm

Associated Types

type XDRDiscriminant a :: * Source #

Methods

xdrSplitUnion :: a -> (Int, Put) Source #

Split a union into its discriminant and body generator.

xdrGetUnionArm :: Int -> Get a Source #

Get the body of a union based on its discriminant.

xdrPutUnion :: XDRUnion a => a -> Put Source #

Default implementation of xdrPut for XDRUnion.

xdrGetUnion :: XDRUnion a => Get a Source #

Default implementation of xdrGet for XDRUnion.