{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Data.Prim
( Prim
, Atom(..)
, Atomic
, AtomicCount
, AtomicBits
, MonadPrim
, RW
, RealWorld
, byteCount
, byteCountType
, byteCountProxy
, alignment
, alignmentType
, alignmentProxy
, Size(..)
, Count(..)
, unCountBytes
, toByteCount
, unCountBytes#
, fromByteCount
, fromByteCountRem
, countToOff
, countToByteOff
, countForType
, countForProxyTypeOf
, Off(..)
, unOffBytes
, toByteOff
, unOffBytes#
, fromByteOff
, fromByteOffRem
, offToCount
, offToByteCount
, offForType
, offForProxyTypeOf
, prefetchValue0
, prefetchValue1
, prefetchValue2
, prefetchValue3
, module Data.Word
, module Data.Int
, Ptr
, ForeignPtr
, Typeable
, Proxy(..)
, module Data.Semigroup
, module Data.Monoid
, module Data.Coerce
) where
import Control.DeepSeq
import Control.Prim.Monad
import Data.Coerce
import Data.Int
import Data.Monoid hiding (First(..), Last(..), (<>))
import Data.Prim.Atom
import Data.Prim.Atomic
import Data.Prim.Class
import Data.Semigroup
import Data.Typeable
import Data.Word
import Foreign.ForeignPtr (ForeignPtr)
import GHC.Base (quotInt, quotRemInt)
import GHC.Exts
newtype Size = Size { unSize :: Int }
deriving (Show, Eq, Ord, Num, Real, Integral, Bounded, Enum)
byteCount :: forall e . Prim e => e -> Count Word8
byteCount _ = coerce (I# (sizeOf# (proxy# :: Proxy# e)))
{-# INLINE byteCount #-}
byteCountType :: forall e . Prim e => Count Word8
byteCountType = coerce (I# (sizeOf# (proxy# :: Proxy# e)))
{-# INLINE byteCountType #-}
byteCountProxy :: forall proxy e . Prim e => proxy e -> Count Word8
byteCountProxy _ = coerce (I# (sizeOf# (proxy# :: Proxy# e)))
{-# INLINE byteCountProxy #-}
alignment :: forall e . Prim e => e -> Int
alignment _ = I# (alignment# (proxy# :: Proxy# e))
{-# INLINE alignment #-}
alignmentType :: forall e . Prim e => Int
alignmentType = I# (alignment# (proxy# :: Proxy# e))
{-# INLINE alignmentType #-}
alignmentProxy :: forall proxy e . Prim e => proxy e -> Int
alignmentProxy _ = I# (alignment# (proxy# :: Proxy# e))
{-# INLINE alignmentProxy #-}
newtype Count e = Count
{ unCount :: Int
} deriving (Eq, Show, Ord, Enum, Bounded, Num, Integral, Real, NFData)
instance Prim (Count e) where
type PrimBase (Count e) = Int
unCountWord8# :: Count Word8 -> Int#
unCountWord8# (Count (I# n#)) = n#
{-# INLINE unCountWord8# #-}
unCountInt8# :: Count Int8 -> Int#
unCountInt8# (Count (I# n#)) = n#
{-# INLINE unCountInt8# #-}
unCountBytes# :: Prim e => Count e -> Int#
unCountBytes# c@(Count (I# n#)) =
case coerce (byteCountProxy c) of
I# sz# -> sz# *# n#
{-# INLINE[0] unCountBytes# #-}
{-# RULES
"unCountWord8#" unCountBytes# = unCountWord8#
"unCountInt8#" unCountBytes# = unCountInt8#
#-}
unCountBytes :: Prim e => Count e -> Int
unCountBytes c = I# (unCountBytes# c)
{-# INLINE unCountBytes #-}
toByteCount :: Prim e => Count e -> Count Word8
toByteCount = Count . unCountBytes
{-# INLINE toByteCount #-}
countToOff :: Count e -> Off e
countToOff = coerce
countToByteOff :: Prim e => Count e -> Off Word8
countToByteOff = countToOff . toByteCount
{-# INLINE countToByteOff #-}
countForProxyTypeOf :: Count e -> proxy e -> Count e
countForProxyTypeOf count _ = count
countForType :: Count e -> e -> Count e
countForType count _ = count
fromByteCountInt8 :: Count Word8 -> Count Int8
fromByteCountInt8 = coerce
{-# INLINE fromByteCountInt8 #-}
fromByteCount :: forall e . Prim e => Count Word8 -> Count e
fromByteCount sz = coerce (quotSizeOfWith (proxy# :: Proxy# e) (coerce sz) 0 quotInt)
{-# INLINE[0] fromByteCount #-}
{-# RULES
"fromByteCount" fromByteCount = id
"fromByteCount" fromByteCount = fromByteCountInt8
#-}
fromByteCountRemWord8 :: Count Word8 -> (Count Word8, Count Word8)
fromByteCountRemWord8 i = (coerce i, 0)
{-# INLINE fromByteCountRemWord8 #-}
fromByteCountRemInt8 :: Count Word8 -> (Count Int8, Count Word8)
fromByteCountRemInt8 i = (coerce i, 0)
{-# INLINE fromByteCountRemInt8 #-}
fromByteCountRem :: forall e . Prim e => Count Word8 -> (Count e, Count Word8)
fromByteCountRem sz = coerce (quotSizeOfWith (proxy# :: Proxy# e) (coerce sz) (0, 0) quotRemInt)
{-# INLINE[0] fromByteCountRem #-}
{-# RULES
"fromByteCountRemWord8" fromByteCountRem = fromByteCountRemWord8
"fromByteCountRemInt8" fromByteCountRem = fromByteCountRemInt8
#-}
quotSizeOfWith :: forall e b. Prim e => Proxy# e -> Int -> b -> (Int -> Int -> b) -> b
quotSizeOfWith px# sz onZero quotWith
| tySize <= 0 = onZero
| otherwise = sz `quotWith` tySize
where
tySize = I# (sizeOf# px#)
{-# INLINE quotSizeOfWith #-}
newtype Off e = Off
{ unOff :: Int
} deriving (Eq, Show, Ord, Enum, Bounded, Num, Integral, Real, NFData)
instance Prim (Off e) where
type PrimBase (Off e) = Int
offForProxyTypeOf :: Off e -> proxy e -> Off e
offForProxyTypeOf off _ = off
offForType :: Off e -> e -> Off e
offForType c _ = c
offToCount :: Off e -> Count e
offToCount = coerce
offToByteCount :: Prim e => Off e -> Count Word8
offToByteCount = offToCount . toByteOff
{-# INLINE offToByteCount #-}
toByteOff :: Prim e => Off e -> Off Word8
toByteOff off = Off (I# (unOffBytes# off))
{-# INLINE toByteOff #-}
unOffBytes :: Prim e => Off e -> Int
unOffBytes off = I# (unOffBytes# off)
{-# INLINE unOffBytes #-}
unOffWord8# :: Off Word8 -> Int#
unOffWord8# (Off (I# o#)) = o#
{-# INLINE unOffWord8# #-}
unOffInt8# :: Off Int8 -> Int#
unOffInt8# (Off (I# o#)) = o#
{-# INLINE unOffInt8# #-}
unOffBytes# :: Prim e => Off e -> Int#
unOffBytes# o@(Off (I# o#)) =
case coerce (byteCountProxy o) of
I# sz# -> sz# *# o#
{-# INLINE[0] unOffBytes# #-}
{-# RULES
"unOffWord8#" unOffBytes# = unOffWord8#
"unOffInt8#" unOffBytes# = unOffInt8#
#-}
fromByteOffInt8 :: Off Word8 -> Off Int8
fromByteOffInt8 = coerce
{-# INLINE fromByteOffInt8 #-}
fromByteOff :: forall e . Prim e => Off Word8 -> Off e
fromByteOff sz = coerce (quotSizeOfWith (proxy# :: Proxy# e) (coerce sz) 0 quotInt)
{-# INLINE[0] fromByteOff #-}
{-# RULES
"fromByteOff" fromByteOff = id
"fromByteOff" fromByteOff = fromByteOffInt8
#-}
fromByteOffRemWord8 :: Off Word8 -> (Off Word8, Off Word8)
fromByteOffRemWord8 i = (coerce i, 0)
{-# INLINE fromByteOffRemWord8 #-}
fromByteOffRemInt8 :: Off Word8 -> (Off Int8, Off Word8)
fromByteOffRemInt8 i = (coerce i, 0)
{-# INLINE fromByteOffRemInt8 #-}
fromByteOffRem :: forall e . Prim e => Off Word8 -> (Off e, Off Word8)
fromByteOffRem sz = coerce (quotSizeOfWith (proxy# :: Proxy# e) (coerce sz) (0, 0) quotRemInt)
{-# INLINE[0] fromByteOffRem #-}
{-# RULES
"fromByteOffRemWord8" fromByteOffRem = fromByteOffRemWord8
"fromByteOffRemInt8" fromByteOffRem = fromByteOffRemInt8
#-}
prefetchValue0 :: MonadPrim s m => a -> m ()
prefetchValue0 a = prim_ (prefetchValue0# a)
{-# INLINE prefetchValue0 #-}
prefetchValue1 :: MonadPrim s m => a -> m ()
prefetchValue1 a = prim_ (prefetchValue1# a)
{-# INLINE prefetchValue1 #-}
prefetchValue2 :: MonadPrim s m => a -> m ()
prefetchValue2 a = prim_ (prefetchValue2# a)
{-# INLINE prefetchValue2 #-}
prefetchValue3 :: MonadPrim s m => a -> m ()
prefetchValue3 a = prim_ (prefetchValue3# a)
{-# INLINE prefetchValue3 #-}