module Foreign.Storable.Generic (
GStorable(..),
sizeOfDefault,
alignmentDefault,
peekDefault,
peekByteOffDefault,
peekElemOffDefault,
pokeDefault,
pokeByteOffDefault,
pokeElemOffDefault,
StorableWrapper(..),
) where
import Control.Monad
import Data.Word
import Foreign.Ptr
import Foreign.Storable
import GHC.Generics
class GStorable f where
gsizeOf :: f a -> Int
galignment :: f a -> Int
galignment = gsizeOf
gpeek :: Ptr (f a) -> IO (f a)
gpeekByteOff :: Ptr (f a) -> Int -> IO (f a)
gpeekByteOff addr off = gpeek (addr `plusPtr` off)
gpeekElemOff :: Ptr (f a) -> Int -> IO (f a)
gpeekElemOff addr idx = gpeek (addr `plusPtr` (idx * gsizeOf (undefined :: f a)))
gpoke :: Ptr (f a) -> f a -> IO ()
gpokeByteOff :: Ptr (f a) -> Int -> f a -> IO ()
gpokeByteOff addr off = gpoke (addr `plusPtr` off)
gpokeElemOff :: Ptr (f a) -> Int -> f a -> IO ()
gpokeElemOff addr idx = gpoke (addr `plusPtr` (idx * gsizeOf (undefined :: f a)))
sizeOfDefault :: (Generic a, GStorable (Rep a)) => a -> Int
sizeOfDefault = gsizeOf . from
alignmentDefault :: (Generic a, GStorable (Rep a)) => a -> Int
alignmentDefault = galignment . from
peekDefault :: (Generic a, GStorable (Rep a)) => Ptr a -> IO a
peekDefault ptr = to <$> gpeek (castPtr ptr)
peekByteOffDefault :: (Generic a, GStorable (Rep a)) => Ptr a -> Int -> IO a
peekByteOffDefault ptr ofs = to <$> gpeekByteOff (castPtr ptr) ofs
peekElemOffDefault :: (Generic a, GStorable (Rep a)) => Ptr a -> Int -> IO a
peekElemOffDefault ptr idx = to <$> gpeekElemOff (castPtr ptr) idx
pokeDefault :: (Generic a, GStorable (Rep a)) => Ptr a -> a -> IO ()
pokeDefault ptr = gpoke (castPtr ptr) . from
pokeByteOffDefault :: (Generic a, GStorable (Rep a)) => Ptr a -> Int -> a -> IO ()
pokeByteOffDefault ptr ofs = gpokeByteOff (castPtr ptr) ofs . from
pokeElemOffDefault :: (Generic a, GStorable (Rep a)) => Ptr a -> Int -> a -> IO ()
pokeElemOffDefault ptr idx = gpokeElemOff (castPtr ptr) idx . from
newtype StorableWrapper a = StorableWrapper { unStorableWrapper :: a }
instance (Generic a, GStorable (Rep a)) => Storable (StorableWrapper a) where
sizeOf _ = gsizeOf $ from (undefined :: a)
alignment _ = galignment $ from (undefined :: a)
peek ptr = StorableWrapper . to <$> gpeek (castPtr ptr)
poke ptr (StorableWrapper v) = gpoke (castPtr ptr) $ from v
instance GStorable U1 where
gsizeOf _ = 0
gpeek _ = return U1
gpoke _ _ = return ()
instance (GStorable a, GStorable b) => GStorable (a :*: b) where
gsizeOf _ = gsizeOf (undefined :: a x) + gsizeOf (undefined :: b x)
gpeek ptr = do
a <- gpeek (castPtr ptr)
b <- gpeekByteOff (castPtr ptr) (gsizeOf a)
return $ a :*: b
gpoke ptr (a :*: b) = do
gpoke (castPtr ptr) a
gpokeByteOff (castPtr ptr) (gsizeOf a) b
instance (GStorable a, GStorable b) => GStorable (a :+: b) where
gsizeOf _ = 4 + (gsizeOf (undefined :: a x) `max` gsizeOf (undefined :: b x))
gpeek ptr = do
tag <- peek (castPtr ptr)
if (tag :: Word32) == 0
then return L1 `ap` gpeekByteOff (castPtr ptr) 4
else return R1 `ap` gpeekByteOff (castPtr ptr) 4
gpoke ptr (L1 val) = poke (castPtr ptr) (0 :: Word32) >> gpokeByteOff (castPtr ptr) 4 val
gpoke ptr (R1 val) = poke (castPtr ptr) (1 :: Word32) >> gpokeByteOff (castPtr ptr) 4 val
instance (GStorable a) => GStorable (M1 i c a) where
gsizeOf _ = gsizeOf (undefined :: a x)
gpeek ptr = return M1 `ap` gpeek (castPtr ptr)
gpoke ptr (M1 val) = gpoke (castPtr ptr) val
instance (Storable a) => GStorable (K1 i a) where
gsizeOf _ = sizeOf (undefined :: a)
gpeek ptr = return K1 `ap` peek (castPtr ptr)
gpoke ptr (K1 val) = poke (castPtr ptr) val