{-#LANGUAGE FlexibleInstances #-}
{-#LANGUAGE FlexibleContexts #-}
{-#LANGUAGE TypeOperators #-}
{-#LANGUAGE ScopedTypeVariables #-}
{-#LANGUAGE UndecidableInstances #-}
module Foreign.Storable.Generic (GStorable (..), Storable(..), getFilling) where
import Foreign.Storable (Storable(..))
import GHC.Generics
import Foreign.Storable.Generic.Internal (GStorable (..), GStorable' (..))
import qualified Foreign.Storable.Generic.Tools as Tools
getFilling :: (Generic a, GStorable a, GStorable' (Rep a)) => a -> [Tools.Filling]
getFilling :: a -> [Filling]
getFilling a
x = [(Size, Size)] -> [Filling]
Tools.getFilling ([(Size, Size)] -> [Filling]) -> [(Size, Size)] -> [Filling]
forall a b. (a -> b) -> a -> b
$ [Size] -> [Size] -> [(Size, Size)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Size]
sizes [Size]
aligns
where sizes :: [Size]
sizes = Rep a Any -> [Size]
forall (f :: * -> *) a. GStorable' f => f a -> [Size]
glistSizeOf' Rep a Any
forall x. Rep a x
gx
aligns :: [Size]
aligns = Rep a Any -> [Size]
forall (f :: * -> *) a. GStorable' f => f a -> [Size]
glistAlignment' Rep a Any
forall x. Rep a x
gx
gx :: Rep a x
gx = a -> Rep a x
forall a x. Generic a => a -> Rep a x
from a
x