{-|
This module lists all of the exceptions thrown by 'llvm-hs' itself.
Note that other exceptions can potentially be thrown
by the underlying libraries, e.g., for functions doing file IO.
-}
module LLVM.Exception where

import LLVM.Prelude

import Control.Monad.Catch

-- | Indicates an error during the translation of the AST provided by
-- 'llvm-hs-pure' to LLVM’s internal representation.
data EncodeException =
  EncodeException !String
  deriving (Int -> EncodeException -> ShowS
[EncodeException] -> ShowS
EncodeException -> String
(Int -> EncodeException -> ShowS)
-> (EncodeException -> String)
-> ([EncodeException] -> ShowS)
-> Show EncodeException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EncodeException] -> ShowS
$cshowList :: [EncodeException] -> ShowS
show :: EncodeException -> String
$cshow :: EncodeException -> String
showsPrec :: Int -> EncodeException -> ShowS
$cshowsPrec :: Int -> EncodeException -> ShowS
Show, EncodeException -> EncodeException -> Bool
(EncodeException -> EncodeException -> Bool)
-> (EncodeException -> EncodeException -> Bool)
-> Eq EncodeException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EncodeException -> EncodeException -> Bool
$c/= :: EncodeException -> EncodeException -> Bool
== :: EncodeException -> EncodeException -> Bool
$c== :: EncodeException -> EncodeException -> Bool
Eq, Eq EncodeException
Eq EncodeException =>
(EncodeException -> EncodeException -> Ordering)
-> (EncodeException -> EncodeException -> Bool)
-> (EncodeException -> EncodeException -> Bool)
-> (EncodeException -> EncodeException -> Bool)
-> (EncodeException -> EncodeException -> Bool)
-> (EncodeException -> EncodeException -> EncodeException)
-> (EncodeException -> EncodeException -> EncodeException)
-> Ord EncodeException
EncodeException -> EncodeException -> Bool
EncodeException -> EncodeException -> Ordering
EncodeException -> EncodeException -> EncodeException
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
min :: EncodeException -> EncodeException -> EncodeException
$cmin :: EncodeException -> EncodeException -> EncodeException
max :: EncodeException -> EncodeException -> EncodeException
$cmax :: EncodeException -> EncodeException -> EncodeException
>= :: EncodeException -> EncodeException -> Bool
$c>= :: EncodeException -> EncodeException -> Bool
> :: EncodeException -> EncodeException -> Bool
$c> :: EncodeException -> EncodeException -> Bool
<= :: EncodeException -> EncodeException -> Bool
$c<= :: EncodeException -> EncodeException -> Bool
< :: EncodeException -> EncodeException -> Bool
$c< :: EncodeException -> EncodeException -> Bool
compare :: EncodeException -> EncodeException -> Ordering
$ccompare :: EncodeException -> EncodeException -> Ordering
$cp1Ord :: Eq EncodeException
Ord, Typeable)

instance Exception EncodeException

