{-# LANGUAGE DeriveDataTypeable #-}
module Basement.Exception
    ( OutOfBound(..)
    , OutOfBoundOperation(..)
    , isOutOfBound
    , outOfBound
    , primOutOfBound
    , InvalidRecast(..)
    , RecastSourceSize(..)
    , RecastDestinationSize(..)
    , NonEmptyCollectionIsEmpty(..)
    ) where
import           Basement.Compat.Base
import           Basement.Types.OffsetSize
import           Basement.Monad
data OutOfBoundOperation = OOB_Read | OOB_Write | OOB_MemSet | OOB_MemCopy | OOB_Index
    deriving (Show,Eq,Typeable)
data OutOfBound = OutOfBound OutOfBoundOperation Int Int
    deriving (Show,Typeable)
instance Exception OutOfBound
outOfBound :: OutOfBoundOperation -> Offset ty -> CountOf ty -> a
outOfBound oobop (Offset ofs) (CountOf sz) = throw (OutOfBound oobop ofs sz)
{-# INLINE outOfBound #-}
primOutOfBound :: PrimMonad prim => OutOfBoundOperation -> Offset ty -> CountOf ty -> prim a
primOutOfBound oobop (Offset ofs) (CountOf sz) = primThrow (OutOfBound oobop ofs sz)
{-# INLINE primOutOfBound #-}
isOutOfBound :: Offset ty -> CountOf ty -> Bool
isOutOfBound (Offset ty) (CountOf sz) = ty < 0 || ty >= sz
{-# INLINE isOutOfBound #-}
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
data NonEmptyCollectionIsEmpty = NonEmptyCollectionIsEmpty
    deriving (Show,Typeable)
instance Exception NonEmptyCollectionIsEmpty