| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
Language.Haskell.TH.Ppr
Description
contains a prettyprinter for the Template Haskell datatypes
Synopsis
- nestDepth :: Int
- type Precedence = Int
- appPrec :: Precedence
- opPrec :: Precedence
- unopPrec :: Precedence
- sigPrec :: Precedence
- noPrec :: Precedence
- parensIf :: Bool -> Doc -> Doc
- pprint :: Ppr a => a -> String
- class Ppr a where
- ppr_sig :: Name -> Type -> Doc
- pprFixity :: Name -> Fixity -> Doc
- pprPatSynSig :: Name -> PatSynType -> Doc
- pprPatSynType :: PatSynType -> Doc
- pprPrefixOcc :: Name -> Doc
- isSymOcc :: Name -> Bool
- pprInfixExp :: Exp -> Doc
- pprExp :: Precedence -> Exp -> Doc
- pprFields :: [(Name, Exp)] -> Doc
- pprMaybeExp :: Precedence -> Maybe Exp -> Doc
- pprMatchPat :: Pat -> Doc
- pprGuarded :: Doc -> (Guard, Exp) -> Doc
- pprBody :: Bool -> Body -> Doc
- pprLit :: Precedence -> Lit -> Doc
- bytesToString :: [Word8] -> String
- pprString :: String -> Doc
- pprPat :: Precedence -> Pat -> Doc
- ppr_dec :: Bool -> Dec -> Doc
- ppr_deriv_strategy :: DerivStrategy -> Doc
- ppr_overlap :: Overlap -> Doc
- ppr_data :: Doc -> Cxt -> Maybe Name -> Doc -> Maybe Kind -> [Con] -> [DerivClause] -> Doc
- ppr_newtype :: Doc -> Cxt -> Maybe Name -> Doc -> Maybe Kind -> Con -> [DerivClause] -> Doc
- ppr_deriv_clause :: DerivClause -> Doc
- ppr_tySyn :: Doc -> Maybe Name -> Doc -> Type -> Doc
- ppr_tf_head :: TypeFamilyHead -> Doc
- ppr_bndrs :: Maybe [TyVarBndr] -> Doc
- commaSepApplied :: [Name] -> Doc
- pprForall :: [TyVarBndr] -> Cxt -> Doc
- pprForallVis :: [TyVarBndr] -> Cxt -> Doc
- pprForall' :: ForallVisFlag -> [TyVarBndr] -> Cxt -> Doc
- pprRecFields :: [(Name, Strict, Type)] -> Type -> Doc
- pprGadtRHS :: [(Strict, Type)] -> Type -> Doc
- pprVarBangType :: VarBangType -> Doc
- pprBangType :: BangType -> Doc
- pprVarStrictType :: (Name, Strict, Type) -> Doc
- pprStrictType :: (Strict, Type) -> Doc
- pprParendType :: Type -> Doc
- pprUInfixT :: Type -> Doc
- pprParendTypeArg :: TypeArg -> Doc
- pprTyApp :: (Type, [TypeArg]) -> Doc
- pprFunArgType :: Type -> Doc
- data ForallVisFlag
- data TypeArg
- split :: Type -> (Type, [TypeArg])
- pprTyLit :: TyLit -> Doc
- pprCxt :: Cxt -> Doc
- ppr_cxt_preds :: Cxt -> Doc
- where_clause :: [Dec] -> Doc
- showtextl :: Show a => a -> Doc
- hashParens :: Doc -> Doc
- quoteParens :: Doc -> Doc
- commaSep :: Ppr a => [a] -> Doc
- commaSepWith :: (a -> Doc) -> [a] -> Doc
- semiSep :: Ppr a => [a] -> Doc
- unboxedSumBars :: Doc -> SumAlt -> SumArity -> Doc
- bar :: Doc
Documentation
type Precedence = Int Source #
appPrec :: Precedence Source #
opPrec :: Precedence Source #
sigPrec :: Precedence Source #
noPrec :: Precedence Source #
Minimal complete definition
Instances
| Ppr Role Source # | |
| Ppr TyLit Source # | |
| Ppr InjectivityAnn Source # | |
| Defined in Language.Haskell.TH.Ppr | |
| Ppr FamilyResultSig Source # | |
| Defined in Language.Haskell.TH.Ppr | |
| Ppr TyVarBndr Source # | |
| Ppr Type Source # | |
| Ppr PatSynArgs Source # | |
| Defined in Language.Haskell.TH.Ppr | |
| Ppr PatSynDir Source # | |
| Ppr Bang Source # | |
| Ppr Con Source # | |
| Ppr DecidedStrictness Source # | |
| Defined in Language.Haskell.TH.Ppr | |
| Ppr SourceStrictness Source # | |
| Defined in Language.Haskell.TH.Ppr | |
| Ppr SourceUnpackedness Source # | |
| Defined in Language.Haskell.TH.Ppr | |
| Ppr RuleBndr Source # | |
| Ppr Phases Source # | |
| Ppr RuleMatch Source # | |
| Ppr Inline Source # | |
| Ppr Pragma Source # | |
| Ppr Foreign Source # | |
| Ppr FunDep Source # | |
| Ppr Dec Source # | |
| Ppr Range Source # | |
| Ppr Stmt Source # | |
| Ppr Exp Source # | |
| Ppr Clause Source # | |
| Ppr Match Source # | |
| Ppr Pat Source # | |
| Ppr Lit Source # | |
| Ppr ModuleInfo Source # | |
| Defined in Language.Haskell.TH.Ppr | |
| Ppr Info Source # | |
| Ppr Loc Source # | |
| Ppr Name Source # | |
| Ppr Module Source # | |
| Ppr TypeArg Source # | |
| Ppr a => Ppr [a] Source # | |
pprPatSynSig :: Name -> PatSynType -> Doc Source #
Pretty prints a pattern synonym type signature
pprPatSynType :: PatSynType -> Doc Source #
Pretty prints a pattern synonym's type; follows the usual
 conventions to print a pattern synonym type compactly, yet
 unambiguously. See the note on PatSynType and the section on
 pattern synonyms in the GHC user's guide for more information.
