Safe Haskell | Safe-Inferred |
---|---|
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
- errBadDataDecl :: (Loc x, PPrint x) => x -> Error
Concrete Location Type
A Reusable SrcSpan Type ------------------------------------------
Instances
Data SrcSpan Source # | |
Defined in Language.Fixpoint.Types.Spans gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcSpan -> c SrcSpan # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcSpan # toConstr :: SrcSpan -> Constr # dataTypeOf :: SrcSpan -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcSpan) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcSpan) # gmapT :: (forall b. Data b => b -> b) -> SrcSpan -> SrcSpan # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r # gmapQ :: (forall d. Data d => d -> u) -> SrcSpan -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcSpan -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # | |
Generic SrcSpan Source # | |
Show SrcSpan Source # | |
Binary SrcSpan Source # | |
Serialize SrcSpan Source # | |
NFData SrcSpan Source # | |
Defined in Language.Fixpoint.Types.Spans | |
Eq SrcSpan Source # | |
Ord SrcSpan Source # | |
Defined in Language.Fixpoint.Types.Spans | |
Hashable SrcSpan Source # | |
Defined in Language.Fixpoint.Types.Spans | |
PPrint SrcSpan Source # | |
Defined in Language.Fixpoint.Types.Spans | |
Loc SrcSpan Source # | |
Store SrcSpan Source # | |
type Rep SrcSpan Source # | |
Defined in Language.Fixpoint.Types.Spans type Rep SrcSpan = D1 ('MetaData "SrcSpan" "Language.Fixpoint.Types.Spans" "liquid-fixpoint-0.9.2.5-8VOJ4a5jXPy7nyhLFTxkOW" 'False) (C1 ('MetaCons "SS" 'PrefixI 'True) (S1 ('MetaSel ('Just "sp_start") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SourcePos) :*: S1 ('MetaSel ('Just "sp_stop") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SourcePos))) |
sourcePosElts :: SourcePos -> (SourceName, Line, Column) Source #
Result
Result ---------------------------------------------------------
Crash [(a, Maybe String)] String | |
Unsafe Stats ![a] | |
Safe Stats | The |
Instances
colorResult :: FixResult a -> Moods Source #
resultExit :: FixResult a -> ExitCode Source #
Error Type
A BareBones Error Type ----------------------------------------------------
Instances
Exception Error Source # | |
Defined in Language.Fixpoint.Types.Errors toException :: Error -> SomeException # fromException :: SomeException -> Maybe Error # displayException :: Error -> String # | |
Generic Error Source # | |
Show Error Source # | |
Serialize Error Source # | |
Eq Error Source # | |
Ord Error Source # | |
PPrint Error Source # | |
Defined in Language.Fixpoint.Types.Errors | |
Serialize (FixResult Error) Source # | |
type Rep Error Source # | |
Defined in Language.Fixpoint.Types.Errors |
Instances
Generic Error1 Source # | |
Show Error1 Source # | |
Serialize Error1 Source # | |
Eq Error1 Source # | |
Ord Error1 Source # | |
Fixpoint Error1 Source # | |
PPrint Error1 Source # | |
Defined in Language.Fixpoint.Types.Errors | |
type Rep Error1 Source # | |
Defined in Language.Fixpoint.Types.Errors type Rep Error1 = D1 ('MetaData "Error1" "Language.Fixpoint.Types.Errors" "liquid-fixpoint-0.9.2.5-8VOJ4a5jXPy7nyhLFTxkOW" '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
errBadDataDecl :: (Loc x, PPrint x) => x -> Error Source #
Catalogue of Errors --------------------------------------------
Orphan instances
Serialize TextDetails Source # | |
put :: Putter TextDetails # get :: Get TextDetails # | |
Serialize Doc Source # | |
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 (AnnotDetails a) Source # | |
put :: Putter (AnnotDetails a) # get :: Get (AnnotDetails a) # | |
Serialize a => Serialize (Doc a) Source # | |