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
- funPrec :: Precedence
- qualPrec :: 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 -> NamespaceSpecifier -> Doc
- pprNamespaceSpecifier :: NamespaceSpecifier -> 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
- pprClause :: Bool -> Clause -> 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 :: Bool -> Doc -> Cxt -> Maybe Name -> Doc -> Maybe Kind -> [Con] -> [DerivClause] -> Doc
- ppr_newtype :: Bool -> Doc -> Cxt -> Maybe Name -> Doc -> Maybe Kind -> Con -> [DerivClause] -> Doc
- ppr_type_data :: Bool -> Doc -> Cxt -> Maybe Name -> Doc -> Maybe Kind -> [Con] -> [DerivClause] -> Doc
- ppr_typedef :: String -> Bool -> 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 :: PprFlag flag => Maybe [TyVarBndr flag] -> Doc
- commaSepApplied :: [Name] -> Doc
- pprForall :: [TyVarBndr Specificity] -> Cxt -> Doc
- pprForallVis :: [TyVarBndr ()] -> Cxt -> Doc
- pprForall' :: PprFlag flag => ForallVisFlag -> [TyVarBndr flag] -> 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
- pprType :: Precedence -> Type -> Doc
- pprParendType :: Type -> Doc
- pprInfixT :: Precedence -> Type -> Doc
- pprParendTypeArg :: TypeArg -> Doc
- isStarT :: Type -> Bool
- pprTyApp :: Precedence -> (Type, [TypeArg]) -> Doc
- fromTANormal :: TypeArg -> Maybe Type
- pprFunArgType :: Type -> Doc
- data ForallVisFlag
- = ForallVis
- | ForallInvis
- data TypeArg
- split :: Type -> (Type, [TypeArg])
- pprTyLit :: TyLit -> Doc
- class PprFlag flag where
- pprTyVarBndr :: TyVarBndr flag -> Doc
- pprBndrVis :: BndrVis -> Doc -> Doc
- pprCxt :: Cxt -> Doc
- ppr_cxt_preds :: Precedence -> Cxt -> Doc
- where_clause :: [Dec] -> Doc
- showtextl :: Show a => a -> Doc
- hashParens :: Doc -> Doc
- quoteParens :: Doc -> Doc
- sepWith :: Doc -> (a -> Doc) -> [a] -> Doc
- commaSep :: Ppr a => [a] -> Doc
- commaSepWith :: (a -> Doc) -> [a] -> Doc
- semiSep :: Ppr a => [a] -> Doc
- semiSepWith :: (a -> Doc) -> [a] -> Doc
- unboxedSumBars :: Doc -> SumAlt -> SumArity -> Doc
- bar :: Doc
Documentation
type Precedence = Int Source #
appPrec :: Precedence Source #
opPrec :: Precedence Source #
funPrec :: Precedence Source #
sigPrec :: Precedence Source #
noPrec :: Precedence Source #
Minimal complete definition
Instances
Instances details
Instance details
Defined in Language.Haskell.TH.Ppr
Instance details
Defined in Language.Haskell.TH.Ppr
Instance details
Defined in Language.Haskell.TH.Ppr
Instance details
Defined in Language.Haskell.TH.Ppr
Instance details
Defined in Language.Haskell.TH.Ppr
Instance details
Defined in Language.Haskell.TH.Ppr
Instance details
Defined in Language.Haskell.TH.Ppr
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_typedef :: String -> Bool -> 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' :: PprFlag flag => ForallVisFlag -> [TyVarBndr flag] -> 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 #
pprParendTypeArg :: TypeArg -> Doc Source #
pprFunArgType :: Type -> Doc Source #
data ForallVisFlag Source #
Instances
Instances details
Instance details
Defined in Language.Haskell.TH.Ppr
Methods
showsPrec :: Int -> ForallVisFlag -> ShowS #
show :: ForallVisFlag -> String #
showList :: [ForallVisFlag] -> ShowS #
class PprFlag flag where Source #
Methods
pprTyVarBndr :: TyVarBndr flag -> Doc Source #
Instances
Instances details
Instance details
Defined in Language.Haskell.TH.Ppr
Instance details
Defined in Language.Haskell.TH.Ppr
Methods
pprTyVarBndr :: TyVarBndr Specificity -> Doc Source #
Instance details
Defined in Language.Haskell.TH.Ppr
Methods
pprTyVarBndr :: TyVarBndr () -> Doc Source #
ppr_cxt_preds :: Precedence -> Cxt -> Doc Source #
where_clause :: [Dec] -> Doc Source #
hashParens :: Doc -> Doc Source #
quoteParens :: Doc -> Doc Source #
commaSepWith :: (a -> Doc) -> [a] -> Doc Source #
semiSepWith :: (a -> Doc) -> [a] -> Doc Source #