derive-storable-0.2.0.0: Derive Storable instances with GHC.Generics.

Copyright(c) Mateusz Kłoczko 2016
LicenseMIT
Maintainermateusz.p.kloczko@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Foreign.Storable.Generic.Internal

Description

 
Synopsis

Documentation

class GStorable' f where Source #

Methods

gpeekByteOff' Source #

Arguments

:: [Int]

List of fields' offsets for the type/struct.

-> Int

The index. Used to obtain the correct offset

-> Ptr b

The pointer to the type/struct.

-> Int

Global offset.

-> IO (f a)

The result, wrapped in GHC.Generic metadata. | Write the element at a given offset. Additional information about the offests of the subfields are needed.

Read the element at a given offset. Additional information about the offests of the subfields are needed.

gpokeByteOff' Source #

Arguments

:: [Int]

List of fields' offsets for the type/struct.

-> Int

The index. Used to obtain the correct offset.

-> Ptr b

The pointer to the type/struct.

-> Int

Global offset.

-> f a

The element to write, wrapped in GHC.Generic metadata.

-> IO () 

glistSizeOf' Source #

Arguments

:: f a

GHC.Generic information about a given type/struct.

-> [Size]

List of sizes.

Calculates the sizes of type's/struct's fields.

glistAlignment' Source #

Arguments

:: f a

GHC.Generic information about a given type/struct.

-> [Alignment]

List of alignments.

Calculates the alignments of type's/struct's fields.

Instances
GStorable' (U1 :: Type -> Type) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

gpeekByteOff' :: [Int] -> Int -> Ptr b -> Int -> IO (U1 a) Source #

gpokeByteOff' :: [Int] -> Int -> Ptr b -> Int -> U1 a -> IO () Source #

glistSizeOf' :: U1 a -> [Size] Source #

glistAlignment' :: U1 a -> [Alignment] Source #

GStorable a => GStorable' (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

gpeekByteOff' :: [Int] -> Int -> Ptr b -> Int -> IO (K1 i a a0) Source #

gpokeByteOff' :: [Int] -> Int -> Ptr b -> Int -> K1 i a a0 -> IO () Source #

glistSizeOf' :: K1 i a a0 -> [Size] Source #

glistAlignment' :: K1 i a a0 -> [Alignment] Source #

(KnownNat (NoFields f), KnownNat (NoFields g), GStorable' f, GStorable' g) => GStorable' (f :*: g) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

gpeekByteOff' :: [Int] -> Int -> Ptr b -> Int -> IO ((f :*: g) a) Source #

gpokeByteOff' :: [Int] -> Int -> Ptr b -> Int -> (f :*: g) a -> IO () Source #

glistSizeOf' :: (f :*: g) a -> [Size] Source #

glistAlignment' :: (f :*: g) a -> [Alignment] Source #

GStorable' f => GStorable' (M1 i t f) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

gpeekByteOff' :: [Int] -> Int -> Ptr b -> Int -> IO (M1 i t f a) Source #

gpokeByteOff' :: [Int] -> Int -> Ptr b -> Int -> M1 i t f a -> IO () Source #

glistSizeOf' :: M1 i t f a -> [Size] Source #

glistAlignment' :: M1 i t f a -> [Alignment] Source #

class GStorable a where Source #

The class uses the default Generic based implementations to provide Storable instances for types made from primitive types. Sum types work with sumtypes cabal flag enabled - or just with -DGSTORABLE_SUMTYPES cpp flag.

Minimal complete definition

Nothing

Methods

gsizeOf Source #

Arguments

:: a

Element of a given type. Can be undefined.

-> Int

Size.

Calculate the size of the type.

galignment Source #

Arguments

:: a

Element of a given type. Can be undefined

-> Int

Alignment.

Calculate the alignment of the type.

gpeekByteOff Source #

Arguments

:: Ptr b

Pointer to the variable

-> Int

Offset

-> IO a

Returned variable.

Read the variable from a given pointer.

gpokeByteOff Source #

Arguments

:: Ptr b

Pointer to the variable.

-> Int

Offset.

-> a

The variable

-> IO () 

Write the variable to a pointer.

gsizeOf Source #

Arguments

:: (ConstraintsSize a, GStorableChoice a) 
=> a

Element of a given type. Can be undefined.

-> Int

Size.

Calculate the size of the type.

galignment Source #

Arguments

:: (ConstraintsAlignment a, GStorableChoice a) 
=> a

Element of a given type. Can be undefined

-> Int

Alignment.

Calculate the alignment of the type.

