Safe Haskell | None |
---|---|
Language | Haskell98 |
This module contains a single function that converts a RType -> Doc without using *any* simplifications.
Synopsis
- 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)
- rtypeDoc :: OkRT c tv r => Tidy -> RType c tv r -> Doc
- pprManyOrdered :: (PPrint a, Ord a) => Tidy -> String -> [a] -> [Doc]
- pprintLongList :: PPrint a => Tidy -> [a] -> Doc
- pprintSymbol :: Symbol -> Doc
- printWarning :: DynFlags -> Warning -> IO ()
- printError :: (Show e, PPrint e) => Tidy -> DynFlags -> TError e -> IO ()
- reportErrors :: (Show e, PPrint e) => Tidy -> [TError e] -> TcRn ()
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) #
Printers
Printing Lists (TODO: move to fixpoint)
pprintLongList :: PPrint a => Tidy -> [a] -> Doc #
pprintSymbol :: Symbol -> Doc #
Printing diagnostics
printWarning :: DynFlags -> Warning -> IO () #
Printing Warnings ---------------------------------------------------------
printError :: (Show e, PPrint e) => Tidy -> DynFlags -> TError e -> IO () #
Pretty-printing errors ----------------------------------------------------
Reporting errors in the typechecking phase
reportErrors :: (Show e, PPrint e) => Tidy -> [TError e] -> TcRn () #
Similar in spirit to reportErrors
from the GHC API, but it uses our pretty-printer
and shim functions under the hood.
Orphan instances
Show Predicate # | |
PPrint SourceError # | |
pprintTidy :: Tidy -> SourceError -> Doc # pprintPrec :: Int -> Tidy -> SourceError -> Doc # | |
PPrint Class # | |
pprintTidy :: Tidy -> Class -> Doc # pprintPrec :: Int -> Tidy -> Class -> Doc # | |
PPrint Type # | |
pprintTidy :: Tidy -> Type -> Doc # pprintPrec :: Int -> Tidy -> Type -> Doc # | |
PPrint Var # | |
pprintTidy :: Tidy -> Var -> Doc # pprintPrec :: Int -> Tidy -> Var -> Doc # | |
PPrint ErrMsg # | A whole bunch of PPrint instances follow ---------------------------------- |
pprintTidy :: Tidy -> ErrMsg -> Doc # pprintPrec :: Int -> Tidy -> ErrMsg -> Doc # | |
PPrint TyCon # | |
pprintTidy :: Tidy -> TyCon -> Doc # pprintPrec :: Int -> Tidy -> TyCon -> Doc # | |
PPrint Name # | |
pprintTidy :: Tidy -> Name -> Doc # pprintPrec :: Int -> Tidy -> Name -> Doc # | |
PPrint Tidy # | |
pprintTidy :: Tidy -> Tidy -> Doc # pprintPrec :: Int -> Tidy -> Tidy -> Doc # | |
PPrint LMap # | |
pprintTidy :: Tidy -> LMap -> Doc # pprintPrec :: Int -> Tidy -> LMap -> Doc # | |
PPrint LogicMap # | |
pprintTidy :: Tidy -> LogicMap -> Doc # pprintPrec :: Int -> Tidy -> LogicMap -> Doc # | |
PPrint a => Show (AnnInfo a) # | |
PPrint (Expr Var) # | |
PPrint (Bind Var) # | |
PPrint t => PPrint (Annot t) # | |
pprintTidy :: Tidy -> Annot t -> Doc # pprintPrec :: Int -> Tidy -> Annot t -> Doc # | |
PPrint a => PPrint (AnnInfo a) # | |
pprintTidy :: Tidy -> AnnInfo a -> Doc # pprintPrec :: Int -> Tidy -> AnnInfo a -> Doc # | |
(PPrint r, Reftable r) => PPrint (UReft r) # | |
pprintTidy :: Tidy -> UReft r -> Doc # pprintPrec :: Int -> Tidy -> UReft r -> Doc # | |
(PPrint tv, PPrint t) => PPrint (RTEnv tv t) # | |
pprintTidy :: Tidy -> RTEnv tv t -> Doc # pprintPrec :: Int -> Tidy -> RTEnv tv t -> Doc # | |
(PPrint tv, PPrint ty) => PPrint (RTAlias tv ty) # | |
pprintTidy :: Tidy -> RTAlias tv ty -> Doc # pprintPrec :: Int -> Tidy -> RTAlias tv ty -> Doc # | |
OkRT c tv r => PPrint (RType c tv r) # | Pretty Printing RefType --------------------------------------------------- |
pprintTidy :: Tidy -> RType c tv r -> Doc # pprintPrec :: Int -> Tidy -> RType c tv r -> Doc # |