module Foreign.Storable.Traversable (
alignment, sizeOf,
peek, poke,
peekApplicative,
) where
import qualified Data.Traversable as Trav
import qualified Data.Foldable as Fold
import qualified Control.Applicative as App
import Control.Monad.Trans.State
(StateT, evalStateT, get, put, modify, )
import Control.Monad.IO.Class (liftIO, )
import Foreign.Storable.FixedArray (roundUp, )
import qualified Foreign.Storable as St
import Foreign.Ptr (Ptr, castPtr, )
import Foreign.Storable (Storable, )
import Foreign.Marshal.Array (advancePtr, )
{-# INLINE elementType #-}
elementType :: f a -> a
elementType _ =
error "Storable.Traversable.alignment and sizeOf may not depend on element values"
{-# INLINE alignment #-}
alignment ::
(Fold.Foldable f, Storable a) =>
f a -> Int
alignment = St.alignment . elementType
{-# INLINE sizeOf #-}
sizeOf ::
(Fold.Foldable f, Storable a) =>
f a -> Int
sizeOf f =
Fold.foldl' (\s _ -> s + 1) 0 f *
roundUp (alignment f) (St.sizeOf (elementType f))
{-# INLINE peek #-}
peek ::
(Trav.Traversable f, Storable a) =>
f () -> Ptr (f a) -> IO (f a)
peek skeleton =
evalStateT (Trav.mapM (const peekState) skeleton) .
castPtr
{-# INLINE peekApplicative #-}
peekApplicative ::
(App.Applicative f, Trav.Traversable f, Storable a) =>
Ptr (f a) -> IO (f a)
peekApplicative =
evalStateT (Trav.sequence (App.pure peekState)) . castPtr
{-# INLINE peekState #-}
peekState ::
(Storable a) =>
StateT (Ptr a) IO a
peekState =
get >>= \p -> put (advancePtr p 1) >> liftIO (St.peek p)
{-# INLINE poke #-}
poke ::
(Fold.Foldable f, Storable a) =>
Ptr (f a) -> f a -> IO ()
poke ptr x =
evalStateT (Fold.traverse_ pokeState x) $
castPtr ptr
{-# INLINE pokeState #-}
pokeState ::
(Storable a) =>
a -> StateT (Ptr a) IO ()
pokeState x = do
liftIO . flip St.poke x =<< get
modify (flip advancePtr 1)