Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- data SrcSpan = SS {}
- dummySpan :: SrcSpan
- sourcePosElts :: SourcePos -> (SourceName, Line, Column)
- data FixResult a
- colorResult :: FixResult a -> Moods
- resultDoc :: Fixpoint a => FixResult a -> Doc
- resultExit :: FixResult a -> ExitCode
- data Error
- data Error1
- err :: SrcSpan -> Doc -> Error
- errLoc :: Error1 -> SrcSpan
- errMsg :: Error1 -> Doc
- errs :: Error -> [Error1]
- catError :: Error -> Error -> Error
- catErrors :: ListNE Error -> Error
- panic :: String -> a
- die :: Error -> a
- dieAt :: SrcSpan -> Error -> a
- exit :: a -> IO a -> IO a
- errFreeVarInQual :: (PPrint q, Loc q, PPrint x) => q -> x -> Error
- errFreeVarInConstraint :: PPrint a => (Integer, a) -> Error
- errIllScopedKVar :: (PPrint k, PPrint bs) => (k, Integer, Integer, bs) -> Error
Concrete Location Type
A Reusable SrcSpan Type ------------------------------------------
Instances
sourcePosElts :: SourcePos -> (SourceName, Line, Column) Source #
Result
Result ---------------------------------------------------------
Crash [a] String | |
Safe Stats | The |
Unsafe Stats ![a] |
Instances
colorResult :: FixResult a -> Moods Source #
resultExit :: FixResult a -> ExitCode Source #
Error Type
A BareBones Error Type ----------------------------------------------------
Instances
Eq Error Source # | |
Ord Error Source # | |
Show Error Source # | |
Generic Error Source # | |
Exception Error Source # | |
Defined in Language.Fixpoint.Types.Errors toException :: Error -> SomeException # fromException :: SomeException -> Maybe Error # displayException :: Error -> String # | |
Serialize Error Source # | |
PPrint Error Source # | |
Defined in Language.Fixpoint.Types.Errors | |
Exception (FixResult Error) Source # | |
Defined in Language.Fixpoint.Types.Errors toException :: FixResult Error -> SomeException # fromException :: SomeException -> Maybe (FixResult Error) # displayException :: FixResult Error -> String # | |
Serialize (FixResult Error) Source # | |
type Rep Error Source # | |
Defined in Language.Fixpoint.Types.Errors |
Instances
Eq Error1 Source # | |
Ord Error1 Source # | |
Show Error1 Source # | |
Generic Error1 Source # | |
Serialize Error1 Source # | |
PPrint Error1 Source # | |
Defined in Language.Fixpoint.Types.Errors | |
Fixpoint Error1 Source # | |
type Rep Error1 Source # | |
Defined in Language.Fixpoint.Types.Errors type Rep Error1 = D1 (MetaData "Error1" "Language.Fixpoint.Types.Errors" "liquid-fixpoint-0.8.0.2-EGSzGwrlcJrCaUaEYLNzOY" False) (C1 (MetaCons "Error1" PrefixI True) (S1 (MetaSel (Just "errLoc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan) :*: S1 (MetaSel (Just "errMsg") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Doc))) |
Constructor
Accessors
Adding Insult to Injury
Fatal Exit
Some popular errors
errFreeVarInQual :: (PPrint q, Loc q, PPrint x) => q -> x -> Error Source #
Catalogue of Errors --------------------------------------------
Orphan instances
Serialize Doc Source # | |
Serialize TextDetails Source # | |
put :: Putter TextDetails # get :: Get TextDetails # | |
Generic (AnnotDetails a) Source # | |
type Rep (AnnotDetails a) :: Type -> Type # from :: AnnotDetails a -> Rep (AnnotDetails a) x # to :: Rep (AnnotDetails a) x -> AnnotDetails a # | |
Serialize a => Serialize (Doc a) Source # | |
Serialize a => Serialize (AnnotDetails a) Source # | |
put :: Putter (AnnotDetails a) # get :: Get (AnnotDetails a) # |