module Foreign.Marshal.ContT
(
alloca, allocaWith, allocaBytes, allocaBytesAligned
, calloc, callocBytes
, allocaArray, allocaArrayWith, allocaArray0, allocaArrayWith0
, callocArray, callocArray0
, withForeignPtr
, ToCString(..)
) where
import Control.Monad.Cont
import Control.Monad.IO.Class
import qualified Data.ByteString as BS
import qualified Data.ByteString.Short as SBS
import Data.Foldable
import Foreign.C.String ( CString, CStringLen )
import qualified Foreign.C.String as C
import qualified Foreign.ForeignPtr as C
import Foreign.ForeignPtr ( ForeignPtr )
import qualified Foreign.Marshal.Alloc as C
import qualified Foreign.Marshal.Array as C
import Foreign.Ptr
import Foreign.Storable
alloca :: Storable a => ContT r IO (Ptr a)
alloca = ContT C.alloca
{-# INLINE alloca #-}
allocaWith :: Storable a => a -> ContT r IO (Ptr a)
allocaWith val = do
ptr <- alloca
liftIO $ poke ptr val
return ptr
allocaBytes :: Int -> ContT r IO (Ptr a)
allocaBytes size = ContT $ C.allocaBytes size
{-# INLINE allocaBytes #-}
allocaBytesAligned :: Int -> Int -> ContT r IO (Ptr a)
allocaBytesAligned size alignment = ContT $ C.allocaBytesAligned size alignment
{-# INLINE allocaBytesAligned #-}
calloc :: forall r a. Storable a => ContT r IO (Ptr a)
calloc = ContT $ \f -> do
ptr <- C.calloc
out <- f ptr
C.free ptr
return out
{-# INLINE calloc #-}
callocBytes :: Int -> ContT r IO (Ptr a)
callocBytes size = ContT $ \f -> do
ptr <- C.callocBytes size
out <- f ptr
C.free ptr
return out
{-# INLINE callocBytes #-}
allocaArray :: Storable a => Int -> ContT r IO (Ptr a)
allocaArray = ContT . C.allocaArray
{-# INLINE allocaArray #-}
allocaArrayWith :: (Traversable t, Storable a) => t a -> ContT r IO (Ptr a)
allocaArrayWith t = do
ptr <- allocaArray (length t)
liftIO $ foldrM go ptr t
return ptr
where
go x ptr = do
poke ptr x
return (C.advancePtr ptr 1)
{-# INLINE allocaArrayWith #-}
allocaArray0 :: Storable a => Int -> ContT r IO (Ptr a)
allocaArray0 = ContT . C.allocaArray0
{-# INLINE allocaArray0 #-}
allocaArrayWith0 :: (Traversable t, Storable a) => t a -> a -> ContT r IO (Ptr a)
allocaArrayWith0 t end = do
ptr <- allocaArray0 (length t)
endPtr <- liftIO $ foldrM go ptr t
liftIO $ poke endPtr end
return ptr
where
go x ptr = do
poke ptr x
return (C.advancePtr ptr 1)
{-# INLINE allocaArrayWith0 #-}
callocArray :: Storable a => Int -> ContT r IO (Ptr a)
callocArray len = ContT $ \f -> do
ptr <- C.callocArray len
out <- f ptr
C.free ptr
return out
{-# INLINE callocArray #-}
callocArray0 :: Storable a => Int -> ContT r IO (Ptr a)
callocArray0 len = ContT $ \f -> do
ptr <- C.callocArray0 len
out <- f ptr
C.free ptr
return out
{-# INLINE callocArray0 #-}
withForeignPtr :: ForeignPtr a -> ContT r IO (Ptr a)
withForeignPtr = ContT . C.withForeignPtr
{-# INLINE withForeignPtr #-}
class ToCString a where
withCString :: a -> ContT r IO CString
withCStringLen :: a -> ContT r IO CStringLen
instance ToCString String where
withCString = ContT . C.withCString
{-# INLINE withCString #-}
withCStringLen = ContT . C.withCStringLen
{-# INLINE withCStringLen #-}
instance ToCString BS.ByteString where
withCString = ContT . BS.useAsCString
{-# INLINE withCString #-}
withCStringLen = ContT . BS.useAsCStringLen
{-# INLINE withCStringLen #-}
instance ToCString SBS.ShortByteString where
withCString = ContT . SBS.useAsCString
{-# INLINE withCString #-}
withCStringLen = ContT . SBS.useAsCStringLen
{-# INLINE withCStringLen #-}