Copyright | (c) Mateusz Kłoczko 2016 |
---|---|
License | MIT |
Maintainer | mateusz.p.kloczko@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class GStorable' f where
- gpeekByteOff' :: [Int] -> Int -> Ptr b -> Int -> IO (f a)
- gpokeByteOff' :: [Int] -> Int -> Ptr b -> Int -> f a -> IO ()
- glistSizeOf' :: f a -> [Size]
- glistAlignment' :: f a -> [Alignment]
- class GStorable a where
- gsizeOf :: a -> Int
- galignment :: a -> Int
- gpeekByteOff :: Ptr b -> Int -> IO a
- gpokeByteOff :: Ptr b -> Int -> a -> IO ()
- class GStorableSum' f where
- seeFirstByte' :: f p -> Int -> Word8
- gsizeOfSum' :: f p -> Int
- alignOfSum' :: f p -> Int
- gpeekByteOffSum' :: Int -> Ptr b -> Int -> IO (f p)
- gpokeByteOffSum' :: Ptr b -> Int -> f p -> IO ()
- class GStorableChoice' (choice :: Bool) a where
- chSizeOf :: proxy choice -> a -> Int
- chAlignment :: proxy choice -> a -> Int
- chPeekByteOff :: proxy choice -> Ptr b -> Int -> IO a
- chPokeByteOff :: proxy choice -> Ptr b -> Int -> a -> IO ()
- type GStorableChoice a = GStorableChoice' (IsSumType (Rep a)) a
- internalTagValue :: (KnownNat (SumArity (Rep a)), GStorableSum' (Rep a), Generic a) => a -> Word8
- internalSizeOf :: forall f p. GStorable' f => f p -> Int
- internalAlignment :: forall f p. GStorable' f => f p -> Alignment
- internalPeekByteOff :: forall f p b. (KnownNat (NoFields f), GStorable' f) => Ptr b -> Offset -> IO (f p)
- internalPokeByteOff :: forall f p b. (KnownNat (NoFields f), GStorable' f) => Ptr b -> Offset -> f p -> IO ()
- internalOffsets :: forall f p. GStorable' f => f p -> [Offset]
Documentation
class GStorable' f where Source #
:: [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.
:: [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 () |
:: f a | GHC.Generic information about a given type/struct. |
-> [Size] | List of sizes. |
Calculates the sizes of type's/struct's fields.
:: 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 # | |
GStorable a => GStorable' (K1 i a :: Type -> Type) Source # | |
(KnownNat (NoFields f), KnownNat (NoFields g), GStorable' f, GStorable' g) => GStorable' (f :*: g) Source # | |
GStorable' f => GStorable' (M1 i t f) 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.
Nothing
:: a | Element of a given type. Can be undefined. |
-> Int | Size. |
Calculate the size of the type.
:: a | Element of a given type. Can be undefined |
-> Int | Alignment. |
Calculate the alignment of the type.
Read the variable from a given pointer.
Write the variable to a pointer.
:: (ConstraintsSize a, GStorableChoice a) | |
=> a | Element of a given type. Can be undefined. |
-> Int | Size. |
Calculate the size of the type.
:: (ConstraintsAlignment a, GStorableChoice a) | |
=> a | Element of a given type. Can be undefined |
-> Int | Alignment. |
Calculate the alignment of the type.
:: (GStorableChoice a, ConstraintsPeek a) | |
=> Ptr b | Pointer to the variable |
-> Int | Offset |
-> IO a | Returned variable. |
Read the variable from a given pointer.
:: (GStorableChoice a, ConstraintsPoke a) | |
=> Ptr b | Pointer to the variable. |
-> Int | Offset. |
-> a | The variable |
-> IO () |
Write the variable to a pointer.
Instances
class GStorableSum' f where Source #
Work on the sum type.
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.
Instances
GStorableSum' (V1 :: Type -> Type) Source # | |
GStorableSum' (U1 :: Type -> Type) Source # | |
GStorableSum' (K1 i a :: Type -> Type) Source # | |
Defined in Foreign.Storable.Generic.Internal | |
(KnownNat (SumArity g), KnownNat (SumArity f), GStorableSum' f, GStorableSum' g) => GStorableSum' (f :+: g) Source # | |
Defined in Foreign.Storable.Generic.Internal | |
GStorableSum' (f :*: g) Source # | |
Defined in Foreign.Storable.Generic.Internal | |
GStorableSum' f => GStorableSum' (M1 D t f) Source # | |
Defined in Foreign.Storable.Generic.Internal | |
(KnownNat (NoFields f), GStorable' f, GStorableSum' f) => GStorableSum' (M1 C t f) Source # | |
Defined in Foreign.Storable.Generic.Internal | |
GStorableSum' f => GStorableSum' (M1 S t f) Source # | |
Defined in Foreign.Storable.Generic.Internal |
class GStorableChoice' (choice :: Bool) a where Source #
Choose a GStorable implementation - whether a sum type (with tag) or raw product type (without the tag).
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 #
type GStorableChoice a = GStorableChoice' (IsSumType (Rep a)) a Source #
internalTagValue :: (KnownNat (SumArity (Rep a)), GStorableSum' (Rep a), Generic a) => a -> Word8 Source #
Get the tag value from the generic representation.
:: GStorable' f | |
=> f p | Generic representation |
-> Int | Resulting size |
Calculates the size of generic data-type.
:: GStorable' f | |
=> f p | Generic representation |
-> Alignment | Resulting alignment |
Calculates the alignment of generic data-type.
:: (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.
:: (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