gpeekByteOff Source #

Arguments

:: (GStorableChoice a, ConstraintsPeek a) 
=> Ptr b

Pointer to the variable

-> Int

Offset

-> IO a

Returned variable.

Read the variable from a given pointer.

gpokeByteOff Source #

Arguments

:: (GStorableChoice a, ConstraintsPoke a) 
=> Ptr b

Pointer to the variable.

-> Int

Offset.

-> a

The variable

-> IO () 

Write the variable to a pointer.

Instances
GStorable Bool Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable Char Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable Double Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable Float Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable Int Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable Int8 Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable Int16 Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable Int32 Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable Int64 Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable Word Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable Word8 Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable Word16 Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable Word32 Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable Word64 Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CDev Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CIno Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CMode Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable COff Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CPid Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CSsize Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CGid Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CNlink Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CUid Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CCc Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CSpeed Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CTcflag Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CRLim Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable Fd Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

Methods

gsizeOf :: Fd -> Int Source #

galignment :: Fd -> Int Source #

gpeekByteOff :: Ptr b -> Int -> IO Fd Source #

gpokeByteOff :: Ptr b -> Int -> Fd -> IO () Source #

GStorable CChar Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CSChar Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CUChar Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CShort Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CUShort Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CInt Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CUInt Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CLong Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CULong Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CLLong Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CULLong Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CFloat Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CDouble Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CPtrdiff Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CSigAtomic Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CClock Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CTime Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CUSeconds Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CSUSeconds Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CIntMax Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable CUIntMax Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable WordPtr Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable IntPtr Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable Fingerprint Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable (StablePtr a) Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

GStorable (Ptr a) Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

Methods

gsizeOf :: Ptr a -> Int Source #

galignment :: Ptr a -> Int Source #

gpeekByteOff :: Ptr b -> Int -> IO (Ptr a) Source #

gpokeByteOff :: Ptr b -> Int -> Ptr a -> IO () Source #

GStorable (FunPtr a) Source # 
Instance details

Defined in Foreign.Storable.Generic.Instances

Methods

gsizeOf :: FunPtr a -> Int Source #

galignment :: FunPtr a -> Int Source #

gpeekByteOff :: Ptr b -> Int -> IO (FunPtr a) Source #

gpokeByteOff :: Ptr b -> Int -> FunPtr a -> IO () Source #

class GStorableSum' f where Source #

Work on the sum type.

Methods

seeFirstByte' :: f p -> Int -> Word8 Source #

gsizeOfSum' :: f p -> Int Source #

The size of the biggest subtree

alignOfSum' :: f p -> Int Source #

Alignment of the biggest subtree

gpeekByteOffSum' :: Int -> Ptr b -> Int -> IO (f p) Source #

Peek the type based on the tag.

gpokeByteOffSum' :: Ptr b -> Int -> f p -> IO () Source #

Instances
GStorableSum' (V1 :: Type -> Type) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

seeFirstByte' :: V1 p -> Int -> Word8 Source #

gsizeOfSum' :: V1 p -> Int Source #

alignOfSum' :: V1 p -> Int Source #

gpeekByteOffSum' :: Int -> Ptr b -> Int -> IO (V1 p) Source #

gpokeByteOffSum' :: Ptr b -> Int -> V1 p -> IO () Source #

GStorableSum' (U1 :: Type -> Type) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

seeFirstByte' :: U1 p -> Int -> Word8 Source #

gsizeOfSum' :: U1 p -> Int Source #

alignOfSum' :: U1 p -> Int Source #

gpeekByteOffSum' :: Int -> Ptr b -> Int -> IO (U1 p) Source #

gpokeByteOffSum' :: Ptr b -> Int -> U1 p -> IO () Source #

GStorableSum' (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

seeFirstByte' :: K1 i a p -> Int -> Word8 Source #

gsizeOfSum' :: K1 i a p -> Int Source #

alignOfSum' :: K1 i a p -> Int Source #

gpeekByteOffSum' :: Int -> Ptr b -> Int -> IO (K1 i a p) Source #

gpokeByteOffSum' :: Ptr b -> Int -> K1 i a p -> IO () Source #

(KnownNat (SumArity g), KnownNat (SumArity f), GStorableSum' f, GStorableSum' g) => GStorableSum' (f :+: g) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

seeFirstByte' :: (f :+: g) p -> Int -> Word8 Source #

gsizeOfSum' :: (f :+: g) p -> Int Source #

alignOfSum' :: (f :+: g) p -> Int Source #

gpeekByteOffSum' :: Int -> Ptr b -> Int -> IO ((f :+: g) p) Source #

gpokeByteOffSum' :: Ptr b -> Int -> (f :+: g) p -> IO () Source #

