liquidhaskell-boot-0.9.10.1.2: Liquid Types for Haskell
Safe HaskellNone
LanguageHaskell98

Language.Haskell.Liquid.Types.PrettyPrint

Description

This module contains a single function that converts a RType -> Doc without using *any* simplifications.

Synopsis

Printable RTypes

type OkRT c tv r = (TyConable c, PPrint tv, PPrint c, PPrint r, Reftable r, Reftable (RTProp c tv ()), Reftable (RTProp c tv r), Eq c, Eq tv, Hashable tv) Source #

Printers

rtypeDoc :: OkRT c tv r => Tidy -> RType c tv r -> Doc Source #

Printing Lists (TODO: move to fixpoint)

pprManyOrdered :: (PPrint a, Ord a) => Tidy -> String -> [a] -> [Doc] Source #

pprintLongList :: PPrint a => Tidy -> [a] -> Doc Source #

Printing diagnostics

printWarning :: Logger -> Warning -> IO () Source #

Printing Warnings ---------------------------------------------------------

Filtering errors

data Filter Source #

Filters match errors. They are used to ignore classes of errors they match. AnyFilter matches all errors. StringFilter matches any error whose "representation" contains the given String. A "representation" is pretty-printed String of the error.

Instances

Instances details
Show Filter Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.PrettyPrint

Eq Filter Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.PrettyPrint

Methods

(==) :: Filter -> Filter -> Bool #

(/=) :: Filter -> Filter -> Bool #

Ord Filter Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.PrettyPrint

getFilters :: Config -> [Filter] Source #

Retrieve the Filters from the Config.

reduceFilters :: (e -> String) -> [Filter] -> e -> [Filter] Source #

Return the list of filters that matched the err , given a renderer for the err and some filters

defaultFilterReporter :: FilePath -> [Filter] -> TcRn () Source #

Report errors via GHC's API stating the given Filters did not get matched. Does nothing if the list of filters is empty.

Reporting errors in the typechecking phase

data FilterReportErrorsArgs (m :: Type -> Type) filter msg e a Source #

Used in filterReportErrorsWith'

Constructors

FilterReportErrorsArgs 

Fields

  • errorReporter :: [e] -> m ()

    Report the msgs to the monad (usually IO)

  • filterReporter :: [filter] -> m ()

    Report unmatched filters to the monad

  • failure :: m a

    Continuation for when there are unmatched filters or unmatched errors

  • continue :: m a

    Continuation for when there are no unmatched errors or filters

  • matchingFilters :: e -> [filter]

    Yields the filters that map a given error. Must only yield filters in the filters field.

  • filters :: [filter]

    List of filters which could have been matched

filterReportErrorsWith :: (Monad m, Ord filter) => FilterReportErrorsArgs m filter msg e a -> [e] -> m a Source #

Calls the continuations in FilterReportErrorsArgs depending on whethere there are unmatched errors, unmatched filters or none.

filterReportErrors :: (Show e', PPrint e') => FilePath -> TcRn a -> TcRn a -> [Filter] -> Tidy -> [TError e'] -> TcRn a Source #

Pretty-printing errors ----------------------------------------------------

Similar in spirit to reportErrors from the GHC API, but it uses our pretty-printer and shim functions under the hood. Also filters the errors according to the given Filter list.

filterReportErrors failure continue filters k will call failure if there are unexpected errors, or will call continue otherwise.

An error is expected if there is any filter that matches it.

Orphan instances

Show Predicate Source # 
Instance details

PPrint Class Source # 
Instance details

Methods

pprintTidy :: Tidy -> Class -> Doc #

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

PPrint Type Source # 
Instance details

Methods

pprintTidy :: Tidy -> Type -> Doc #

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

PPrint Name Source # 
Instance details

Methods

pprintTidy :: Tidy -> Name -> Doc #

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

PPrint SourceError Source #

A whole bunch of PPrint instances follow ----------------------------------

Instance details

PPrint Var Source # 
Instance details

Methods

pprintTidy :: Tidy -> Var -> Doc #

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

PPrint Tidy Source # 
Instance details

Methods

pprintTidy :: Tidy -> Tidy -> Doc #

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

PPrint LogicMap Source # 
Instance details

Methods

pprintTidy :: Tidy -> LogicMap -> Doc #

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

PPrint a => Show (AnnInfo a) Source # 
Instance details

Methods

showsPrec :: Int -> AnnInfo a -> ShowS #

show :: AnnInfo a -> String #

showList :: [AnnInfo a] -> ShowS #

PPrint (Bind Var) Source # 
Instance details

Methods

pprintTidy :: Tidy -> Bind Var -> Doc #

pprintPrec :: Int -> Tidy -> Bind Var -> Doc #

PPrint (Expr Var) Source # 
Instance details

Methods

pprintTidy :: Tidy -> Expr Var -> Doc #

pprintPrec :: Int -> Tidy -> Expr Var -> Doc #

PPrint a => PPrint (AnnInfo a) Source # 
Instance details

Methods

pprintTidy :: Tidy -> AnnInfo a -> Doc #

pprintPrec :: Int -> Tidy -> AnnInfo a -> Doc #

PPrint t => PPrint (Annot t) Source # 
Instance details

Methods

pprintTidy :: Tidy -> Annot t -> Doc #

pprintPrec :: Int -> Tidy -> Annot t -> Doc #

(Ord v, Fixpoint v, PPrint v) => PPrint (LMapV v) Source # 
Instance details

Methods

pprintTidy :: Tidy -> LMapV v -> Doc #

pprintPrec :: Int -> Tidy -> LMapV v -> Doc #

(PPrint (PredicateV v), Reftable (PredicateV v), PPrint r, Reftable r) => PPrint (UReftV v r) Source # 
Instance details

Methods

pprintTidy :: Tidy -> UReftV v r -> Doc #

pprintPrec :: Int -> Tidy -> UReftV v r -> Doc #

(PPrint tv, PPrint ty) => PPrint (RTAlias tv ty) Source # 
Instance details

Methods

pprintTidy :: Tidy -> RTAlias tv ty -> Doc #

pprintPrec :: Int -> Tidy -> RTAlias tv ty -> Doc #

(PPrint tv, PPrint t) => PPrint (RTEnv tv t) Source # 
Instance details

Methods

pprintTidy :: Tidy -> RTEnv tv t -> Doc #

pprintPrec :: Int -> Tidy -> RTEnv tv t -> Doc #

OkRT c tv r => PPrint (RType c tv r) Source #

Pretty Printing RefType ---------------------------------------------------

Instance details

Methods

pprintTidy :: Tidy -> RType c tv r -> Doc #

pprintPrec :: Int -> Tidy -> RType c tv r -> Doc #