ONC-RPC-0.2: ONC RPC (aka Sun RPC) and XDR library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.ONCRPC.XDR.Serial

Description

XDR Serialization

Synopsis

Documentation

class XDR a where Source #

An XDR type that can be (de)serialized.

Methods

xdrType :: a -> String Source #

XDR identifier/type descriptor; argument value is ignored.

xdrPut :: a -> Put Source #

xdrGet :: Get a Source #

Instances

Instances details
XDR Auth Source # 
Instance details

Defined in Network.ONCRPC.Auth

XDR Call_args Source # 
Instance details

Defined in Network.ONCRPC.Bind.Prot

XDR Call_result Source # 
Instance details

Defined in Network.ONCRPC.Bind.Prot

XDR Mapping Source # 
Instance details

Defined in Network.ONCRPC.Bind.Prot

XDR Netbuf Source # 
Instance details

Defined in Network.ONCRPC.Bind.Prot

XDR Pmap Source # 
Instance details

Defined in Network.ONCRPC.Bind.Prot

XDR Rp__list Source # 
Instance details

Defined in Network.ONCRPC.Bind.Prot

XDR Rpcb Source # 
Instance details

Defined in Network.ONCRPC.Bind.Prot

XDR Rpcb_entry Source # 
Instance details

Defined in Network.ONCRPC.Bind.Prot

XDR Rpcb_entry_list Source # 
Instance details

Defined in Network.ONCRPC.Bind.Prot

XDR Rpcb_rmtcallargs Source # 
Instance details

Defined in Network.ONCRPC.Bind.Prot

XDR Rpcb_rmtcallres Source # 
Instance details

Defined in Network.ONCRPC.Bind.Prot

XDR Rpcb_stat Source # 
Instance details

Defined in Network.ONCRPC.Bind.Prot

XDR Rpcbs_addrlist Source # 
Instance details

Defined in Network.ONCRPC.Bind.Prot

XDR Rpcbs_rmtcalllist Source # 
Instance details

Defined in Network.ONCRPC.Bind.Prot

XDR Accept_stat Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDR Accepted_reply Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDR Accepted_reply_data Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDR Auth_flavor Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDR Auth_stat Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDR Authsys_parms Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDR Call_body Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDR Msg_type Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDR Opaque_auth Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDR Reject_stat Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDR Rejected_reply Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDR Reply_body Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDR Reply_stat Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDR Rpc_msg Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDR Rpc_msg_body Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDR Hyper Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

XDR Int Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

XDR UnsignedHyper Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

XDR UnsignedInt Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

XDR () Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

Methods

xdrType :: () -> String Source #

xdrPut :: () -> Put Source #

xdrGet :: Get () Source #

XDR Bool Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

XDR Double Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

XDR Float Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

XDR a => XDR (Reply a) Source # 
Instance details

Defined in Network.ONCRPC.Message

XDR a => XDR (Optional a) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

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

Defined in Network.ONCRPC.Message

Methods

xdrType :: Call a r -> String Source #

xdrPut :: Call a r -> Put Source #

xdrGet :: Get (Call a r) Source #

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

Defined in Network.ONCRPC.Message

Methods

xdrType :: Msg a r -> String Source #

xdrPut :: Msg a r -> Put Source #

xdrGet :: Get (Msg a r) Source #

(XDR a, XDR b) => XDR (a, b) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

Methods

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

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

xdrGet :: Get (a, b) Source #

KnownNat n => XDR (LengthArray 'EQ n OpaqueString) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

KnownNat n => XDR (LengthArray 'EQ n ByteString) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

(KnownNat n, XDR a) => XDR (LengthArray 'EQ n (Vector a)) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

(KnownNat n, XDR a) => XDR (LengthArray 'EQ n [a]) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

KnownNat n => XDR (LengthArray 'LT n OpaqueString) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

KnownNat n => XDR (LengthArray 'LT n ByteString) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

(KnownNat n, XDR a) => XDR (LengthArray 'LT n (Vector a)) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

(KnownNat n, XDR a) => XDR (LengthArray 'LT n [a]) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

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

Defined in Network.ONCRPC.XDR.Serial

Methods

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

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

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

(XDR a, XDR b, XDR c, XDR d) => XDR (a, b, c, d) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

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.

Methods

xdrFromEnum :: a -> Int Source #

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

Instances

Instances details
XDREnum Accept_stat Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDREnum Auth_flavor Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDREnum Auth_stat Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDREnum Msg_type Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDREnum Reject_stat Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDREnum Reply_stat Source # 
Instance details

Defined in Network.ONCRPC.Prot

XDREnum Int Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

XDREnum UnsignedInt Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

XDREnum Bool Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

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

Version of xdrToEnum that fails at runtime for invalid values: fromJust . 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"

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.