-- |
-- Module      : Basement.Exception
-- License     : BSD-style
-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
-- Stability   : experimental
-- Portability : portable
--
-- Common part for vectors
--
{-# 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

-- | The type of operation that triggers an OutOfBound exception.
--
-- * OOB_Index: reading an immutable vector
-- * OOB_Read: reading a mutable vector
-- * OOB_Write: write a mutable vector
-- * OOB_MemCopy: copying a vector
-- * OOB_MemSet: initializing a mutable vector
data OutOfBoundOperation = OOB_Read | OOB_Write | OOB_MemSet | OOB_MemCopy | OOB_Index
    deriving (Int -> OutOfBoundOperation -> ShowS
[OutOfBoundOperation] -> ShowS
OutOfBoundOperation -> String
(Int -> OutOfBoundOperation -> ShowS)
-> (OutOfBoundOperation -> String)
-> ([OutOfBoundOperation] -> ShowS)
-> Show OutOfBoundOperation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OutOfBoundOperation] -> ShowS
$cshowList :: [OutOfBoundOperation] -> ShowS
show :: OutOfBoundOperation -> String
$cshow :: OutOfBoundOperation -> String
showsPrec :: Int -> OutOfBoundOperation -> ShowS
$cshowsPrec :: Int -> OutOfBoundOperation -> ShowS
Show,OutOfBoundOperation -> OutOfBoundOperation -> Bool
(OutOfBoundOperation -> OutOfBoundOperation -> Bool)
-> (OutOfBoundOperation -> OutOfBoundOperation -> Bool)
-> Eq OutOfBoundOperation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutOfBoundOperation -> OutOfBoundOperation -> Bool
$c/= :: OutOfBoundOperation -> OutOfBoundOperation -> Bool
== :: OutOfBoundOperation -> OutOfBoundOperation -> Bool
$c== :: OutOfBoundOperation -> OutOfBoundOperation -> Bool
Eq,Typeable)

-- | Exception during an operation accessing the vector out of bound
--
-- Represent the type of operation, the index accessed, and the total length of the vector.
data OutOfBound = OutOfBound OutOfBoundOperation Int Int
    deriving (Int -> OutOfBound -> ShowS
[OutOfBound] -> ShowS
OutOfBound -> String
(Int -> OutOfBound -> ShowS)
-> (OutOfBound -> String)
-> ([OutOfBound] -> ShowS)
-> Show OutOfBound
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OutOfBound] -> ShowS
$cshowList :: [OutOfBound] -> ShowS
show :: OutOfBound -> String
$cshow :: OutOfBound -> String
showsPrec :: Int -> OutOfBound -> ShowS
$cshowsPrec :: Int -> OutOfBound -> ShowS
Show,Typeable)

instance Exception OutOfBound