GStorableSum' (f :*: g) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

seeFirstByte' :: (f :*: g) p -> Int -> Word8 Source #

gsizeOfSum' :: (f :*: g) p -> Int Source #

alignOfSum' :: (f :*: g) p -> Int Source #

gpeekByteOffSum' :: Int -> Ptr b -> Int -> IO ((f :*: g) p) Source #

gpokeByteOffSum' :: Ptr b -> Int -> (f :*: g) p -> IO () Source #

GStorableSum' f => GStorableSum' (M1 D t f) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

seeFirstByte' :: M1 D t f p -> Int -> Word8 Source #

gsizeOfSum' :: M1 D t f p -> Int Source #

alignOfSum' :: M1 D t f p -> Int Source #

gpeekByteOffSum' :: Int -> Ptr b -> Int -> IO (M1 D t f p) Source #

gpokeByteOffSum' :: Ptr b -> Int -> M1 D t f p -> IO () Source #

(KnownNat (NoFields f), GStorable' f, GStorableSum' f) => GStorableSum' (M1 C t f) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

seeFirstByte' :: M1 C t f p -> Int -> Word8 Source #

gsizeOfSum' :: M1 C t f p -> Int Source #

alignOfSum' :: M1 C t f p -> Int Source #

gpeekByteOffSum' :: Int -> Ptr b -> Int -> IO (M1 C t f p) Source #

gpokeByteOffSum' :: Ptr b -> Int -> M1 C t f p -> IO () Source #

GStorableSum' f => GStorableSum' (M1 S t f) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

seeFirstByte' :: M1 S t f p -> Int -> Word8 Source #

gsizeOfSum' :: M1 S t f p -> Int Source #

alignOfSum' :: M1 S t f p -> Int Source #

gpeekByteOffSum' :: Int -> Ptr b -> Int -> IO (M1 S t f p) Source #

gpokeByteOffSum' :: Ptr b -> Int -> M1 S t f p -> IO () Source #

class GStorableChoice' (choice :: Bool) a where Source #

Choose a GStorable implementation - whether a sum type (with tag) or raw product type (without the tag).

Methods

chSizeOf :: proxy choice -> a -> Int Source #

chAlignment :: proxy choice -> a -> Int Source #

chPeekByteOff :: proxy choice -> Ptr b -> Int -> IO a Source #

chPokeByteOff :: proxy choice -> Ptr b -> Int -> a -> IO () Source #

Instances
(ConstraintsAll a, IsSumType (Rep a) ~ False) => GStorableChoice' False a Source #

Implementation for the non-sum types.

Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

chSizeOf :: proxy False -> a -> Int Source #

chAlignment :: proxy False -> a -> Int Source #

chPeekByteOff :: proxy False -> Ptr b -> Int -> IO a Source #

chPokeByteOff :: proxy False -> Ptr b -> Int -> a -> IO () Source #

(Generic a, KnownNat (SumArity (Rep a)), GStorableSum' (Rep a), IsSumType (Rep a) ~ True) => GStorableChoice' True a Source #

Implementation for the sum types.

Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

chSizeOf :: proxy True -> a -> Int Source #

chAlignment :: proxy True -> a -> Int Source #

chPeekByteOff :: proxy True -> Ptr b -> Int -> IO a Source #

chPokeByteOff :: proxy True -> Ptr b -> Int -> a -> IO () Source #

internalTagValue :: (KnownNat (SumArity (Rep a)), GStorableSum' (Rep a), Generic a) => a -> Word8 Source #

Get the tag value from the generic representation.

internalSizeOf Source #

Arguments

:: GStorable' f 
=> f p

Generic representation

-> Int

Resulting size

Calculates the size of generic data-type.

internalAlignment Source #

Arguments

:: GStorable' f 
=> f p

Generic representation

-> Alignment

Resulting alignment

Calculates the alignment of generic data-type.

internalPeekByteOff Source #

Arguments

:: (KnownNat (NoFields f), GStorable' f) 
=> Ptr b

Pointer to peek

-> Offset

Offset

-> IO (f p)

Resulting generic representation

View the variable under a pointer, with offset.

internalPokeByteOff Source #

Arguments

:: (KnownNat (NoFields f), GStorable' f) 
=> Ptr b

Pointer to write to

-> Offset

Offset

-> f p

Written generic representation

-> IO () 

Write the variable under the pointer, with offset.

internalOffsets :: forall f p. GStorable' f => f p -> [Offset] Source #

Obtain the list of offsets