-- | Indicates an error during the translation of LLVM’s internal representation
-- to the AST provided 'llvm-hs-pure'.
data DecodeException =
  DecodeException !String
  deriving (Int -> DecodeException -> ShowS
[DecodeException] -> ShowS
DecodeException -> String
(Int -> DecodeException -> ShowS)
-> (DecodeException -> String)
-> ([DecodeException] -> ShowS)
-> Show DecodeException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodeException] -> ShowS
$cshowList :: [DecodeException] -> ShowS
show :: DecodeException -> String
$cshow :: DecodeException -> String
showsPrec :: Int -> DecodeException -> ShowS
$cshowsPrec :: Int -> DecodeException -> ShowS
Show, DecodeException -> DecodeException -> Bool
(DecodeException -> DecodeException -> Bool)
-> (DecodeException -> DecodeException -> Bool)
-> Eq DecodeException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodeException -> DecodeException -> Bool
$c/= :: DecodeException -> DecodeException -> Bool
== :: DecodeException -> DecodeException -> Bool
$c== :: DecodeException -> DecodeException -> Bool
Eq, Eq DecodeException
Eq DecodeException =>
(DecodeException -> DecodeException -> Ordering)
-> (DecodeException -> DecodeException -> Bool)
-> (DecodeException -> DecodeException -> Bool)
-> (DecodeException -> DecodeException -> Bool)
-> (DecodeException -> DecodeException -> Bool)
-> (DecodeException -> DecodeException -> DecodeException)
-> (DecodeException -> DecodeException -> DecodeException)
-> Ord DecodeException
DecodeException -> DecodeException -> Bool
DecodeException -> DecodeException -> Ordering
DecodeException -> DecodeException -> DecodeException
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
min :: DecodeException -> DecodeException -> DecodeException
$cmin :: DecodeException -> DecodeException -> DecodeException
max :: DecodeException -> DecodeException -> DecodeException
$cmax :: DecodeException -> DecodeException -> DecodeException
>= :: DecodeException -> DecodeException -> Bool
$c>= :: DecodeException -> DecodeException -> Bool
> :: DecodeException -> DecodeException -> Bool
$c> :: DecodeException -> DecodeException -> Bool
<= :: DecodeException -> DecodeException -> Bool
$c<= :: DecodeException -> DecodeException -> Bool
< :: DecodeException -> DecodeException -> Bool
$c< :: DecodeException -> DecodeException -> Bool
compare :: DecodeException -> DecodeException -> Ordering
$ccompare :: DecodeException -> DecodeException -> Ordering
$cp1Ord :: Eq DecodeException
Ord, Typeable)

instance Exception DecodeException

-- | Indicates an error during the parsing of a module. This is used
-- for errors encountered when parsing LLVM’s human readable assembly
-- format and when parsing the binary bitcode format.
data ParseFailureException =
  ParseFailureException !String
  deriving (Int -> ParseFailureException -> ShowS
[ParseFailureException] -> ShowS
ParseFailureException -> String
(Int -> ParseFailureException -> ShowS)
-> (ParseFailureException -> String)
-> ([ParseFailureException] -> ShowS)
-> Show ParseFailureException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ParseFailureException] -> ShowS
$cshowList :: [ParseFailureException] -> ShowS
show :: ParseFailureException -> String
$cshow :: ParseFailureException -> String
showsPrec :: Int -> ParseFailureException -> ShowS
$cshowsPrec :: Int -> ParseFailureException -> ShowS
Show, ParseFailureException -> ParseFailureException -> Bool
(ParseFailureException -> ParseFailureException -> Bool)
-> (ParseFailureException -> ParseFailureException -> Bool)
-> Eq ParseFailureException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParseFailureException -> ParseFailureException -> Bool
$c/= :: ParseFailureException -> ParseFailureException -> Bool
== :: ParseFailureException -> ParseFailureException -> Bool
$c== :: ParseFailureException -> ParseFailureException -> Bool
Eq, Eq ParseFailureException
Eq ParseFailureException =>
(ParseFailureException -> ParseFailureException -> Ordering)
-> (ParseFailureException -> ParseFailureException -> Bool)
-> (ParseFailureException -> ParseFailureException -> Bool)
-> (ParseFailureException -> ParseFailureException -> Bool)
-> (ParseFailureException -> ParseFailureException -> Bool)
-> (ParseFailureException
    -> ParseFailureException -> ParseFailureException)
-> (ParseFailureException
    -> ParseFailureException -> ParseFailureException)