pprPrefixOcc :: Name -> Doc Source #
pprInfixExp :: Exp -> Doc Source #
pprMaybeExp :: Precedence -> Maybe Exp -> Doc Source #
pprMatchPat :: Pat -> Doc Source #
bytesToString :: [Word8] -> String Source #
ppr_overlap :: Overlap -> Doc Source #
ppr_newtype :: Doc -> Cxt -> Maybe Name -> Doc -> Maybe Kind -> Con -> [DerivClause] -> Doc Source #
ppr_deriv_clause :: DerivClause -> Doc Source #
ppr_tf_head :: TypeFamilyHead -> Doc Source #
commaSepApplied :: [Name] -> Doc Source #
pprForall' :: ForallVisFlag -> [TyVarBndr] -> Cxt -> Doc Source #
pprVarBangType :: VarBangType -> Doc Source #
pprBangType :: BangType -> Doc Source #
pprVarStrictType :: (Name, Strict, Type) -> Doc Source #
Deprecated: As of template-haskell-2.11.0.0, VarStrictType has been replaced by VarBangType. Please use pprVarBangType instead.
pprStrictType :: (Strict, Type) -> Doc Source #
Deprecated: As of template-haskell-2.11.0.0, StrictType has been replaced by BangType. Please use pprBangType instead.
pprParendType :: Type -> Doc Source #
pprUInfixT :: Type -> Doc Source #
pprParendTypeArg :: TypeArg -> Doc Source #
pprFunArgType :: Type -> Doc Source #
data ForallVisFlag Source #
Constructors
| ForallVis | |
| ForallInvis | 
Instances
| Show ForallVisFlag Source # | |
| Defined in Language.Haskell.TH.Ppr Methods showsPrec :: Int -> ForallVisFlag -> ShowS # show :: ForallVisFlag -> String # showList :: [ForallVisFlag] -> ShowS # | |
ppr_cxt_preds :: Cxt -> Doc Source #
where_clause :: [Dec] -> Doc Source #
hashParens :: Doc -> Doc Source #
quoteParens :: Doc -> Doc Source #
commaSepWith :: (a -> Doc) -> [a] -> Doc Source #