grisette-0.5.0.0: Symbolic evaluation as a library
Copyright(c) Sirui Lu 2021-2024
LicenseBSD-3-Clause (see the LICENSE file)
Maintainersiruilu@cs.washington.edu
StabilityExperimental
PortabilityGHC only
Safe HaskellTrustworthy
LanguageHaskell2010

Grisette.Internal.Core.Data.Class.SafeDivision

Description

 
Synopsis

Documentation

data ArithException #

Arithmetic exceptions.

Instances

Instances details
Exception ArithException

Since: base-4.0.0.0

Instance details

Defined in GHC.Exception.Type

Show ArithException

Since: base-4.0.0.0

Instance details

Defined in GHC.Exception.Type

Eq ArithException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Ord ArithException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Mergeable ArithException Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.Mergeable

TransformError ArithException AssertionError Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.Error

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Int16 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Int32 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Int64 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Int8 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Word16 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Word32 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Word64 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Word8 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadUnion m, MonadError ArithException m) => SafeDivision ArithException SymInteger m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Integer m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Int m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

Methods

safeDiv :: Int -> Int -> m Int Source #

safeMod :: Int -> Int -> m Int Source #

safeDivMod :: Int -> Int -> m (Int, Int) Source #

safeQuot :: Int -> Int -> m Int Source #

safeRem :: Int -> Int -> m Int Source #

safeQuotRem :: Int -> Int -> m (Int, Int) Source #

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Word m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeLinearArith ArithException Int16 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeLinearArith

(MonadError ArithException m, TryMerge m) => SafeLinearArith ArithException Int32 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeLinearArith

(MonadError ArithException m, TryMerge m) => SafeLinearArith ArithException Int64 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeLinearArith

(MonadError ArithException m, TryMerge m) => SafeLinearArith ArithException Int8 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeLinearArith

Methods

safeAdd :: Int8 -> Int8 -> m Int8 Source #

safeNeg :: Int8 -> m Int8 Source #

safeSub :: Int8 -> Int8 -> m Int8 Source #

(MonadError ArithException m, TryMerge m) => SafeLinearArith ArithException Word16 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeLinearArith

(MonadError ArithException m, TryMerge m) => SafeLinearArith ArithException Word32 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeLinearArith

(MonadError ArithException m, TryMerge m) => SafeLinearArith ArithException Word64 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeLinearArith

(MonadError ArithException m, TryMerge m) => SafeLinearArith ArithException Word8 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeLinearArith

(MonadError ArithException m, TryMerge m) => SafeLinearArith ArithException SymInteger m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeLinearArith

(MonadError ArithException m, TryMerge m) => SafeLinearArith ArithException Integer m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeLinearArith

(MonadError ArithException m, TryMerge m) => SafeLinearArith ArithException Int m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeLinearArith

Methods

safeAdd :: Int -> Int -> m Int Source #

safeNeg :: Int -> m Int Source #

safeSub :: Int -> Int -> m Int Source #

(MonadError ArithException m, TryMerge m) => SafeLinearArith ArithException Word m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeLinearArith

Methods

safeAdd :: Word -> Word -> m Word Source #

safeNeg :: Word -> m Word Source #

safeSub :: Word -> Word -> m Word Source #

(MonadError ArithException m, TryMerge m) => SafeSymRotate ArithException Int16 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymRotate

(MonadError ArithException m, TryMerge m) => SafeSymRotate ArithException Int32 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymRotate

(MonadError ArithException m, TryMerge m) => SafeSymRotate ArithException Int64 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymRotate

(MonadError ArithException m, TryMerge m) => SafeSymRotate ArithException Int8 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymRotate

(MonadError ArithException m, TryMerge m) => SafeSymRotate ArithException Word16 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymRotate

(MonadError ArithException m, TryMerge m) => SafeSymRotate ArithException Word32 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymRotate

(MonadError ArithException m, TryMerge m) => SafeSymRotate ArithException Word64 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymRotate

(MonadError ArithException m, TryMerge m) => SafeSymRotate ArithException Word8 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymRotate

(MonadError ArithException m, TryMerge m) => SafeSymRotate ArithException Int m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymRotate

(MonadError ArithException m, TryMerge m) => SafeSymRotate ArithException Word m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymRotate

(MonadError ArithException m, TryMerge m) => SafeSymShift ArithException Int16 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymShift

(MonadError ArithException m, TryMerge m) => SafeSymShift ArithException Int32 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymShift

(MonadError ArithException m, TryMerge m) => SafeSymShift ArithException Int64 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymShift

(MonadError ArithException m, TryMerge m) => SafeSymShift ArithException Int8 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymShift

(MonadError ArithException m, TryMerge m) => SafeSymShift ArithException Word16 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymShift

(MonadError ArithException m, TryMerge m) => SafeSymShift ArithException Word32 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymShift

(MonadError ArithException m, TryMerge m) => SafeSymShift ArithException Word64 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymShift

(MonadError ArithException m, TryMerge m) => SafeSymShift ArithException Word8 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymShift

(MonadError ArithException m, TryMerge m) => SafeSymShift ArithException Int m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymShift

(MonadError ArithException m, TryMerge m) => SafeSymShift ArithException Word m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymShift

(MonadError ArithException m, TryMerge m, KnownNat n, 1 <= n) => SafeDivision ArithException (IntN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

Methods

safeDiv :: IntN n -> IntN n -> m (IntN n) Source #

safeMod :: IntN n -> IntN n -> m (IntN n) Source #

safeDivMod :: IntN n -> IntN n -> m (IntN n, IntN n) Source #

safeQuot :: IntN n -> IntN n -> m (IntN n) Source #

safeRem :: IntN n -> IntN n -> m (IntN n) Source #

safeQuotRem :: IntN n -> IntN n -> m (IntN n, IntN n) Source #

(MonadError ArithException m, TryMerge m, KnownNat n, 1 <= n) => SafeDivision ArithException (WordN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

Methods

safeDiv :: WordN n -> WordN n -> m (WordN n) Source #

safeMod :: WordN n -> WordN n -> m (WordN n) Source #

safeDivMod :: WordN n -> WordN n -> m (WordN n, WordN n) Source #

safeQuot :: WordN n -> WordN n -> m (WordN n) Source #

safeRem :: WordN n -> WordN n -> m (WordN n) Source #

safeQuotRem :: WordN n -> WordN n -> m (WordN n, WordN n) Source #

(MonadError ArithException m, MonadUnion m, KnownNat n, 1 <= n) => SafeDivision ArithException (SymIntN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

Methods

safeDiv :: SymIntN n -> SymIntN n -> m (SymIntN n) Source #

safeMod :: SymIntN n -> SymIntN n -> m (SymIntN n) Source #

safeDivMod :: SymIntN n -> SymIntN n -> m (SymIntN n, SymIntN n) Source #

safeQuot :: SymIntN n -> SymIntN n -> m (SymIntN n) Source #

safeRem :: SymIntN n -> SymIntN n -> m (SymIntN n) Source #

safeQuotRem :: SymIntN n -> SymIntN n -> m (SymIntN n, SymIntN n) Source #

(MonadError ArithException m, MonadUnion m, KnownNat n, 1 <= n) => SafeDivision ArithException (SymWordN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m, KnownNat n, 1 <= n) => SafeLinearArith ArithException (IntN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeLinearArith

Methods

safeAdd :: IntN n -> IntN n -> m (IntN n) Source #

safeNeg :: IntN n -> m (IntN n) Source #

safeSub :: IntN n -> IntN n -> m (IntN n) Source #

(MonadError ArithException m, TryMerge m, KnownNat n, 1 <= n) => SafeLinearArith ArithException (WordN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeLinearArith

Methods

safeAdd :: WordN n -> WordN n -> m (WordN n) Source #

safeNeg :: WordN n -> m (WordN n) Source #

safeSub :: WordN n -> WordN n -> m (WordN n) Source #

(MonadError ArithException m, MonadUnion m, KnownNat n, 1 <= n) => SafeLinearArith ArithException (SymIntN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeLinearArith

Methods

safeAdd :: SymIntN n -> SymIntN n -> m (SymIntN n) Source #

safeNeg :: SymIntN n -> m (SymIntN n) Source #

safeSub :: SymIntN n -> SymIntN n -> m (SymIntN n) Source #

(MonadError ArithException m, MonadUnion m, KnownNat n, 1 <= n) => SafeLinearArith ArithException (SymWordN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeLinearArith

Methods

safeAdd :: SymWordN n -> SymWordN n -> m (SymWordN n) Source #

safeNeg :: SymWordN n -> m (SymWordN n) Source #

safeSub :: SymWordN n -> SymWordN n -> m (SymWordN n) Source #

(MonadError ArithException m, TryMerge m, KnownNat n, 1 <= n) => SafeSymRotate ArithException (IntN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymRotate

Methods

safeSymRotateL :: IntN n -> IntN n -> m (IntN n) Source #

safeSymRotateR :: IntN n -> IntN n -> m (IntN n) Source #

(MonadError ArithException m, TryMerge m, KnownNat n, 1 <= n) => SafeSymRotate ArithException (WordN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymRotate

Methods

safeSymRotateL :: WordN n -> WordN n -> m (WordN n) Source #

safeSymRotateR :: WordN n -> WordN n -> m (WordN n) Source #

(MonadError ArithException m, MonadUnion m, KnownNat n, 1 <= n) => SafeSymRotate ArithException (SymIntN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymRotate

(MonadError ArithException m, TryMerge m, KnownNat n, 1 <= n) => SafeSymRotate ArithException (SymWordN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymRotate

(MonadError ArithException m, TryMerge m, KnownNat n, 1 <= n) => SafeSymShift ArithException (IntN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymShift

Methods

safeSymShiftL :: IntN n -> IntN n -> m (IntN n) Source #

safeSymShiftR :: IntN n -> IntN n -> m (IntN n) Source #

safeSymStrictShiftL :: IntN n -> IntN n -> m (IntN n) Source #

safeSymStrictShiftR :: IntN n -> IntN n -> m (IntN n) Source #

(MonadError ArithException m, TryMerge m, KnownNat n, 1 <= n) => SafeSymShift ArithException (WordN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymShift

Methods

safeSymShiftL :: WordN n -> WordN n -> m (WordN n) Source #

safeSymShiftR :: WordN n -> WordN n -> m (WordN n) Source #

safeSymStrictShiftL :: WordN n -> WordN n -> m (WordN n) Source #

safeSymStrictShiftR :: WordN n -> WordN n -> m (WordN n) Source #

(MonadError ArithException m, MonadUnion m, KnownNat n, 1 <= n) => SafeSymShift ArithException (SymIntN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymShift

(MonadError ArithException m, MonadUnion m, KnownNat n, 1 <= n) => SafeSymShift ArithException (SymWordN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeSymShift

class (MonadError e m, TryMerge m, Mergeable a) => SafeDivision e a m where Source #

Safe division with monadic error handling in multi-path execution. These procedures throw an exception when the divisor is zero. The result should be able to handle errors with MonadError.

Minimal complete definition

(safeDiv, safeMod | safeDivMod), (safeQuot, safeRem | safeQuotRem)

Methods

safeDiv :: a -> a -> m a Source #

Safe signed div with monadic error handling in multi-path execution.

>>> safeDiv (ssym "a") (ssym "b") :: ExceptT ArithException UnionM SymInteger
ExceptT {If (= b 0) (Left divide by zero) (Right (div a b))}

safeMod :: a -> a -> m a Source #

Safe signed mod with monadic error handling in multi-path execution.

>>> safeMod (ssym "a") (ssym "b") :: ExceptT ArithException UnionM SymInteger
ExceptT {If (= b 0) (Left divide by zero) (Right (mod a b))}

safeDivMod :: a -> a -> m (a, a) Source #

Safe signed divMod with monadic error handling in multi-path execution.

>>> safeDivMod (ssym "a") (ssym "b") :: ExceptT ArithException UnionM (SymInteger, SymInteger)
ExceptT {If (= b 0) (Left divide by zero) (Right ((div a b),(mod a b)))}

safeQuot :: a -> a -> m a Source #

Safe signed quot with monadic error handling in multi-path execution.

safeRem :: a -> a -> m a Source #

Safe signed rem with monadic error handling in multi-path execution.

safeQuotRem :: a -> a -> m (a, a) Source #

Safe signed quotRem with monadic error handling in multi-path execution.

Instances

Instances details
(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Int16 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Int32 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Int64 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Int8 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Word16 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Word32 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Word64 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Word8 m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadUnion m, MonadError ArithException m) => SafeDivision ArithException SymInteger m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Integer m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Int m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

Methods

safeDiv :: Int -> Int -> m Int Source #

safeMod :: Int -> Int -> m Int Source #

safeDivMod :: Int -> Int -> m (Int, Int) Source #

safeQuot :: Int -> Int -> m Int Source #

safeRem :: Int -> Int -> m Int Source #

safeQuotRem :: Int -> Int -> m (Int, Int) Source #

(MonadError ArithException m, TryMerge m) => SafeDivision ArithException Word m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(MonadError ArithException m, TryMerge m, KnownNat n, 1 <= n) => SafeDivision ArithException (IntN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

Methods

safeDiv :: IntN n -> IntN n -> m (IntN n) Source #

safeMod :: IntN n -> IntN n -> m (IntN n) Source #

safeDivMod :: IntN n -> IntN n -> m (IntN n, IntN n) Source #

safeQuot :: IntN n -> IntN n -> m (IntN n) Source #

safeRem :: IntN n -> IntN n -> m (IntN n) Source #

safeQuotRem :: IntN n -> IntN n -> m (IntN n, IntN n) Source #

(MonadError ArithException m, TryMerge m, KnownNat n, 1 <= n) => SafeDivision ArithException (WordN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

Methods

safeDiv :: WordN n -> WordN n -> m (WordN n) Source #

safeMod :: WordN n -> WordN n -> m (WordN n) Source #

safeDivMod :: WordN n -> WordN n -> m (WordN n, WordN n) Source #

safeQuot :: WordN n -> WordN n -> m (WordN n) Source #

safeRem :: WordN n -> WordN n -> m (WordN n) Source #

safeQuotRem :: WordN n -> WordN n -> m (WordN n, WordN n) Source #

(MonadError ArithException m, MonadUnion m, KnownNat n, 1 <= n) => SafeDivision ArithException (SymIntN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

Methods

safeDiv :: SymIntN n -> SymIntN n -> m (SymIntN n) Source #

safeMod :: SymIntN n -> SymIntN n -> m (SymIntN n) Source #

safeDivMod :: SymIntN n -> SymIntN n -> m (SymIntN n, SymIntN n) Source #

safeQuot :: SymIntN n -> SymIntN n -> m (SymIntN n) Source #

safeRem :: SymIntN n -> SymIntN n -> m (SymIntN n) Source #

safeQuotRem :: SymIntN n -> SymIntN n -> m (SymIntN n, SymIntN n) Source #

(MonadError ArithException m, MonadUnion m, KnownNat n, 1 <= n) => SafeDivision ArithException (SymWordN n) m Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Class.SafeDivision

(forall (n :: Nat). (KnownNat n, 1 <= n) => SafeDivision e (bv n) (ExceptT e m), MonadError (Either BitwidthMismatch e) m, TryMerge m, Mergeable e) => SafeDivision (Either BitwidthMismatch e) (SomeBV bv) m Source # 
Instance details

Defined in Grisette.Internal.SymPrim.SomeBV

Methods

safeDiv :: SomeBV bv -> SomeBV bv -> m (SomeBV bv) Source #

safeMod :: SomeBV bv -> SomeBV bv -> m (SomeBV bv) Source #

safeDivMod :: SomeBV bv -> SomeBV bv -> m (SomeBV bv, SomeBV bv) Source #

safeQuot :: SomeBV bv -> SomeBV bv -> m (SomeBV bv) Source #

safeRem :: SomeBV bv -> SomeBV bv -> m (SomeBV bv) Source #

safeQuotRem :: SomeBV bv -> SomeBV bv -> m (SomeBV bv, SomeBV bv) Source #