-> Ord ParseFailureException
ParseFailureException -> ParseFailureException -> Bool
ParseFailureException -> ParseFailureException -> Ordering
ParseFailureException
-> ParseFailureException -> ParseFailureException
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
min :: ParseFailureException
-> ParseFailureException -> ParseFailureException
$cmin :: ParseFailureException
-> ParseFailureException -> ParseFailureException
max :: ParseFailureException
-> ParseFailureException -> ParseFailureException
$cmax :: ParseFailureException
-> ParseFailureException -> ParseFailureException
>= :: ParseFailureException -> ParseFailureException -> Bool
$c>= :: ParseFailureException -> ParseFailureException -> Bool
> :: ParseFailureException -> ParseFailureException -> Bool
$c> :: ParseFailureException -> ParseFailureException -> Bool
<= :: ParseFailureException -> ParseFailureException -> Bool
$c<= :: ParseFailureException -> ParseFailureException -> Bool
< :: ParseFailureException -> ParseFailureException -> Bool
$c< :: ParseFailureException -> ParseFailureException -> Bool
compare :: ParseFailureException -> ParseFailureException -> Ordering
$ccompare :: ParseFailureException -> ParseFailureException -> Ordering
$cp1Ord :: Eq ParseFailureException
Ord, Typeable)

instance Exception ParseFailureException

-- | Indicates an error during the linking of two modules.
data LinkException =
  LinkException !String
  deriving (Int -> LinkException -> ShowS
[LinkException] -> ShowS
LinkException -> String
(Int -> LinkException -> ShowS)
-> (LinkException -> String)
-> ([LinkException] -> ShowS)
-> Show LinkException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LinkException] -> ShowS
$cshowList :: [LinkException] -> ShowS
show :: LinkException -> String
$cshow :: LinkException -> String
showsPrec :: Int -> LinkException -> ShowS
$cshowsPrec :: Int -> LinkException -> ShowS
Show, LinkException -> LinkException -> Bool
(LinkException -> LinkException -> Bool)
-> (LinkException -> LinkException -> Bool) -> Eq LinkException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LinkException -> LinkException -> Bool
$c/= :: LinkException -> LinkException -> Bool
== :: LinkException -> LinkException -> Bool
$c== :: LinkException -> LinkException -> Bool
Eq, Eq LinkException
Eq LinkException =>
(LinkException -> LinkException -> Ordering)
-> (LinkException -> LinkException -> Bool)
-> (LinkException -> LinkException -> Bool)
-> (LinkException -> LinkException -> Bool)
-> (LinkException -> LinkException -> Bool)
-> (LinkException -> LinkException -> LinkException)
-> (LinkException -> LinkException -> LinkException)
-> Ord LinkException
LinkException -> LinkException -> Bool
LinkException -> LinkException -> Ordering
LinkException -> LinkException -> LinkException
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
min :: LinkException -> LinkException -> LinkException
$cmin :: LinkException -> LinkException -> LinkException
max :: LinkException -> LinkException -> LinkException
$cmax :: LinkException -> LinkException -> LinkException
>= :: LinkException -> LinkException -> Bool
$c>= :: LinkException -> LinkException -> Bool
> :: LinkException -> LinkException -> Bool
$c> :: LinkException -> LinkException -> Bool
<= :: LinkException -> LinkException -> Bool
$c<= :: LinkException -> LinkException -> Bool
< :: LinkException -> LinkException -> Bool
$c< :: LinkException -> LinkException -> Bool
compare :: LinkException -> LinkException -> Ordering
$ccompare :: LinkException -> LinkException -> Ordering
$cp1Ord :: Eq LinkException
Ord, Typeable)

instance Exception LinkException

