liquidhaskell-0.8.0.2: Liquid Types for Haskell

Safe HaskellNone
LanguageHaskell98

Language.Haskell.Liquid.Types.Errors

Contents

Description

This module contains the *types* related creating Errors. It depends only on Fixpoint and basic haskell libraries, and hence, should be importable everywhere.

Synopsis

Generic Error Type

data TError t Source #

Generic Type for Error Messages -------------------------------------------

INVARIANT : all Error constructors should have a pos field

Constructors

ErrSubType

liquid type error

Fields

ErrSubTypeModel

liquid type error with a counter-example

Fields

ErrFCrash

liquid type error

Fields

ErrAssType

condition failure error

Fields

ErrParse

specification parse error

Fields

ErrTySpec

sort error in specification

Fields

ErrTermSpec

sort error in specification

Fields

ErrDupAlias

multiple alias with same name error

Fields

ErrDupSpecs

multiple specs for same binder error

Fields

ErrDupIMeas

multiple definitions of the same instance measure

Fields

ErrDupMeas

multiple definitions of the same measure

Fields

ErrDupField

duplicate fields in same datacon

Fields

ErrDupNames

name resolves to multiple possible GHC vars

Fields

ErrBadData

bad data type specification (?)

Fields

ErrDataCon

refined datacon mismatches haskell datacon

Fields

ErrInvt

Invariant sort error

Fields

ErrIAl

Using sort error

Fields

ErrIAlMis

Incompatible using error

Fields

ErrMeas

Measure sort error

Fields

ErrHMeas

Haskell bad Measure error

Fields

ErrUnbound

Unbound symbol in specification

Fields

ErrUnbPred

Unbound predicate being applied

Fields

ErrGhc

GHC error: parsing or type checking

Fields

ErrMismatch

Mismatch between Liquid and Haskell types

Fields

ErrPartPred

Mismatch in expected/actual args of abstract refinement

Fields

ErrAliasCycle

Cyclic Refined Type Alias Definitions

Fields

ErrIllegalAliasApp

Illegal RTAlias application (from BSort, eg. in PVar)

Fields

ErrAliasApp 

Fields

ErrTermin

Termination Error

Fields

ErrRClass

Refined Class/Interfaces Conflict

Fields

ErrBadQual

Non well sorted Qualifier

Fields

ErrSaved

Previously saved error, that carries over after DiffCheck

Fields

ErrFilePragma 

Fields

ErrTyCon 

Fields

ErrLiftExp 

Fields

ErrParseAnn 

Fields

ErrOther

Sigh. Other.

Fields

Instances

Functor TError Source # 

Methods

fmap :: (a -> b) -> TError a -> TError b #

(<$) :: a -> TError b -> TError a #

Show UserError Source # 
Exception UserError Source # 
PPrint UserError Source # 

Methods

pprintTidy :: Tidy -> UserError -> Doc #

pprintPrec :: Int -> Tidy -> UserError -> Doc #

Result UserError Source # 

Methods

result :: UserError -> FixResult UserError Source #

Result Error Source # 

Methods

result :: Error -> FixResult UserError Source #

Eq (TError a) Source # 

Methods

(==) :: TError a -> TError a -> Bool #

(/=) :: TError a -> TError a -> Bool #

Ord (TError a) Source # 

Methods

compare :: TError a -> TError a -> Ordering #

(<) :: TError a -> TError a -> Bool #

(<=) :: TError a -> TError a -> Bool #

(>) :: TError a -> TError a -> Bool #

(>=) :: TError a -> TError a -> Bool #

max :: TError a -> TError a -> TError a #

min :: TError a -> TError a -> TError a #

Generic (TError t) Source # 

Associated Types

type Rep (TError t) :: * -> * #

Methods

from :: TError t -> Rep (TError t) x #

to :: Rep (TError t) x -> TError t #

(PPrint a, Show a) => ToJSON (TError a) Source # 

Methods

toJSON :: TError a -> Value #

toEncoding :: TError a -> Encoding #

FromJSON (TError a) Source # 

Methods

parseJSON :: Value -> Parser (TError a) #

Result [Error] Source # 

Methods

result :: [Error] -> FixResult UserError Source #

