Safe Haskell | None |
---|---|
Language | Haskell98 |
This module contains the *types* related creating Errors. It depends only on Fixpoint and basic haskell libraries, and hence, should be importable everywhere.
Synopsis
- data TError t
- = ErrSubType { }
- | ErrSubTypeModel { }
- | ErrFCrash { }
- | ErrHole { }
- | ErrHoleCycle {
- pos :: !SrcSpan
- holesCycle :: [Symbol]
- | ErrAssType { }
- | ErrParse { }
- | ErrTySpec { }
- | ErrTermSpec { }
- | ErrDupAlias { }
- | ErrDupSpecs { }
- | ErrDupIMeas { }
- | ErrDupMeas { }
- | ErrDupField { }
- | ErrDupNames { }
- | ErrBadData { }
- | ErrBadGADT { }
- | ErrDataCon { }
- | ErrInvt { }
- | ErrIAl { }
- | ErrIAlMis { }
- | ErrMeas { }
- | ErrHMeas { }
- | ErrUnbound { }
- | ErrUnbPred { }
- | ErrGhc { }
- | ErrResolve { }
- | ErrMismatch { }
- | ErrPartPred { }
- | ErrAliasCycle { }
- | ErrIllegalAliasApp { }
- | ErrAliasApp { }
- | ErrTermin { }
- | ErrStTerm { }
- | ErrILaw { }
- | ErrRClass { }
- | ErrMClass { }
- | ErrBadQual { }
- | ErrSaved { }
- | ErrFilePragma { }
- | ErrTyCon { }
- | ErrLiftExp { }
- | ErrParseAnn { }
- | ErrNoSpec { }
- | ErrFail { }
- | ErrFailUsed { }
- | ErrRewrite { }
- | ErrOther { }
- data CtxError t = CtxError {}
- errorsWithContext :: [TError Doc] -> IO [CtxError Doc]
- data Oblig
- data WithModel t
- dropModel :: WithModel t -> t
- type UserError = TError Doc
- panic :: Maybe SrcSpan -> String -> a
- panicDoc :: SrcSpan -> Doc -> a
- todo :: Maybe SrcSpan -> String -> a
- impossible :: Maybe SrcSpan -> String -> a
- uError :: UserError -> a
- sourceErrors :: String -> SourceError -> [TError t]
- errDupSpecs :: Doc -> ListNE SrcSpan -> TError t
- ppError :: (PPrint a, Show a) => Tidy -> Doc -> TError a -> Doc
- ppTicks :: PPrint a => a -> Doc
- realSrcSpan :: FilePath -> Int -> Int -> Int -> Int -> RealSrcSpan
- unpackRealSrcSpan :: RealSrcSpan -> (String, Int, Int, Int, Int)
- srcSpanFileMb :: SrcSpan -> Maybe FilePath
Generic Error Type
Generic Type for Error Messages -------------------------------------------
INVARIANT : all Error constructors should have a pos field
ErrSubType | liquid type error |
ErrSubTypeModel | liquid type error with a counter-example |
ErrFCrash | liquid type error |
ErrHole | hole type |
ErrHoleCycle | hole dependencies form a cycle error |
| |
ErrAssType | condition failure error |
ErrParse | specification parse error |
ErrTySpec | sort error in specification |
ErrTermSpec | sort error in specification |
ErrDupAlias | multiple alias with same name error |
ErrDupSpecs | multiple specs for same binder error |
ErrDupIMeas | multiple definitions of the same instance measure |
ErrDupMeas | multiple definitions of the same measure |
ErrDupField | duplicate fields in same datacon |
ErrDupNames | name resolves to multiple possible GHC vars |
ErrBadData | bad data type specification (?) |
ErrBadGADT | bad data type specification (?) |
ErrDataCon | refined datacon mismatches haskell datacon |
ErrInvt | Invariant sort error |
ErrIAl | Using sort error |
ErrIAlMis | Incompatible using error |
ErrMeas | Measure sort error |
ErrHMeas | Haskell bad Measure error |
ErrUnbound | Unbound symbol in specification |
ErrUnbPred | Unbound predicate being applied |
ErrGhc | GHC error: parsing or type checking |
ErrResolve | Name resolution error |
ErrMismatch | Mismatch between Liquid and Haskell types |
ErrPartPred | Mismatch in expected/actual args of abstract refinement |
ErrAliasCycle | Cyclic Refined Type Alias Definitions |
ErrIllegalAliasApp | Illegal RTAlias application (from BSort, eg. in PVar) |
ErrAliasApp | |
ErrTermin | Termination Error |
ErrStTerm | Termination Error |
ErrILaw | Instance Law Error |
ErrRClass | Refined Class/Interfaces Conflict |
ErrMClass | Standalone class method refinements |
ErrBadQual | Non well sorted Qualifier |
ErrSaved | Previously saved error, that carries over after DiffCheck |
ErrFilePragma | |
ErrTyCon | |
ErrLiftExp | |
ErrParseAnn | |
ErrNoSpec | |
ErrFail | |
ErrFailUsed | |
ErrRewrite | |
ErrOther | Sigh. Other. |
Instances
Error with Source Context
Context information for Error Messages ------------------------------------
Instances
Functor CtxError # | |
Eq (CtxError t) # | |
Ord (CtxError t) # | |
Defined in Language.Haskell.Liquid.Types.Errors | |
Show (CtxError Doc) # | |
PPrint (CtxError Doc) # | Pretty Printing Error Messages -------------------------------------------- Need to put |
Defined in Language.Haskell.Liquid.UX.Tidy | |
PPrint (CtxError SpecType) # | |
Defined in Language.Haskell.Liquid.UX.Tidy |
Subtyping Obligation Type
Different kinds of Check Obligations ------------------------------------
OTerm | Obligation that proves termination |
OInv | Obligation that proves invariants |
OCons | Obligation that proves subtyping constraints |
Instances
Eq Oblig # | |
Data Oblig # | |
Defined in Language.Haskell.Liquid.Types.Errors gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Oblig -> c Oblig # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Oblig # dataTypeOf :: Oblig -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Oblig) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Oblig) # gmapT :: (forall b. Data b => b -> b) -> Oblig -> Oblig # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Oblig -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Oblig -> r # gmapQ :: (forall d. Data d => d -> u) -> Oblig -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Oblig -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Oblig -> m Oblig # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Oblig -> m Oblig # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Oblig -> m Oblig # | |
Show Oblig # | |
Generic Oblig # | |
NFData Oblig # | |
Defined in Language.Haskell.Liquid.Types.Errors | |
Binary Oblig # | |
PPrint Oblig # | |
Defined in Language.Haskell.Liquid.Types.Errors pprintTidy :: Tidy -> Oblig -> Doc # pprintPrec :: Int -> Tidy -> Oblig -> Doc # | |
Hashable Oblig # | |
Defined in Language.Haskell.Liquid.Types.Errors | |
type Rep Oblig # | |
Defined in Language.Haskell.Liquid.Types.Errors type Rep Oblig = D1 ('MetaData "Oblig" "Language.Haskell.Liquid.Types.Errors" "liquidhaskell-0.8.10.1-inplace" 'False) (C1 ('MetaCons "OTerm" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OInv" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OCons" 'PrefixI 'False) (U1 :: Type -> Type))) |
Adding a Model of the context
Instances
Functor WithModel # | |
Eq t => Eq (WithModel t) # | |
Show t => Show (WithModel t) # | |
Generic (WithModel t) # | |
NFData t => NFData (WithModel t) # | |
Defined in Language.Haskell.Liquid.Types.Errors | |
Subable t => Subable (WithModel t) | |
type Rep (WithModel t) # | |
Defined in Language.Haskell.Liquid.Types.Errors type Rep (WithModel t) = D1 ('MetaData "WithModel" "Language.Haskell.Liquid.Types.Errors" "liquidhaskell-0.8.10.1-inplace" 'False) (C1 ('MetaCons "NoModel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 t)) :+: C1 ('MetaCons "WithModel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Doc) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 t))) |
Panic (unexpected failures)
Simple unstructured type for panic ----------------------------------------
todo :: Maybe SrcSpan -> String -> a #
Construct and show an Error with an optional SrcSpan, then crash This function should be used to mark unimplemented functionality
impossible :: Maybe SrcSpan -> String -> a #
Construct and show an Error with an optional SrcSpan, then crash This function should be used to mark impossible-to-reach codepaths
sourceErrors :: String -> SourceError -> [TError t] #
Convert a GHC error into a list of our errors.
errDupSpecs :: Doc -> ListNE SrcSpan -> TError t #
Printing Errors
SrcSpan Helpers
realSrcSpan :: FilePath -> Int -> Int -> Int -> Int -> RealSrcSpan #
unpackRealSrcSpan :: RealSrcSpan -> (String, Int, Int, Int, Int) #
srcSpanFileMb :: SrcSpan -> Maybe FilePath #
Orphan instances
NFData ParseError # | |
rnf :: ParseError -> () # | |
PPrint SrcSpan # | |
pprintTidy :: Tidy -> SrcSpan -> Doc # pprintPrec :: Int -> Tidy -> SrcSpan -> Doc # | |
PPrint ParseError # | |
pprintTidy :: Tidy -> ParseError -> Doc # pprintPrec :: Int -> Tidy -> ParseError -> Doc # | |
FromJSON RealSrcSpan # | |
parseJSON :: Value -> Parser RealSrcSpan parseJSONList :: Value -> Parser [RealSrcSpan] | |
FromJSON SrcSpan # | |
parseJSON :: Value -> Parser SrcSpan parseJSONList :: Value -> Parser [SrcSpan] | |
FromJSONKey SrcSpan # | |
fromJSONKey :: FromJSONKeyFunction SrcSpan fromJSONKeyList :: FromJSONKeyFunction [SrcSpan] | |
ToJSON RealSrcSpan # | |
toJSON :: RealSrcSpan -> Value toEncoding :: RealSrcSpan -> Encoding toJSONList :: [RealSrcSpan] -> Value toEncodingList :: [RealSrcSpan] -> Encoding | |
ToJSON SrcSpan # | |
toEncoding :: SrcSpan -> Encoding toJSONList :: [SrcSpan] -> Value toEncodingList :: [SrcSpan] -> Encoding | |
ToJSONKey SrcSpan # | |
toJSONKey :: ToJSONKeyFunction SrcSpan toJSONKeyList :: ToJSONKeyFunction [SrcSpan] |