-- | Indicates an error during the creation of a
-- <http://llvm.org/docs/doxygen/html/classllvm_1_1raw__fd__ostream.html raw_fd_ostream>.
-- This could be caused by a nonexisting file path.
data FdStreamException =
  FdStreamException !String
  deriving (Int -> FdStreamException -> ShowS
[FdStreamException] -> ShowS
FdStreamException -> String
(Int -> FdStreamException -> ShowS)
-> (FdStreamException -> String)
-> ([FdStreamException] -> ShowS)
-> Show FdStreamException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FdStreamException] -> ShowS
$cshowList :: [FdStreamException] -> ShowS
show :: FdStreamException -> String
$cshow :: FdStreamException -> String
showsPrec :: Int -> FdStreamException -> ShowS
$cshowsPrec :: Int -> FdStreamException -> ShowS
Show, FdStreamException -> FdStreamException -> Bool
(FdStreamException -> FdStreamException -> Bool)
-> (FdStreamException -> FdStreamException -> Bool)
-> Eq FdStreamException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FdStreamException -> FdStreamException -> Bool
$c/= :: FdStreamException -> FdStreamException -> Bool
== :: FdStreamException -> FdStreamException -> Bool
$c== :: FdStreamException -> FdStreamException -> Bool
Eq, Eq FdStreamException
Eq FdStreamException =>
(FdStreamException -> FdStreamException -> Ordering)
-> (FdStreamException -> FdStreamException -> Bool)
-> (FdStreamException -> FdStreamException -> Bool)
-> (FdStreamException -> FdStreamException -> Bool)
-> (FdStreamException -> FdStreamException -> Bool)
-> (FdStreamException -> FdStreamException -> FdStreamException)
-> (FdStreamException -> FdStreamException -> FdStreamException)
-> Ord FdStreamException
FdStreamException -> FdStreamException -> Bool
FdStreamException -> FdStreamException -> Ordering
FdStreamException -> FdStreamException -> FdStreamException
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
min :: FdStreamException -> FdStreamException -> FdStreamException
$cmin :: FdStreamException -> FdStreamException -> FdStreamException
max :: FdStreamException -> FdStreamException -> FdStreamException
$cmax :: FdStreamException -> FdStreamException -> FdStreamException
>= :: FdStreamException -> FdStreamException -> Bool
$c>= :: FdStreamException -> FdStreamException -> Bool
> :: FdStreamException -> FdStreamException -> Bool
$c> :: FdStreamException -> FdStreamException -> Bool
<= :: FdStreamException -> FdStreamException -> Bool
$c<= :: FdStreamException -> FdStreamException -> Bool
< :: FdStreamException -> FdStreamException -> Bool
$c< :: FdStreamException -> FdStreamException -> Bool
compare :: FdStreamException -> FdStreamException -> Ordering
$ccompare :: FdStreamException -> FdStreamException -> Ordering
$cp1Ord :: Eq FdStreamException
Ord, Typeable)

instance Exception FdStreamException

-- | Indicates an error during a call to 'LLVM.Internal.Module.targetMachineEmit'.
data TargetMachineEmitException =
  TargetMachineEmitException !String
  deriving (Int -> TargetMachineEmitException -> ShowS
[TargetMachineEmitException] -> ShowS
TargetMachineEmitException -> String
(Int -> TargetMachineEmitException -> ShowS)
-> (TargetMachineEmitException -> String)
-> ([TargetMachineEmitException] -> ShowS)
-> Show TargetMachineEmitException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TargetMachineEmitException] -> ShowS
$cshowList :: [TargetMachineEmitException] -> ShowS
show :: TargetMachineEmitException -> String
$cshow :: TargetMachineEmitException -> String
showsPrec :: Int -> TargetMachineEmitException -> ShowS
$cshowsPrec :: Int -> TargetMachineEmitException -> ShowS
Show, TargetMachineEmitException -> TargetMachineEmitException -> Bool
(TargetMachineEmitException -> TargetMachineEmitException -> Bool)
-> (TargetMachineEmitException
    -> TargetMachineEmitException -> Bool)
-> Eq TargetMachineEmitException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TargetMachineEmitException -> TargetMachineEmitException -> Bool
$c/= :: TargetMachineEmitException -> TargetMachineEmitException -> Bool
== :: TargetMachineEmitException -> TargetMachineEmitException -> Bool
$c== :: TargetMachineEmitException -> TargetMachineEmitException -> Bool
Eq, Eq TargetMachineEmitException
Eq TargetMachineEmitException =>
(TargetMachineEmitException
 -> TargetMachineEmitException -> Ordering)
