{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wall #-}
module Initialize
( Initialize(initialize, initializeElemOff, initializeElems)
, Deinitialize(deinitialize, deinitializeElemOff, deinitializeElems)
, Uninitialized(..)
) where
import Data.Int (Int, Int8, Int16, Int32, Int64)
import Data.Word (Word, Word8, Word16, Word32, Word64)
import Data.Ord (Ord((<)))
import Data.Eq (Eq)
import Control.Monad (return)
import Data.Char (Char)
import Foreign.Storable (Storable(sizeOf))
import GHC.Ptr (Ptr, plusPtr)
import Foreign.Marshal.Alloc ()
import GHC.IO (IO)
import GHC.Err (undefined)
import GHC.Num (Num((*),(+)))
class Storable a => Initialize a where
#if __GLASGOW_HASKELL__ >= 708
{-# MINIMAL initialize #-}
#endif
initialize :: Ptr a -> IO ()
initializeElemOff :: Ptr a -> Int -> IO ()
initializeElemOff ptr ix = do
initialize (plusPtr ptr (ix * sizeOf (undefined :: a)) :: Ptr a)
initializeElems :: Ptr a -> Int -> IO ()
initializeElems ptr n = go 0 where
go !i = if i < n
then do
initialize (plusPtr ptr (i * sizeOf (undefined :: a)) :: Ptr a)
go (i + 1)
else return ()
class Storable a => Deinitialize a where
#if __GLASGOW_HASKELL__ >= 708
{-# MINIMAL deinitialize #-}
#endif
deinitialize :: Ptr a -> IO ()
deinitializeElemOff :: Ptr a -> Int -> IO ()
deinitializeElemOff ptr ix =
deinitialize (plusPtr ptr (ix * sizeOf (undefined :: a)) :: Ptr a)
deinitializeElems :: Ptr a -> Int -> IO ()
deinitializeElems ptr n = go 0 where
go !i = if i < n
then do
deinitialize (plusPtr ptr (i * sizeOf (undefined :: a)) :: Ptr a)
go (i + 1)
else return ()
newtype Uninitialized a = Uninitialized a
deriving (Eq, Storable)
instance Storable a => Initialize (Uninitialized a) where
initialize _ = return ()
initializeElemOff _ _ = return ()
initializeElems _ _ = return ()
instance Storable a => Deinitialize (Uninitialized a) where
deinitialize _ = return ()
deinitializeElemOff _ _ = return ()
deinitializeElems _ _ = return ()
#define deriveInit(ty) \
instance Initialize (ty) where { \
initialize _ = return () \
; initializeElemOff _ _ = return () \
; initializeElems _ _ = return () \
; {-# INLINE initialize #-} \
; {-# INLINE initializeElemOff #-} \
; {-# INLINE initializeElems #-} \
}
deriveInit(Word)
deriveInit(Word8)
deriveInit(Word16)
deriveInit(Word32)
deriveInit(Word64)
deriveInit(Int)
deriveInit(Int8)
deriveInit(Int16)
deriveInit(Int32)
deriveInit(Int64)
deriveInit(Char)
#define deriveDeinit(ty) \
instance Deinitialize (ty) where { \
deinitialize _ = return () \
; deinitializeElemOff _ _ = return () \
; deinitializeElems _ _ = return () \
; {-# INLINE deinitialize #-} \
; {-# INLINE deinitializeElemOff #-} \
; {-# INLINE deinitializeElems #-} \
}
deriveDeinit(Word)
deriveDeinit(Word8)
deriveDeinit(Word16)
deriveDeinit(Word32)
deriveDeinit(Word64)
deriveDeinit(Int)
deriveDeinit(Int8)
deriveDeinit(Int16)
deriveDeinit(Int32)
deriveDeinit(Int64)
deriveDeinit(Char)