outOfBound :: OutOfBoundOperation -> Offset ty -> CountOf ty -> a
outOfBound :: OutOfBoundOperation -> Offset ty -> CountOf ty -> a
outOfBound OutOfBoundOperation
oobop (Offset Int
ofs) (CountOf Int
sz) = OutOfBound -> a
forall a e. Exception e => e -> a
throw (OutOfBoundOperation -> Int -> Int -> OutOfBound
OutOfBound OutOfBoundOperation
oobop Int
ofs Int
sz)
{-# INLINE outOfBound #-}

primOutOfBound :: PrimMonad prim => OutOfBoundOperation -> Offset ty -> CountOf ty -> prim a
primOutOfBound :: OutOfBoundOperation -> Offset ty -> CountOf ty -> prim a
primOutOfBound OutOfBoundOperation
oobop (Offset Int
ofs) (CountOf Int
sz) = OutOfBound -> prim a
forall (m :: * -> *) e a. (PrimMonad m, Exception e) => e -> m a
primThrow (OutOfBoundOperation -> Int -> Int -> OutOfBound
OutOfBound OutOfBoundOperation
oobop Int
ofs Int
sz)
{-# INLINE primOutOfBound #-}

isOutOfBound :: Offset ty -> CountOf ty -> Bool
isOutOfBound :: Offset ty -> CountOf ty -> Bool
isOutOfBound (Offset Int
ty) (CountOf Int
sz) = Int
ty Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| Int
ty Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
sz
{-# INLINE isOutOfBound #-}

newtype RecastSourceSize      = RecastSourceSize Int
    deriving (Int -> RecastSourceSize -> ShowS
[RecastSourceSize] -> ShowS
RecastSourceSize -> String
(Int -> RecastSourceSize -> ShowS)
-> (RecastSourceSize -> String)
-> ([RecastSourceSize] -> ShowS)
-> Show RecastSourceSize
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecastSourceSize] -> ShowS
$cshowList :: [RecastSourceSize] -> ShowS
show :: RecastSourceSize -> String
$cshow :: RecastSourceSize -> String
showsPrec :: Int -> RecastSourceSize -> ShowS
$cshowsPrec :: Int -> RecastSourceSize -> ShowS
Show,RecastSourceSize -> RecastSourceSize -> Bool
(RecastSourceSize -> RecastSourceSize -> Bool)
-> (RecastSourceSize -> RecastSourceSize -> Bool)
-> Eq RecastSourceSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecastSourceSize -> RecastSourceSize -> Bool
$c/= :: RecastSourceSize -> RecastSourceSize -> Bool
== :: RecastSourceSize -> RecastSourceSize -> Bool
$c== :: RecastSourceSize -> RecastSourceSize -> Bool
Eq,Typeable)
newtype RecastDestinationSize = RecastDestinationSize Int
    deriving (Int -> RecastDestinationSize -> ShowS
[RecastDestinationSize] -> ShowS
RecastDestinationSize -> String
(Int -> RecastDestinationSize -> ShowS)
-> (RecastDestinationSize -> String)
-> ([RecastDestinationSize] -> ShowS)
-> Show RecastDestinationSize
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecastDestinationSize] -> ShowS
$cshowList :: [RecastDestinationSize] -> ShowS
show :: RecastDestinationSize -> String
$cshow :: RecastDestinationSize -> String
showsPrec :: Int -> RecastDestinationSize -> ShowS
$cshowsPrec :: Int -> RecastDestinationSize -> ShowS
Show,RecastDestinationSize -> RecastDestinationSize -> Bool
(RecastDestinationSize -> RecastDestinationSize -> Bool)
-> (RecastDestinationSize -> RecastDestinationSize -> Bool)
-> Eq RecastDestinationSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecastDestinationSize -> RecastDestinationSize -> Bool
$c/= :: RecastDestinationSize -> RecastDestinationSize -> Bool
== :: RecastDestinationSize -> RecastDestinationSize -> Bool
$c== :: RecastDestinationSize -> RecastDestinationSize -> Bool
Eq,Typeable)

data InvalidRecast = InvalidRecast RecastSourceSize RecastDestinationSize
    deriving (Int -> InvalidRecast -> ShowS
[InvalidRecast] -> ShowS
InvalidRecast -> String
(Int -> InvalidRecast -> ShowS)
-> (InvalidRecast -> String)
-> ([InvalidRecast] -> ShowS)
-> Show InvalidRecast
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InvalidRecast] -> ShowS
$cshowList :: [InvalidRecast] -> ShowS
show :: InvalidRecast -> String
$cshow :: InvalidRecast -> String
showsPrec :: Int -> InvalidRecast -> ShowS
$cshowsPrec :: Int -> InvalidRecast -> ShowS
Show,Typeable)

instance Exception InvalidRecast

-- | Exception for using NonEmpty assertion with an empty collection
data NonEmptyCollectionIsEmpty = NonEmptyCollectionIsEmpty
    deriving (Int -> NonEmptyCollectionIsEmpty -> ShowS
[NonEmptyCollectionIsEmpty] -> ShowS
NonEmptyCollectionIsEmpty -> String
(Int -> NonEmptyCollectionIsEmpty -> ShowS)
-> (NonEmptyCollectionIsEmpty -> String)
-> ([NonEmptyCollectionIsEmpty] -> ShowS)
-> Show NonEmptyCollectionIsEmpty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NonEmptyCollectionIsEmpty] -> ShowS
$cshowList :: [NonEmptyCollectionIsEmpty] -> ShowS
show :: NonEmptyCollectionIsEmpty -> String
$cshow :: NonEmptyCollectionIsEmpty -> String
showsPrec :: Int -> NonEmptyCollectionIsEmpty -> ShowS
$cshowsPrec :: Int -> NonEmptyCollectionIsEmpty -> ShowS
Show,Typeable)

instance Exception NonEmptyCollectionIsEmpty