-> (TargetMachineEmitException
    -> TargetMachineEmitException -> Bool)
-> (TargetMachineEmitException
    -> TargetMachineEmitException -> Bool)
-> (TargetMachineEmitException
    -> TargetMachineEmitException -> Bool)
-> (TargetMachineEmitException
    -> TargetMachineEmitException -> Bool)
-> (TargetMachineEmitException
    -> TargetMachineEmitException -> TargetMachineEmitException)
-> (TargetMachineEmitException
    -> TargetMachineEmitException -> TargetMachineEmitException)
-> Ord TargetMachineEmitException
TargetMachineEmitException -> TargetMachineEmitException -> Bool
TargetMachineEmitException
-> TargetMachineEmitException -> Ordering
TargetMachineEmitException
-> TargetMachineEmitException -> TargetMachineEmitException
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
min :: TargetMachineEmitException
-> TargetMachineEmitException -> TargetMachineEmitException
$cmin :: TargetMachineEmitException
-> TargetMachineEmitException -> TargetMachineEmitException
max :: TargetMachineEmitException
-> TargetMachineEmitException -> TargetMachineEmitException
$cmax :: TargetMachineEmitException
-> TargetMachineEmitException -> TargetMachineEmitException
>= :: TargetMachineEmitException -> TargetMachineEmitException -> Bool
$c>= :: TargetMachineEmitException -> TargetMachineEmitException -> Bool
> :: TargetMachineEmitException -> TargetMachineEmitException -> Bool
$c> :: TargetMachineEmitException -> TargetMachineEmitException -> Bool
<= :: TargetMachineEmitException -> TargetMachineEmitException -> Bool
$c<= :: TargetMachineEmitException -> TargetMachineEmitException -> Bool
< :: TargetMachineEmitException -> TargetMachineEmitException -> Bool
$c< :: TargetMachineEmitException -> TargetMachineEmitException -> Bool
compare :: TargetMachineEmitException
-> TargetMachineEmitException -> Ordering
$ccompare :: TargetMachineEmitException
-> TargetMachineEmitException -> Ordering
$cp1Ord :: Eq TargetMachineEmitException
Ord, Typeable)

instance Exception TargetMachineEmitException

-- | Indicates a failure to find the target.
data LookupTargetException =
  LookupTargetException !String
  deriving (Int -> LookupTargetException -> ShowS
[LookupTargetException] -> ShowS
LookupTargetException -> String
(Int -> LookupTargetException -> ShowS)
-> (LookupTargetException -> String)
-> ([LookupTargetException] -> ShowS)
-> Show LookupTargetException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LookupTargetException] -> ShowS
$cshowList :: [LookupTargetException] -> ShowS
show :: LookupTargetException -> String
$cshow :: LookupTargetException -> String
showsPrec :: Int -> LookupTargetException -> ShowS
$cshowsPrec :: Int -> LookupTargetException -> ShowS
Show, LookupTargetException -> LookupTargetException -> Bool
(LookupTargetException -> LookupTargetException -> Bool)
-> (LookupTargetException -> LookupTargetException -> Bool)
-> Eq LookupTargetException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LookupTargetException -> LookupTargetException -> Bool
$c/= :: LookupTargetException -> LookupTargetException -> Bool
== :: LookupTargetException -> LookupTargetException -> Bool
$c== :: LookupTargetException -> LookupTargetException -> Bool
Eq, Eq LookupTargetException
Eq LookupTargetException =>
(LookupTargetException -> LookupTargetException -> Ordering)
-> (LookupTargetException -> LookupTargetException -> Bool)
-> (LookupTargetException -> LookupTargetException -> Bool)
-> (LookupTargetException -> LookupTargetException -> Bool)
-> (LookupTargetException -> LookupTargetException -> Bool)
-> (LookupTargetException
    -> LookupTargetException -> LookupTargetException)
-> (LookupTargetException
    -> LookupTargetException -> LookupTargetException)
