netw-0.1.1.0: Binding to C socket API operating on bytearrays.
Safe HaskellSafe-Inferred
LanguageGHC2021

Netw.Ancillary

Description

This module contains ancillary data types. Ancillary data can be send and received via the sendmsg and recvmsg functions.

Synopsis

Documentation

class (Typeable a, KnownNatPair (Anci a)) => Ancillary a where Source #

Associated Types

type Anci a = (r :: (Nat, Nat)) | r -> a Source #

This type family enforces an unique mapping between cmsg_level and cmsg_type pair and the ancillary data type

the order is (cmsg_level, cmsg_type)

Methods

cmsgDataSize :: a -> Int Source #

Get the size of the cmsg payload (just cmsg_data[])

cmsgPokeData :: PrimMonad m => a -> MutableByteArray (PrimState m) -> Int -> m () Source #

Write the payload onto the data section. Take the offset of the data section.

This function assumes enough space has been allocated

cmsgPeekData :: ByteArray -> Int -> Int -> a Source #

Read the payload from the data section. Take the offset and size of the payload section.

Instances

Instances details
Ancillary ScmRights Source # 
Instance details

Defined in Netw.Ancillary

Associated Types

type Anci ScmRights = (r :: (Nat, Nat)) Source #

cmsgLevel :: forall a. Ancillary a => CmsghdrLevel Source #

cmsgType :: forall a. Ancillary a => CmsghdrType Source #

cmsgSpace :: Ancillary a => a -> Int Source #

Find the space a control message element occupies in cmsg buffer given the size of its payload section.

peekAncillary :: forall a. Ancillary a => ByteArray -> Int -> Maybe a Source #

Read a control message element, assuming type a. Return Nothing if a is not the correct type.

pokeAncillary :: forall a m. (Ancillary a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> a -> m () Source #

Warning: The buffer must be big enough to store the control message element

Store a control message element at offset in buffer

data AncillaryData Source #

This data type holds an abitrary ancillary data type.

Constructors

AncillaryData 

Fields

writeAncillary :: PrimMonad m => AncillaryData -> MutableByteArray (PrimState m) -> Int -> m () Source #

ancillaryWrite but without the impredicative type

recoverAncillary :: Ancillary a => AncillaryData -> Maybe a Source #

ancillaryData but without the impredicative type

encodeAncillaryData :: [AncillaryData] -> ByteArray Source #

Used internally

Encode a list of control message elements

decodeAncillaryData :: ByteArray -> [AncillaryData] Source #

Used internally. Every AncillaryData element holds a reference to the bytearray and keeps it alive.

Decode a buffer of control message elements. NOTE: The bytearray must be shrunk to msg_controllen bytes before being passed to this function.

newtype ScmRights Source #

Transfer file descriptors between sockets

Constructors

ScmRights [Fd] 

Instances

Instances details
Ancillary ScmRights Source # 
Instance details

Defined in Netw.Ancillary

Associated Types

type Anci ScmRights = (r :: (Nat, Nat)) Source #

type Anci ScmRights Source # 
Instance details

Defined in Netw.Ancillary