module Foundation.Array.Common
( OutOfBound(..)
, OutOfBoundOperation(..)
, isOutOfBound
, outOfBound
, primOutOfBound
, InvalidRecast(..)
, RecastSourceSize(..)
, RecastDestinationSize(..)
) where
import Foundation.Internal.Base
import Foundation.Primitive.Types.OffsetSize
import Foundation.Primitive.Monad
data OutOfBoundOperation = OOB_Read | OOB_Write | OOB_MemSet | OOB_Index
deriving (Show,Eq,Typeable)
data OutOfBound = OutOfBound OutOfBoundOperation Int Int
deriving (Show,Typeable)
instance Exception OutOfBound
outOfBound :: OutOfBoundOperation -> Offset ty -> Size ty -> a
outOfBound oobop (Offset ofs) (Size sz) = throw (OutOfBound oobop ofs sz)
primOutOfBound :: PrimMonad prim => OutOfBoundOperation -> Offset ty -> Size ty -> prim a
primOutOfBound oobop (Offset ofs) (Size sz) = primThrow (OutOfBound oobop ofs sz)
isOutOfBound :: Offset ty -> Size ty -> Bool
isOutOfBound (Offset ty) (Size sz) = ty < 0 || ty >= sz
newtype RecastSourceSize = RecastSourceSize Int
deriving (Show,Eq,Typeable)
newtype RecastDestinationSize = RecastDestinationSize Int
deriving (Show,Eq,Typeable)
data InvalidRecast = InvalidRecast RecastSourceSize RecastDestinationSize
deriving (Show,Typeable)
instance Exception InvalidRecast