| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GhcDump.Pretty
Contents
Synopsis
- class Pretty a where
- pretty :: a -> Doc ann
 - prettyList :: [a] -> Doc ann
 
 - data TyPrec
 - data PrettyOpts = PrettyOpts {
- showUniques :: Bool
 - showIdInfo :: Bool
 - showLetTypes :: Bool
 - showUnfoldings :: Bool
 
 - (<$$>) :: Doc ann -> Doc ann -> Doc ann
 - defaultPrettyOpts :: PrettyOpts
 - pprBinder :: PrettyOpts -> Binder -> Doc ann
 - pprRational :: Rational -> Doc ann
 - pprIdInfo :: PrettyOpts -> IdInfo Binder Binder -> IdDetails -> Doc ann
 - pprUnfolding :: PrettyOpts -> Unfolding Binder Binder -> Doc ann
 - pprType :: PrettyOpts -> Type -> Doc ann
 - pprType' :: PrettyOpts -> TyPrec -> Type -> Doc ann
 - maybeParens :: Bool -> Doc ann -> Doc ann
 - pprExpr :: PrettyOpts -> Expr -> Doc ann
 - pprExpr' :: PrettyOpts -> Bool -> Expr -> Doc ann
 - pprTick :: Tick -> Doc ann
 - pprTopBinding :: PrettyOpts -> TopBinding -> Doc ann
 - pprTypeSig :: PrettyOpts -> Binder -> Doc ann
 - pprBinding :: PrettyOpts -> Binder -> Expr -> Doc ann
 - pprModule :: PrettyOpts -> Module -> Doc ann
 - comment :: Doc ann -> Doc ann
 - dcolon :: Doc ann
 - smallRArrow :: Doc ann
 - hang' :: Doc ann -> Int -> Doc ann -> Doc ann
 - ppWhen :: Bool -> Doc ann -> Doc ann
 
Documentation
Minimal complete definition
Methods
>>>pretty 1 <+> pretty "hello" <+> pretty 1.2341 hello 1.234
prettyList :: [a] -> Doc ann #
 is only used to define the prettyListinstance
 . In normal circumstances only the Pretty a => Pretty [a]
 function is used.pretty
>>>prettyList [1, 23, 456][1, 23, 456]
Instances
| Pretty Bool | 
  | 
Defined in Prettyprinter.Internal  | |
| Pretty Char | Instead of  
  | 
Defined in Prettyprinter.Internal  | |
| Pretty Double | 
  | 
Defined in Prettyprinter.Internal  | |
| Pretty Float | 
  | 
Defined in Prettyprinter.Internal  | |
| Pretty Int | 
  | 
Defined in Prettyprinter.Internal  | |
| Pretty Int8 | |
Defined in Prettyprinter.Internal  | |
| Pretty Int16 | |
Defined in Prettyprinter.Internal  | |
| Pretty Int32 | |
Defined in Prettyprinter.Internal  | |
| Pretty Int64 | |
Defined in Prettyprinter.Internal  | |
| Pretty Integer | 
  | 
Defined in Prettyprinter.Internal  | |
| Pretty Natural | |
Defined in Prettyprinter.Internal  | |
| Pretty Word | |
Defined in Prettyprinter.Internal  | |
| Pretty Word8 | |
Defined in Prettyprinter.Internal  | |
| Pretty Word16 | |
Defined in Prettyprinter.Internal  | |
| Pretty Word32 | |
Defined in Prettyprinter.Internal  | |
| Pretty Word64 | |
Defined in Prettyprinter.Internal  | |
| Pretty () | 
 The argument is not used: 
  | 
Defined in Prettyprinter.Internal  | |
| Pretty Void | Finding a good example for printing something that does not exist is hard, so here is an example of printing a list full of nothing. 
  | 
Defined in Prettyprinter.Internal  | |
| Pretty Text | (lazy   | 
Defined in Prettyprinter.Internal  | |
| Pretty Text | Automatically converts all newlines to  
 Note that   
 Manually use   | 
Defined in Prettyprinter.Internal  | |
| Pretty Unique Source # | |
Defined in GhcDump.Pretty  | |
| Pretty ExternalName Source # | |
Defined in GhcDump.Pretty  | |
| Pretty BinderId Source # | |
Defined in GhcDump.Pretty  | |
| Pretty Binder Source # | |
Defined in GhcDump.Pretty  | |
| Pretty OccInfo Source # | |
Defined in GhcDump.Pretty  | |
| Pretty IdDetails Source # | |
Defined in GhcDump.Pretty  | |
| Pretty Lit Source # | |
Defined in GhcDump.Pretty  | |
| Pretty TyCon Source # | |
Defined in GhcDump.Pretty  | |
| Pretty Type Source # | |
Defined in GhcDump.Pretty  | |
| Pretty ModuleName Source # | |
Defined in GhcDump.Pretty  | |
| Pretty Module Source # | |
Defined in GhcDump.Pretty  | |
| Pretty Expr Source # | |
Defined in GhcDump.Pretty  | |
| Pretty AltCon Source # | |
Defined in GhcDump.Pretty  | |
| Pretty TopBinding Source # | |
Defined in GhcDump.Pretty  | |
| Pretty CoreStats Source # | |
Defined in GhcDump.Pretty  | |
| Pretty a => Pretty [a] | 
  | 
Defined in Prettyprinter.Internal  | |
| Pretty a => Pretty (Maybe a) | Ignore  
 
  | 
Defined in Prettyprinter.Internal  | |
| Pretty a => Pretty (Identity a) | 
  | 
Defined in Prettyprinter.Internal  | |
| Pretty a => Pretty (NonEmpty a) | |
Defined in Prettyprinter.Internal  | |
| (Pretty a1, Pretty a2) => Pretty (a1, a2) | 
  | 
Defined in Prettyprinter.Internal  | |
| (Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3) | 
  | 
Defined in Prettyprinter.Internal  | |
| Pretty a => Pretty (Const a b) | |
Defined in Prettyprinter.Internal  | |
data PrettyOpts Source #
Constructors
| PrettyOpts | |
Fields 
  | |
pprRational :: Rational -> Doc ann Source #
pprUnfolding :: PrettyOpts -> Unfolding Binder Binder -> Doc ann Source #
pprTopBinding :: PrettyOpts -> TopBinding -> Doc ann Source #
pprTypeSig :: PrettyOpts -> Binder -> Doc ann Source #
pprBinding :: PrettyOpts -> Binder -> Expr -> Doc ann Source #
smallRArrow :: Doc ann Source #