-> Ord LookupTargetException
LookupTargetException -> LookupTargetException -> Bool
LookupTargetException -> LookupTargetException -> Ordering
LookupTargetException
-> LookupTargetException -> LookupTargetException
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
min :: LookupTargetException
-> LookupTargetException -> LookupTargetException
$cmin :: LookupTargetException
-> LookupTargetException -> LookupTargetException
max :: LookupTargetException
-> LookupTargetException -> LookupTargetException
$cmax :: LookupTargetException
-> LookupTargetException -> LookupTargetException
>= :: LookupTargetException -> LookupTargetException -> Bool
$c>= :: LookupTargetException -> LookupTargetException -> Bool
> :: LookupTargetException -> LookupTargetException -> Bool
$c> :: LookupTargetException -> LookupTargetException -> Bool
<= :: LookupTargetException -> LookupTargetException -> Bool
$c<= :: LookupTargetException -> LookupTargetException -> Bool
< :: LookupTargetException -> LookupTargetException -> Bool
$c< :: LookupTargetException -> LookupTargetException -> Bool
compare :: LookupTargetException -> LookupTargetException -> Ordering
$ccompare :: LookupTargetException -> LookupTargetException -> Ordering
$cp1Ord :: Eq LookupTargetException
Ord, Typeable)

instance Exception LookupTargetException

-- | Indicates an error during the verification of a module.
data VerifyException =
  VerifyException !String
  deriving (Int -> VerifyException -> ShowS
[VerifyException] -> ShowS
VerifyException -> String
(Int -> VerifyException -> ShowS)
-> (VerifyException -> String)
-> ([VerifyException] -> ShowS)
-> Show VerifyException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerifyException] -> ShowS
$cshowList :: [VerifyException] -> ShowS
show :: VerifyException -> String
$cshow :: VerifyException -> String
showsPrec :: Int -> VerifyException -> ShowS
$cshowsPrec :: Int -> VerifyException -> ShowS
Show, VerifyException -> VerifyException -> Bool
(VerifyException -> VerifyException -> Bool)
-> (VerifyException -> VerifyException -> Bool)
-> Eq VerifyException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerifyException -> VerifyException -> Bool
$c/= :: VerifyException -> VerifyException -> Bool
== :: VerifyException -> VerifyException -> Bool
$c== :: VerifyException -> VerifyException -> Bool
Eq, Eq VerifyException
Eq VerifyException =>
(VerifyException -> VerifyException -> Ordering)
-> (VerifyException -> VerifyException -> Bool)
-> (VerifyException -> VerifyException -> Bool)
-> (VerifyException -> VerifyException -> Bool)
-> (VerifyException -> VerifyException -> Bool)
-> (VerifyException -> VerifyException -> VerifyException)
-> (VerifyException -> VerifyException -> VerifyException)
-> Ord VerifyException
VerifyException -> VerifyException -> Bool
VerifyException -> VerifyException -> Ordering
VerifyException -> VerifyException -> VerifyException
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
min :: VerifyException -> VerifyException -> VerifyException
$cmin :: VerifyException -> VerifyException -> VerifyException
max :: VerifyException -> VerifyException -> VerifyException
$cmax :: VerifyException -> VerifyException -> VerifyException
>= :: VerifyException -> VerifyException -> Bool
$c>= :: VerifyException -> VerifyException -> Bool
> :: VerifyException -> VerifyException -> Bool
$c> :: VerifyException -> VerifyException -> Bool
<= :: VerifyException -> VerifyException -> Bool
$c<= :: VerifyException -> VerifyException -> Bool
< :: VerifyException -> VerifyException -> Bool
$c< :: VerifyException -> VerifyException -> Bool
compare :: VerifyException -> VerifyException -> Ordering
$ccompare :: VerifyException -> VerifyException -> Ordering
$cp1Ord :: Eq VerifyException
Ord, Typeable)

instance Exception VerifyException