type Rep (TError t) Source # 
type Rep (TError t) = D1 (MetaData "TError" "Language.Haskell.Liquid.Types.Errors" "liquidhaskell-0.8.0.2-4zWDXa3VLIUKANK5k7Jte1" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ErrSubType" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc))) ((:*:) (S1 (MetaSel (Just Symbol "ctx") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap Symbol t))) ((:*:) (S1 (MetaSel (Just Symbol "tact") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t)) (S1 (MetaSel (Just Symbol "texp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t)))))) (C1 (MetaCons "ErrSubTypeModel" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc))) ((:*:) (S1 (MetaSel (Just Symbol "ctxM") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap Symbol (WithModel t)))) ((:*:) (S1 (MetaSel (Just Symbol "tactM") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (WithModel t))) (S1 (MetaSel (Just Symbol "texp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t))))))) ((:+:) (C1 (MetaCons "ErrFCrash" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc))) ((:*:) (S1 (MetaSel (Just Symbol "ctx") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap Symbol t))) ((:*:) (S1 (MetaSel (Just Symbol "tact") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t)) (S1 (MetaSel (Just Symbol "texp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t)))))) (C1 (MetaCons "ErrAssType" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "obl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Oblig))) ((:*:) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) ((:*:) (S1 (MetaSel (Just Symbol "ctx") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap Symbol t))) (S1 (MetaSel (Just Symbol "cond") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 t)))))))) ((:+:) ((:+:) (C1 (MetaCons "ErrParse" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "pErr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ParseError))))) (C1 (MetaCons "ErrTySpec" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "var") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc))) ((:*:) (S1 (MetaSel (Just Symbol "typ") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)))))) ((:+:) (C1 (MetaCons "ErrTermSpec" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "var") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc))) ((:*:) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) ((:*:) (S1 (MetaSel (Just Symbol "exp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Expr)) (S1 (MetaSel (Just Symbol "msg'") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)))))) ((:+:) (C1 (MetaCons "ErrDupAlias" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "var") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc))) ((:*:) (S1 (MetaSel (Just Symbol "kind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "locs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [SrcSpan]))))) (C1 (MetaCons "ErrDupSpecs" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "var") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "locs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [SrcSpan]))))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ErrDupIMeas" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "var") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc))) ((:*:) (S1 (MetaSel (Just Symbol "tycon") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "locs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [SrcSpan]))))) (C1 (MetaCons "ErrDupMeas" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "var") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "locs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [SrcSpan])))))) ((:+:) (C1 (MetaCons "ErrDupField" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "dcon") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "field") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc))))) (C1 (MetaCons "ErrDupNames" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "var") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "names") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Doc]))))))) ((:+:) ((:+:) (C1 (MetaCons "ErrBadData" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "var") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc))))) (C1 (MetaCons "ErrDataCon" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "var") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)))))) ((:+:) (C1 (MetaCons "ErrInvt" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "inv") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc))))) ((:+:) (C1 (MetaCons "ErrIAl" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "inv") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc))))) (C1 (MetaCons "ErrIAlMis" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "tAs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t))) ((:*:) (S1 (MetaSel (Just Symbol "tUs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)))))))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ErrMeas" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "ms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc))))) (C1 (MetaCons "ErrHMeas" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "ms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)))))) ((:+:) (C1 (MetaCons "ErrUnbound" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "var") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)))) (C1 (MetaCons "ErrUnbPred" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "var") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)))))) ((:+:) ((:+:) (C1 (MetaCons "ErrGhc" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)))) (C1 (MetaCons "ErrMismatch" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "var") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)))) ((:*:) (S1 (MetaSel (Just Symbol "hs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) ((:*:) (S1 (MetaSel (Just Symbol "lqTy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "lqPos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan))))))) ((:+:) (C1 (MetaCons "ErrPartPred" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "ectr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "var") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)))) ((:*:) (S1 (MetaSel (Just Symbol "argN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) ((:*:) (S1 (MetaSel (Just Symbol "expN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Just Symbol "actN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))))) ((:+:) (C1 (MetaCons "ErrAliasCycle" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "acycle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [(SrcSpan, Doc)])))) (C1 (MetaCons "ErrIllegalAliasApp" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "dname") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "dpos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan))))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ErrAliasApp" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "dname") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc))) ((:*:) (S1 (MetaSel (Just Symbol "dpos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc))))) (C1 (MetaCons "ErrTermin" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "bind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Doc])) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)))))) ((:+:) (C1 (MetaCons "ErrRClass" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "cls") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "insts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [(SrcSpan, Doc)]))))) ((:+:) (C1 (MetaCons "ErrBadQual" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "qname") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc))))) (C1 (MetaCons "ErrSaved" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "nam") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)))))))) ((:+:) ((:+:) (C1 (MetaCons "ErrFilePragma" PrefixI True) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan))) (C1 (MetaCons "ErrTyCon" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) ((:*:) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Just Symbol "tcname") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)))))) ((:+:) (C1 (MetaCons "ErrLiftExp" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)))) ((:+:) (C1 (MetaCons "ErrParseAnn" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)))) (C1 (MetaCons "ErrOther" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pos") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Just Symbol "msg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc))))))))))

Error with Source Context

data CtxError t Source #

Context information for Error Messages ------------------------------------

Constructors

CtxError 

Fields

Instances

Functor CtxError Source # 

Methods

fmap :: (a -> b) -> CtxError a -> CtxError b #

(<$) :: a -> CtxError b -> CtxError a #

Eq (CtxError t) Source # 

Methods

(==) :: CtxError t -> CtxError t -> Bool #

(/=) :: CtxError t -> CtxError t -> Bool #

Ord (CtxError t) Source # 

Methods

compare :: CtxError t -> CtxError t -> Ordering #

(<) :: CtxError t -> CtxError t -> Bool #

(<=) :: CtxError t -> CtxError t -> Bool #

(>) :: CtxError t -> CtxError t -> Bool #

(>=) :: CtxError t -> CtxError t -> Bool #

max :: CtxError t -> CtxError t -> CtxError t #

min :: CtxError t -> CtxError t -> CtxError t #

Subtyping Obligation Type

data Oblig Source #

Different kinds of Check Obligations ------------------------------------

Constructors

OTerm

Obligation that proves termination

OInv

Obligation that proves invariants

OCons

Obligation that proves subtyping constraints

Instances

Data Oblig Source # 

Methods

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 #

toConstr :: Oblig -> Constr #

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 :: (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 Source # 

Methods

showsPrec :: Int -> Oblig -> ShowS #

show :: Oblig -> String #

showList :: [Oblig] -> ShowS #

Generic Oblig Source # 

Associated Types

type Rep Oblig :: * -> * #

Methods

from :: Oblig -> Rep Oblig x #

to :: Rep Oblig x -> Oblig #

Binary Oblig Source # 

Methods

put :: Oblig -> Put #

get :: Get Oblig #

putList :: [Oblig] -> Put #

NFData Oblig Source # 

Methods

rnf :: Oblig -> () #

PPrint Oblig Source # 

Methods

pprintTidy :: Tidy -> Oblig -> Doc #

pprintPrec :: Int -> Tidy -> Oblig -> Doc #

type Rep Oblig Source # 
type Rep Oblig = D1 (MetaData "Oblig" "Language.Haskell.Liquid.Types.Errors" "liquidhaskell-0.8.0.2-4zWDXa3VLIUKANK5k7Jte1" False) ((:+:) (C1 (MetaCons "OTerm" PrefixI False) U1) ((:+:) (C1 (MetaCons "OInv" PrefixI False) U1) (C1 (MetaCons "OCons" PrefixI False) U1)))

Adding a Model of the context

data WithModel t Source #

Constructors

NoModel t 
WithModel !Doc t 

Instances

Functor WithModel Source # 

Methods

fmap :: (a -> b) -> WithModel a -> WithModel b #

(<$) :: a -> WithModel b -> WithModel a #

Eq t => Eq (WithModel t) Source # 

Methods

(==) :: WithModel t -> WithModel t -> Bool #

(/=) :: WithModel t -> WithModel t -> Bool #

Show t => Show (WithModel t) Source # 
Generic (WithModel t) Source # 

Associated Types

type Rep (WithModel t) :: * -> * #

Methods

from :: WithModel t -> Rep (WithModel t) x #

to :: Rep (WithModel t) x -> WithModel t #

NFData t => NFData (WithModel t) Source # 

Methods

rnf :: WithModel t -> () #

type Rep (WithModel t) Source # 
type Rep (WithModel t) = D1 (MetaData "WithModel" "Language.Haskell.Liquid.Types.Errors" "liquidhaskell-0.8.0.2-4zWDXa3VLIUKANK5k7Jte1" False) ((:+:) (C1 (MetaCons "NoModel" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 t))) (C1 (MetaCons "WithModel" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Doc)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 t)))))

Panic (unexpected failures)

type UserError = TError Doc Source #

Simple unstructured type for panic ----------------------------------------

panic :: Maybe SrcSpan -> String -> a Source #

Construct and show an Error, then crash

panicDoc :: SrcSpan -> Doc -> a Source #

Construct and show an Error, then crash

todo :: Maybe SrcSpan -> String -> a Source #

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 Source #

Construct and show an Error with an optional SrcSpan, then crash This function should be used to mark impossible-to-reach codepaths

uError :: UserError -> a Source #

Construct and show an Error, then crash

Printing Errors

ppError :: (PPrint a, Show a) => Tidy -> Doc -> TError a -> Doc Source #

ppError' :: (PPrint a, Show a) => Tidy -> Doc -> Doc -> TError a -> Doc Source #

SrcSpan Helpers

Orphan instances