{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Data.Prim
  ( Prim
  , Atom(..)
  , Atomic
  , AtomicCount
  , AtomicBits
  , MonadPrim
  , RW
  , RealWorld
  , ST
  , runST
  , showsType
  
  , byteCount
  , byteCountType
  , byteCountProxy
  
  , alignment
  , alignmentType
  , alignmentProxy
  
  , 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.Coerce
  , (#.)
  , (.#)
  , module Data.Semigroup
  , module Data.Monoid
  ) 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
showsType :: Typeable t => proxy t -> ShowS
showsType :: proxy t -> ShowS
showsType = TypeRep -> ShowS
showsTypeRep (TypeRep -> ShowS) -> (proxy t -> TypeRep) -> proxy t -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. proxy t -> TypeRep
forall k (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep
byteCount :: forall e . Prim e => e -> Count Word8
byteCount :: e -> Count Word8
byteCount e
_ = Int -> Count Word8
coerce (Int# -> Int
I# (Proxy# e -> Int#
forall a. Prim a => Proxy# a -> Int#
sizeOf# (Proxy# e
forall k (a :: k). Proxy# a
proxy# :: Proxy# e)))
{-# INLINE byteCount #-}
byteCountType :: forall e . Prim e => Count Word8
byteCountType :: Count Word8
byteCountType = Int -> Count Word8
coerce (Int# -> Int
I# (Proxy# e -> Int#
forall a. Prim a => Proxy# a -> Int#
sizeOf# (Proxy# e
forall k (a :: k). Proxy# a
proxy# :: Proxy# e)))
{-# INLINE byteCountType #-}
byteCountProxy :: forall proxy e . Prim e => proxy e -> Count Word8
byteCountProxy :: proxy e -> Count Word8
byteCountProxy proxy e
_ = Int -> Count Word8
coerce (Int# -> Int
I# (Proxy# e -> Int#
forall a. Prim a => Proxy# a -> Int#
sizeOf# (Proxy# e
forall k (a :: k). Proxy# a
proxy# :: Proxy# e)))
{-# INLINE byteCountProxy #-}
alignment :: forall e . Prim e => e -> Int
alignment :: e -> Int
alignment e
_ = Int# -> Int
I# (Proxy# e -> Int#
forall a. Prim a => Proxy# a -> Int#
alignment# (Proxy# e
forall k (a :: k). Proxy# a
proxy# :: Proxy# e))
{-# INLINE alignment #-}
alignmentType :: forall e . Prim e => Int
alignmentType :: Int
alignmentType = Int# -> Int
I# (Proxy# e -> Int#
forall a. Prim a => Proxy# a -> Int#
alignment# (Proxy# e
forall k (a :: k). Proxy# a
proxy# :: Proxy# e))
{-# INLINE alignmentType #-}
alignmentProxy :: forall proxy e . Prim e => proxy e -> Int
alignmentProxy :: proxy e -> Int
alignmentProxy proxy e
_ = Int# -> Int
I# (Proxy# e -> Int#
forall a. Prim a => Proxy# a -> Int#
alignment# (Proxy# e
forall k (a :: k). Proxy# a
proxy# :: Proxy# e))
{-# INLINE alignmentProxy #-}
newtype Count e = Count
  { Count e -> Int
unCount :: Int
  } deriving (Count e -> Count e -> Bool
(Count e -> Count e -> Bool)
-> (Count e -> Count e -> Bool) -> Eq (Count e)
forall e. Count e -> Count e -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Count e -> Count e -> Bool
$c/= :: forall e. Count e -> Count e -> Bool
== :: Count e -> Count e -> Bool
$c== :: forall e. Count e -> Count e -> Bool
Eq, Int -> Count e -> ShowS
[Count e] -> ShowS
Count e -> String
(Int -> Count e -> ShowS)
-> (Count e -> String) -> ([Count e] -> ShowS) -> Show (Count e)
forall e. Int -> Count e -> ShowS
forall e. [Count e] -> ShowS
forall e. Count e -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Count e] -> ShowS
$cshowList :: forall e. [Count e] -> ShowS
show :: Count e -> String
$cshow :: forall e. Count e -> String
showsPrec :: Int -> Count e -> ShowS
$cshowsPrec :: forall e. Int -> Count e -> ShowS
Show, Eq (Count e)
Eq (Count e)
-> (Count e -> Count e -> Ordering)
-> (Count e -> Count e -> Bool)
-> (Count e -> Count e -> Bool)
-> (Count e -> Count e -> Bool)
-> (Count e -> Count e -> Bool)
-> (Count e -> Count e -> Count e)
-> (Count e -> Count e -> Count e)
-> Ord (Count e)
Count e -> Count e -> Bool
Count e -> Count e -> Ordering
Count e -> Count e -> Count e
forall e. Eq (Count e)
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall e. Count e -> Count e -> Bool
forall e. Count e -> Count e -> Ordering
forall e. Count e -> Count e -> Count e
min :: Count e -> Count e -> Count e
$cmin :: forall e. Count e -> Count e -> Count e
max :: Count e -> Count e -> Count e
$cmax :: forall e. Count e -> Count e -> Count e
>= :: Count e -> Count e -> Bool
$c>= :: forall e. Count e -> Count e -> Bool
> :: Count e -> Count e -> Bool
$c> :: forall e. Count e -> Count e -> Bool
<= :: Count e -> Count e -> Bool
$c<= :: forall e. Count e -> Count e -> Bool
< :: Count e -> Count e -> Bool
$c< :: forall e. Count e -> Count e -> Bool
compare :: Count e -> Count e -> Ordering
$ccompare :: forall e. Count e -> Count e -> Ordering
$cp1Ord :: forall e. Eq (Count e)
Ord, Int -> Count e
Count e -> Int
Count e -> [Count e]
Count e -> Count e
Count e -> Count e -> [Count e]
Count e -> Count e -> Count e -> [Count e]
(Count e -> Count e)
-> (Count e -> Count e)
-> (Int -> Count e)
-> (Count e -> Int)
-> (Count e -> [Count e])
-> (Count e -> Count e -> [Count e])
-> (Count e -> Count e -> [Count e])
-> (Count e -> Count e -> Count e -> [Count e])
-> Enum (Count e)
forall e. Int -> Count e
forall e. Count e -> Int
forall e. Count e -> [Count e]
forall e. Count e -> Count e
forall e. Count e -> Count e -> [Count e]
forall e. Count e -> Count e -> Count e -> [Count e]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Count e -> Count e -> Count e -> [Count e]
$cenumFromThenTo :: forall e. Count e -> Count e -> Count e -> [Count e]
enumFromTo :: Count e -> Count e -> [Count e]
$cenumFromTo :: forall e. Count e -> Count e -> [Count e]
enumFromThen :: Count e -> Count e -> [Count e]
$cenumFromThen :: forall e. Count e -> Count e -> [Count e]
enumFrom :: Count e -> [Count e]
$cenumFrom :: forall e. Count e -> [Count e]
fromEnum :: Count e -> Int
$cfromEnum :: forall e. Count e -> Int
toEnum :: Int -> Count e
$ctoEnum :: forall e. Int -> Count e
pred :: Count e -> Count e
$cpred :: forall e. Count e -> Count e
succ :: Count e -> Count e
$csucc :: forall e. Count e -> Count e
Enum, Count e
Count e -> Count e -> Bounded (Count e)
forall e. Count e
forall a. a -> a -> Bounded a
maxBound :: Count e
$cmaxBound :: forall e. Count e
minBound :: Count e
$cminBound :: forall e. Count e
Bounded, Integer -> Count e
Count e -> Count e
Count e -> Count e -> Count e
(Count e -> Count e -> Count e)
-> (Count e -> Count e -> Count e)
-> (Count e -> Count e -> Count e)
-> (Count e -> Count e)
-> (Count e -> Count e)
-> (Count e -> Count e)
-> (Integer -> Count e)
-> Num (Count e)
forall e. Integer -> Count e
forall e. Count e -> Count e
forall e. Count e -> Count e -> Count e
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Count e
$cfromInteger :: forall e. Integer -> Count e
signum :: Count e -> Count e
$csignum :: forall e. Count e -> Count e
abs :: Count e -> Count e
$cabs :: forall e. Count e -> Count e
negate :: Count e -> Count e
$cnegate :: forall e. Count e -> Count e
* :: Count e -> Count e -> Count e
$c* :: forall e. Count e -> Count e -> Count e
- :: Count e -> Count e -> Count e
$c- :: forall e. Count e -> Count e -> Count e
+ :: Count e -> Count e -> Count e
$c+ :: forall e. Count e -> Count e -> Count e
Num, Enum (Count e)
Real (Count e)
Real (Count e)
-> Enum (Count e)
-> (Count e -> Count e -> Count e)
-> (Count e -> Count e -> Count e)
-> (Count e -> Count e -> Count e)
-> (Count e -> Count e -> Count e)
-> (Count e -> Count e -> (Count e, Count e))
-> (Count e -> Count e -> (Count e, Count e))
-> (Count e -> Integer)
-> Integral (Count e)
Count e -> Integer
Count e -> Count e -> (Count e, Count e)
Count e -> Count e -> Count e
forall e. Enum (Count e)
forall e. Real (Count e)
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
forall e. Count e -> Integer
forall e. Count e -> Count e -> (Count e, Count e)
forall e. Count e -> Count e -> Count e
toInteger :: Count e -> Integer
$ctoInteger :: forall e. Count e -> Integer
divMod :: Count e -> Count e -> (Count e, Count e)
$cdivMod :: forall e. Count e -> Count e -> (Count e, Count e)
quotRem :: Count e -> Count e -> (Count e, Count e)
$cquotRem :: forall e. Count e -> Count e -> (Count e, Count e)
mod :: Count e -> Count e -> Count e
$cmod :: forall e. Count e -> Count e -> Count e
div :: Count e -> Count e -> Count e
$cdiv :: forall e. Count e -> Count e -> Count e
rem :: Count e -> Count e -> Count e
$crem :: forall e. Count e -> Count e -> Count e
quot :: Count e -> Count e -> Count e
$cquot :: forall e. Count e -> Count e -> Count e
$cp2Integral :: forall e. Enum (Count e)
$cp1Integral :: forall e. Real (Count e)
Integral, Num (Count e)
Ord (Count e)
Num (Count e)
-> Ord (Count e) -> (Count e -> Rational) -> Real (Count e)
Count e -> Rational
forall e. Num (Count e)
forall e. Ord (Count e)
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
forall e. Count e -> Rational
toRational :: Count e -> Rational
$ctoRational :: forall e. Count e -> Rational
$cp2Real :: forall e. Ord (Count e)
$cp1Real :: forall e. Num (Count e)
Real, Count e -> ()
(Count e -> ()) -> NFData (Count e)
forall e. Count e -> ()
forall a. (a -> ()) -> NFData a
rnf :: Count e -> ()
$crnf :: forall e. Count e -> ()
NFData)
instance Prim (Count e) where
  type PrimBase (Count e) = Int
unCountWord8# :: Count Word8 -> Int#
unCountWord8# :: Count Word8 -> Int#
unCountWord8# (Count (I# Int#
n#)) = Int#
n#
{-# INLINE unCountWord8# #-}
unCountInt8# :: Count Int8 -> Int#
unCountInt8# :: Count Int8 -> Int#
unCountInt8# (Count (I# Int#
n#)) = Int#
n#
{-# INLINE unCountInt8# #-}
unCountBytes# :: Prim e => Count e -> Int#
unCountBytes# :: Count e -> Int#
unCountBytes# c :: Count e
c@(Count (I# Int#
n#)) =
  case Count Word8 -> Int
coerce (Count e -> Count Word8
forall (proxy :: * -> *) e. Prim e => proxy e -> Count Word8
byteCountProxy Count e
c) of
    I# Int#
sz# -> Int#
sz# Int# -> Int# -> Int#
*# Int#
n#
{-# INLINE[0] unCountBytes# #-}
{-# RULES
"unCountWord8#" unCountBytes# = unCountWord8#
"unCountInt8#" unCountBytes# = unCountInt8#
  #-}
unCountBytes :: Prim e => Count e -> Int
unCountBytes :: Count e -> Int
unCountBytes Count e
c = Int# -> Int
I# (Count e -> Int#
forall e. Prim e => Count e -> Int#
unCountBytes# Count e
c)
{-# INLINE unCountBytes #-}
toByteCount :: Prim e => Count e -> Count Word8
toByteCount :: Count e -> Count Word8
toByteCount = Int -> Count Word8
forall e. Int -> Count e
Count (Int -> Count Word8) -> (Count e -> Int) -> Count e -> Count Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Count e -> Int
forall e. Prim e => Count e -> Int
unCountBytes
{-# INLINE toByteCount #-}
countToOff :: Count e -> Off e
countToOff :: Count e -> Off e
countToOff = Count e -> Off e
coerce
countToByteOff :: Prim e => Count e -> Off Word8
countToByteOff :: Count e -> Off Word8
countToByteOff = Count Word8 -> Off Word8
forall e. Count e -> Off e
countToOff (Count Word8 -> Off Word8)
-> (Count e -> Count Word8) -> Count e -> Off Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Count e -> Count Word8
forall e. Prim e => Count e -> Count Word8
toByteCount
{-# INLINE countToByteOff #-}
countForProxyTypeOf :: Count e -> proxy e -> Count e
countForProxyTypeOf :: Count e -> proxy e -> Count e
countForProxyTypeOf Count e
count proxy e
_ = Count e
count
countForType :: Count e -> e -> Count e
countForType :: Count e -> e -> Count e
countForType Count e
count e
_ = Count e
count
fromByteCountInt8 :: Count Word8 -> Count Int8
fromByteCountInt8 :: Count Word8 -> Count Int8
fromByteCountInt8 = Count Word8 -> Count Int8
coerce
{-# INLINE fromByteCountInt8 #-}
fromByteCount :: forall e . Prim e => Count Word8 -> Count e
fromByteCount :: Count Word8 -> Count e
fromByteCount Count Word8
sz = Int -> Count e
coerce (Proxy# e -> Int -> Int -> (Int -> Int -> Int) -> Int
forall e b.
Prim e =>
Proxy# e -> Int -> b -> (Int -> Int -> b) -> b
quotSizeOfWith (Proxy# e
forall k (a :: k). Proxy# a
proxy# :: Proxy# e) (Count Word8 -> Int
coerce Count Word8
sz) Int
0 Int -> Int -> Int
quotInt)
{-# INLINE[0] fromByteCount #-}
{-# RULES
"fromByteCount" fromByteCount = id
"fromByteCount" fromByteCount = fromByteCountInt8
  #-}
fromByteCountRemWord8 :: Count Word8 -> (Count Word8, Count Word8)
fromByteCountRemWord8 :: Count Word8 -> (Count Word8, Count Word8)
fromByteCountRemWord8 Count Word8
i = (Count Word8 -> Count Word8
coerce Count Word8
i, Count Word8
0)
{-# INLINE fromByteCountRemWord8 #-}
fromByteCountRemInt8 :: Count Word8 -> (Count Int8, Count Word8)
fromByteCountRemInt8 :: Count Word8 -> (Count Int8, Count Word8)
fromByteCountRemInt8 Count Word8
i = (Count Word8 -> Count Int8
coerce Count Word8
i, Count Word8
0)
{-# INLINE fromByteCountRemInt8 #-}
fromByteCountRem :: forall e . Prim e => Count Word8 -> (Count e, Count Word8)
fromByteCountRem :: Count Word8 -> (Count e, Count Word8)
fromByteCountRem Count Word8
sz = (Int, Int) -> (Count e, Count Word8)
coerce (Proxy# e
-> Int -> (Int, Int) -> (Int -> Int -> (Int, Int)) -> (Int, Int)
forall e b.
Prim e =>
Proxy# e -> Int -> b -> (Int -> Int -> b) -> b
quotSizeOfWith (Proxy# e
forall k (a :: k). Proxy# a
proxy# :: Proxy# e) (Count Word8 -> Int
coerce Count Word8
sz) (Int
0, Int
0) Int -> Int -> (Int, Int)
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 :: Proxy# e -> Int -> b -> (Int -> Int -> b) -> b
quotSizeOfWith Proxy# e
px# Int
sz b
onZero Int -> Int -> b
quotWith
  | Int
tySize Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = b
onZero
  | Bool
otherwise = Int
sz Int -> Int -> b
`quotWith` Int
tySize
  where
    tySize :: Int
tySize = Int# -> Int
I# (Proxy# e -> Int#
forall a. Prim a => Proxy# a -> Int#
sizeOf# Proxy# e
px#)
{-# INLINE quotSizeOfWith #-}
newtype Off e = Off
  { Off e -> Int
unOff :: Int
  } deriving (Off e -> Off e -> Bool
(Off e -> Off e -> Bool) -> (Off e -> Off e -> Bool) -> Eq (Off e)
forall e. Off e -> Off e -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Off e -> Off e -> Bool
$c/= :: forall e. Off e -> Off e -> Bool
== :: Off e -> Off e -> Bool
$c== :: forall e. Off e -> Off e -> Bool
Eq, Int -> Off e -> ShowS
[Off e] -> ShowS
Off e -> String
(Int -> Off e -> ShowS)
-> (Off e -> String) -> ([Off e] -> ShowS) -> Show (Off e)
forall e. Int -> Off e -> ShowS
forall e. [Off e] -> ShowS
forall e. Off e -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Off e] -> ShowS
$cshowList :: forall e. [Off e] -> ShowS
show :: Off e -> String
$cshow :: forall e. Off e -> String
showsPrec :: Int -> Off e -> ShowS
$cshowsPrec :: forall e. Int -> Off e -> ShowS
Show, Eq (Off e)
Eq (Off e)
-> (Off e -> Off e -> Ordering)
-> (Off e -> Off e -> Bool)
-> (Off e -> Off e -> Bool)
-> (Off e -> Off e -> Bool)
-> (Off e -> Off e -> Bool)
-> (Off e -> Off e -> Off e)
-> (Off e -> Off e -> Off e)
-> Ord (Off e)
Off e -> Off e -> Bool
Off e -> Off e -> Ordering
Off e -> Off e -> Off e
forall e. Eq (Off e)
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall e. Off e -> Off e -> Bool
forall e. Off e -> Off e -> Ordering
forall e. Off e -> Off e -> Off e
min :: Off e -> Off e -> Off e
$cmin :: forall e. Off e -> Off e -> Off e
max :: Off e -> Off e -> Off e
$cmax :: forall e. Off e -> Off e -> Off e
>= :: Off e -> Off e -> Bool
$c>= :: forall e. Off e -> Off e -> Bool
> :: Off e -> Off e -> Bool
$c> :: forall e. Off e -> Off e -> Bool
<= :: Off e -> Off e -> Bool
$c<= :: forall e. Off e -> Off e -> Bool
< :: Off e -> Off e -> Bool
$c< :: forall e. Off e -> Off e -> Bool
compare :: Off e -> Off e -> Ordering
$ccompare :: forall e. Off e -> Off e -> Ordering
$cp1Ord :: forall e. Eq (Off e)
Ord, Int -> Off e
Off e -> Int
Off e -> [Off e]
Off e -> Off e
Off e -> Off e -> [Off e]
Off e -> Off e -> Off e -> [Off e]
(Off e -> Off e)
-> (Off e -> Off e)
-> (Int -> Off e)
-> (Off e -> Int)
-> (Off e -> [Off e])
-> (Off e -> Off e -> [Off e])
-> (Off e -> Off e -> [Off e])
-> (Off e -> Off e -> Off e -> [Off e])
-> Enum (Off e)
forall e. Int -> Off e
forall e. Off e -> Int
forall e. Off e -> [Off e]
forall e. Off e -> Off e
forall e. Off e -> Off e -> [Off e]
forall e. Off e -> Off e -> Off e -> [Off e]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Off e -> Off e -> Off e -> [Off e]
$cenumFromThenTo :: forall e. Off e -> Off e -> Off e -> [Off e]
enumFromTo :: Off e -> Off e -> [Off e]
$cenumFromTo :: forall e. Off e -> Off e -> [Off e]
enumFromThen :: Off e -> Off e -> [Off e]
$cenumFromThen :: forall e. Off e -> Off e -> [Off e]
enumFrom :: Off e -> [Off e]
$cenumFrom :: forall e. Off e -> [Off e]
fromEnum :: Off e -> Int
$cfromEnum :: forall e. Off e -> Int
toEnum :: Int -> Off e
$ctoEnum :: forall e. Int -> Off e
pred :: Off e -> Off e
$cpred :: forall e. Off e -> Off e
succ :: Off e -> Off e
$csucc :: forall e. Off e -> Off e
Enum, Off e
Off e -> Off e -> Bounded (Off e)
forall e. Off e
forall a. a -> a -> Bounded a
maxBound :: Off e
$cmaxBound :: forall e. Off e
minBound :: Off e
$cminBound :: forall e. Off e
Bounded, Integer -> Off e
Off e -> Off e
Off e -> Off e -> Off e
(Off e -> Off e -> Off e)
-> (Off e -> Off e -> Off e)
-> (Off e -> Off e -> Off e)
-> (Off e -> Off e)
-> (Off e -> Off e)
-> (Off e -> Off e)
-> (Integer -> Off e)
-> Num (Off e)
forall e. Integer -> Off e
forall e. Off e -> Off e
forall e. Off e -> Off e -> Off e
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Off e
$cfromInteger :: forall e. Integer -> Off e
signum :: Off e -> Off e
$csignum :: forall e. Off e -> Off e
abs :: Off e -> Off e
$cabs :: forall e. Off e -> Off e
negate :: Off e -> Off e
$cnegate :: forall e. Off e -> Off e
* :: Off e -> Off e -> Off e
$c* :: forall e. Off e -> Off e -> Off e
- :: Off e -> Off e -> Off e
$c- :: forall e. Off e -> Off e -> Off e
+ :: Off e -> Off e -> Off e
$c+ :: forall e. Off e -> Off e -> Off e
Num, Enum (Off e)
Real (Off e)
Real (Off e)
-> Enum (Off e)
-> (Off e -> Off e -> Off e)
-> (Off e -> Off e -> Off e)
-> (Off e -> Off e -> Off e)
-> (Off e -> Off e -> Off e)
-> (Off e -> Off e -> (Off e, Off e))
-> (Off e -> Off e -> (Off e, Off e))
-> (Off e -> Integer)
-> Integral (Off e)
Off e -> Integer
Off e -> Off e -> (Off e, Off e)
Off e -> Off e -> Off e
forall e. Enum (Off e)
forall e. Real (Off e)
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
forall e. Off e -> Integer
forall e. Off e -> Off e -> (Off e, Off e)
forall e. Off e -> Off e -> Off e
toInteger :: Off e -> Integer
$ctoInteger :: forall e. Off e -> Integer
divMod :: Off e -> Off e -> (Off e, Off e)
$cdivMod :: forall e. Off e -> Off e -> (Off e, Off e)
quotRem :: Off e -> Off e -> (Off e, Off e)
$cquotRem :: forall e. Off e -> Off e -> (Off e, Off e)
mod :: Off e -> Off e -> Off e
$cmod :: forall e. Off e -> Off e -> Off e
div :: Off e -> Off e -> Off e
$cdiv :: forall e. Off e -> Off e -> Off e
rem :: Off e -> Off e -> Off e
$crem :: forall e. Off e -> Off e -> Off e
quot :: Off e -> Off e -> Off e
$cquot :: forall e. Off e -> Off e -> Off e
$cp2Integral :: forall e. Enum (Off e)
$cp1Integral :: forall e. Real (Off e)
Integral, Num (Off e)
Ord (Off e)
Num (Off e) -> Ord (Off e) -> (Off e -> Rational) -> Real (Off e)
Off e -> Rational
forall e. Num (Off e)
forall e. Ord (Off e)
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
forall e. Off e -> Rational
toRational :: Off e -> Rational
$ctoRational :: forall e. Off e -> Rational
$cp2Real :: forall e. Ord (Off e)
$cp1Real :: forall e. Num (Off e)
Real, Off e -> ()
(Off e -> ()) -> NFData (Off e)
forall e. Off e -> ()
forall a. (a -> ()) -> NFData a
rnf :: Off e -> ()
$crnf :: forall e. Off e -> ()
NFData)
instance Prim (Off e) where
  type PrimBase (Off e) = Int
offForProxyTypeOf :: Off e -> proxy e -> Off e
offForProxyTypeOf :: Off e -> proxy e -> Off e
offForProxyTypeOf Off e
off proxy e
_ = Off e
off
offForType :: Off e -> e -> Off e
offForType :: Off e -> e -> Off e
offForType Off e
c e
_ = Off e
c
offToCount :: Off e -> Count e
offToCount :: Off e -> Count e
offToCount = Off e -> Count e
coerce
offToByteCount :: Prim e => Off e -> Count Word8
offToByteCount :: Off e -> Count Word8
offToByteCount = Off Word8 -> Count Word8
forall e. Off e -> Count e
offToCount (Off Word8 -> Count Word8)
-> (Off e -> Off Word8) -> Off e -> Count Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Off e -> Off Word8
forall e. Prim e => Off e -> Off Word8
toByteOff
{-# INLINE offToByteCount #-}
toByteOff :: Prim e => Off e -> Off Word8
toByteOff :: Off e -> Off Word8
toByteOff Off e
off = Int -> Off Word8
forall e. Int -> Off e
Off (Int# -> Int
I# (Off e -> Int#
forall e. Prim e => Off e -> Int#
unOffBytes# Off e
off))
{-# INLINE toByteOff #-}
unOffBytes :: Prim e => Off e -> Int
unOffBytes :: Off e -> Int
unOffBytes Off e
off = Int# -> Int
I# (Off e -> Int#
forall e. Prim e => Off e -> Int#
unOffBytes# Off e
off)
{-# INLINE unOffBytes #-}
unOffWord8# :: Off Word8 -> Int#
unOffWord8# :: Off Word8 -> Int#
unOffWord8# (Off (I# Int#
o#)) = Int#
o#
{-# INLINE unOffWord8# #-}
unOffInt8# :: Off Int8 -> Int#
unOffInt8# :: Off Int8 -> Int#
unOffInt8# (Off (I# Int#
o#)) = Int#
o#
{-# INLINE unOffInt8# #-}
unOffBytes# :: Prim e => Off e -> Int#
unOffBytes# :: Off e -> Int#
unOffBytes# o :: Off e
o@(Off (I# Int#
o#)) =
  case Count Word8 -> Int
coerce (Off e -> Count Word8
forall (proxy :: * -> *) e. Prim e => proxy e -> Count Word8
byteCountProxy Off e
o) of
    I# Int#
sz# -> Int#
sz# Int# -> Int# -> Int#
*# Int#
o#
{-# INLINE[0] unOffBytes# #-}
{-# RULES
"unOffWord8#" unOffBytes# = unOffWord8#
"unOffInt8#" unOffBytes# = unOffInt8#
  #-}
fromByteOffInt8 :: Off Word8 -> Off Int8
fromByteOffInt8 :: Off Word8 -> Off Int8
fromByteOffInt8 = Off Word8 -> Off Int8
coerce
{-# INLINE fromByteOffInt8 #-}
fromByteOff :: forall e . Prim e => Off Word8 -> Off e
fromByteOff :: Off Word8 -> Off e
fromByteOff Off Word8
sz = Int -> Off e
coerce (Proxy# e -> Int -> Int -> (Int -> Int -> Int) -> Int
forall e b.
Prim e =>
Proxy# e -> Int -> b -> (Int -> Int -> b) -> b
quotSizeOfWith (Proxy# e
forall k (a :: k). Proxy# a
proxy# :: Proxy# e) (Off Word8 -> Int
coerce Off Word8
sz) Int
0 Int -> Int -> Int
quotInt)
{-# INLINE[0] fromByteOff #-}
{-# RULES
"fromByteOff" fromByteOff = id
"fromByteOff" fromByteOff = fromByteOffInt8
  #-}
fromByteOffRemWord8 :: Off Word8 -> (Off Word8, Off Word8)
fromByteOffRemWord8 :: Off Word8 -> (Off Word8, Off Word8)
fromByteOffRemWord8 Off Word8
i = (Off Word8 -> Off Word8
coerce Off Word8
i, Off Word8
0)
{-# INLINE fromByteOffRemWord8 #-}
fromByteOffRemInt8 :: Off Word8 -> (Off Int8, Off Word8)
fromByteOffRemInt8 :: Off Word8 -> (Off Int8, Off Word8)
fromByteOffRemInt8 Off Word8
i = (Off Word8 -> Off Int8
coerce Off Word8
i, Off Word8
0)
{-# INLINE fromByteOffRemInt8 #-}
fromByteOffRem :: forall e . Prim e => Off Word8 -> (Off e, Off Word8)
fromByteOffRem :: Off Word8 -> (Off e, Off Word8)
fromByteOffRem Off Word8
sz = (Int, Int) -> (Off e, Off Word8)
coerce (Proxy# e
-> Int -> (Int, Int) -> (Int -> Int -> (Int, Int)) -> (Int, Int)
forall e b.
Prim e =>
Proxy# e -> Int -> b -> (Int -> Int -> b) -> b
quotSizeOfWith (Proxy# e
forall k (a :: k). Proxy# a
proxy# :: Proxy# e) (Off Word8 -> Int
coerce Off Word8
sz) (Int
0, Int
0) Int -> Int -> (Int, Int)
quotRemInt)
{-# INLINE[0] fromByteOffRem #-}
{-# RULES
"fromByteOffRemWord8" fromByteOffRem = fromByteOffRemWord8
"fromByteOffRemInt8"  fromByteOffRem = fromByteOffRemInt8
  #-}
prefetchValue0 :: MonadPrim s m => a -> m ()
prefetchValue0 :: a -> m ()
prefetchValue0 a
a = (State# s -> State# s) -> m ()
forall s (m :: * -> *).
MonadPrim s m =>
(State# s -> State# s) -> m ()
prim_ (a -> State# s -> State# s
forall a d. a -> State# d -> State# d
prefetchValue0# a
a)
{-# INLINE prefetchValue0 #-}
prefetchValue1 :: MonadPrim s m => a -> m ()
prefetchValue1 :: a -> m ()
prefetchValue1 a
a = (State# s -> State# s) -> m ()
forall s (m :: * -> *).
MonadPrim s m =>
(State# s -> State# s) -> m ()
prim_ (a -> State# s -> State# s
forall a d. a -> State# d -> State# d
prefetchValue1# a
a)
{-# INLINE prefetchValue1 #-}
prefetchValue2 :: MonadPrim s m => a -> m ()
prefetchValue2 :: a -> m ()
prefetchValue2 a
a = (State# s -> State# s) -> m ()
forall s (m :: * -> *).
MonadPrim s m =>
(State# s -> State# s) -> m ()
prim_ (a -> State# s -> State# s
forall a d. a -> State# d -> State# d
prefetchValue2# a
a)
{-# INLINE prefetchValue2 #-}
prefetchValue3 :: MonadPrim s m => a -> m ()
prefetchValue3 :: a -> m ()
prefetchValue3 a
a = (State# s -> State# s) -> m ()
forall s (m :: * -> *).
MonadPrim s m =>
(State# s -> State# s) -> m ()
prim_ (a -> State# s -> State# s
forall a d. a -> State# d -> State# d
prefetchValue3# a
a)
{-# INLINE prefetchValue3 #-}
(#.) :: forall a b c proxy. Coercible b c => proxy b c -> (a -> b) -> (a -> c)
#. :: proxy b c -> (a -> b) -> a -> c
(#.) proxy b c
_px = (a -> b) -> a -> c
coerce
{-# INLINE (#.) #-}
(.#) :: forall a b c proxy. Coercible b c => (a -> b) -> proxy b c -> (a -> c)
.# :: (a -> b) -> proxy b c -> a -> c
(.#) a -> b
f proxy b c
_px = (a -> b) -> a -> c
coerce a -> b
f
{-# INLINE (.#) #-}