{-#LANGUAGE FlexibleInstances #-}
{-#LANGUAGE FlexibleContexts #-}
{-#LANGUAGE DefaultSignatures #-}
{-#LANGUAGE TypeOperators #-}
{-#LANGUAGE ScopedTypeVariables #-}
{-#LANGUAGE UndecidableInstances #-}
module Foreign.Storable.Generic.Internal (
GStorable'(..),
GStorable (..),
internalSizeOf,
internalAlignment,
internalPeekByteOff,
internalPokeByteOff,
internalOffsets
) where
import GHC.Generics
import Foreign.Ptr
import Foreign.Storable
import Foreign.Marshal.Alloc
import Foreign.C.Types
import Data.Int
import Debug.Trace
import Foreign.Storable.Generic.Tools
import GHC.Exts
class GStorable' f where
gpeekByteOff' :: [Int]
-> Int
-> Ptr b
-> Int
-> IO (f a)
gpokeByteOff' :: [Int]
-> Int
-> Ptr b
-> Int
-> (f a)
-> IO ()
gnumberOf' :: f a
-> Int
glistSizeOf' :: f a
-> [Size]
glistAlignment' :: f a
-> [Alignment]
instance (GStorable' f) => GStorable' (M1 i t f) where
{-# INLINE gpeekByteOff' #-}
gpeekByteOff' offsets ix ptr offset = M1 <$> gpeekByteOff' offsets ix ptr offset
{-# INLINE gpokeByteOff' #-}
gpokeByteOff' offsets ix ptr offset (M1 x) = gpokeByteOff' offsets ix ptr offset x
gnumberOf' (M1 v) = gnumberOf' v
glistSizeOf' _ = glistSizeOf' (undefined :: f p)
glistAlignment' _ = glistAlignment' (undefined :: f p)
instance GStorable' U1 where
{-# INLINE gpeekByteOff' #-}
gpeekByteOff' offsets ix ptr offset = return U1
{-# INLINE gpokeByteOff' #-}
gpokeByteOff' offsets ix ptr offset (U1) = return ()
gnumberOf' (U1) = 0
glistSizeOf' _ = []
glistAlignment' _ = []
instance (GStorable' f, GStorable' g) => GStorable' (f :*: g) where
{-# INLINE gpeekByteOff' #-}
gpeekByteOff' offsets ix ptr offset = (:*:) <$> peeker new_ix <*> peeker ix
where new_ix = ix - n2
n2 = gnumberOf' (undefined :: g a)
peeker n_ix = gpeekByteOff' offsets n_ix ptr offset
{-# INLINE gpokeByteOff' #-}
gpokeByteOff' offsets ix ptr offset (x :*: y) = peeker new_ix x >> peeker ix y
where new_ix = ix - n2
n2 = gnumberOf' (undefined :: g a)
peeker n_ix z = gpokeByteOff' offsets n_ix ptr offset z
gnumberOf' _ = gnumberOf' (undefined :: f a) + gnumberOf' (undefined :: g a)
glistSizeOf' _ = glistSizeOf' (undefined :: f a) ++ glistSizeOf' (undefined :: g a)
glistAlignment' _ = glistAlignment' (undefined :: f a) ++ glistAlignment' (undefined :: g a)
instance (GStorable a) => GStorable' (K1 i a) where
{-# INLINE gpeekByteOff' #-}
gpeekByteOff' offsets ix ptr offset = K1 <$> gpeekByteOff ptr (off1 + offset)
where off1 = inline (offsets !! ix)
{-# INLINE gpokeByteOff' #-}
gpokeByteOff' offsets ix ptr offset (K1 x) = gpokeByteOff ptr (off1 + offset) x
where off1 = inline (offsets !! ix)
gnumberOf' _ = 1
glistSizeOf' _ = [gsizeOf (undefined :: a)]
glistAlignment' _ = [galignment (undefined :: a)]
{-# INLINE internalSizeOf #-}
internalSizeOf :: forall f p. (GStorable' f)
=> f p
-> Int
internalSizeOf _ = calcSize $ zip sizes aligns
where sizes = glistSizeOf' (undefined :: f p)
aligns = glistAlignment' (undefined :: f p)
{-# INLINE internalAlignment #-}
internalAlignment :: forall f p. (GStorable' f)
=> f p
-> Alignment
internalAlignment _ = calcAlignment aligns
where aligns = glistAlignment' (undefined :: f p)
{-# INLINE internalPeekByteOff #-}
internalPeekByteOff :: forall f p b. (GStorable' f)
=> Ptr b
-> Offset
-> IO (f p)
internalPeekByteOff ptr off = gpeekByteOff' offsets ix ptr off
where offsets = internalOffsets (undefined :: f p)
ix = gnumberOf' (undefined :: f p) - 1
{-# INLINE internalPokeByteOff #-}
internalPokeByteOff :: forall f p b. (GStorable' f)
=> Ptr b
-> Offset
-> f p
-> IO ()
internalPokeByteOff ptr off rep = gpokeByteOff' offsets ix ptr off rep
where offsets = internalOffsets (undefined :: f p)
ix = gnumberOf' (undefined :: f p) - 1
{-# INLINE internalOffsets #-}
internalOffsets :: forall f p. (GStorable' f)
=> f p
-> [Offset]
internalOffsets _ = calcOffsets $ zip sizes aligns
where sizes = glistSizeOf' (undefined :: f p)
aligns= glistAlignment' (undefined :: f p)
class GStorable a where
{-# INLINE gsizeOf #-}
gsizeOf :: a
-> Int
default gsizeOf :: (Generic a, GStorable' (Rep a))
=> a -> Int
gsizeOf _ = internalSizeOf (undefined :: Rep a p)
{-# INLINE galignment #-}
galignment :: a
-> Int
default galignment :: (Generic a, GStorable' (Rep a))
=> a -> Int
galignment _ = internalAlignment (undefined :: Rep a p)
gpeekByteOff :: Ptr b
-> Int
-> IO a
default gpeekByteOff :: (Generic a, GStorable' (Rep a))
=> Ptr b -> Int -> IO a
{-# INLINE gpeekByteOff #-}
gpeekByteOff ptr offset = to <$> internalPeekByteOff ptr offset
gpokeByteOff :: Ptr b
-> Int
-> a
-> IO ()
default gpokeByteOff :: (Generic a, GStorable' (Rep a))
=> Ptr b -> Int -> a -> IO ()
{-# INLINE gpokeByteOff #-}
gpokeByteOff ptr offset x = internalPokeByteOff ptr offset (from x)