Lines Matching refs:ppr

38 pprint x = render $ to_HPJ_Doc $ ppr x
41 ppr :: a -> Doc
43 ppr_list = vcat . map ppr
46 ppr x = ppr_list x function
50 ppr v = pprName v function
54 ppr (TyConI d) = ppr d function
55 ppr (ClassI d is) = ppr d $$ vcat (map ppr is) function
56 ppr (FamilyI d is) = ppr d $$ vcat (map ppr is) function
57 ppr (PrimTyConI name arity is_unlifted)
60 <+> text "type constructor" <+> quotes (ppr name)
62 ppr (ClassOpI v ty cls)
63 = text "Class op from" <+> ppr cls <> colon <+> ppr_sig v ty
64 ppr (DataConI v ty tc)
65 = text "Constructor from" <+> ppr tc <> colon <+> ppr_sig v ty
66 ppr (PatSynI nm ty) = pprPatSynSig nm ty function
67 ppr (TyVarI v ty)
68 = text "Type variable" <+> ppr v <+> equals <+> ppr ty
69 ppr (VarI v ty mb_d)
71 case mb_d of { Nothing -> empty; Just d -> ppr d }]
74 ppr_sig v ty = pprName' Applied v <+> dcolon <+> ppr ty
78 pprFixity v (Fixity i d) = ppr_fix d <+> int i <+> ppr v
94 | null exTys, null provs = ppr (ForallT uniTys reqs ty'')
95 | null uniTys, null reqs = noreqs <+> ppr ty'
96 | null reqs = forall uniTys <+> noreqs <+> ppr ty'
97 | otherwise = ppr ty
99 forall tvs = text "forall" <+> (hsep (map ppr tvs)) <+> text "."
100 pprPatSynType ty = ppr ty
104 ppr (Module pkg m) = text (pkgString pkg) <+> text (modString m) function
107 ppr (ModuleInfo imps) = text "Module" <+> vcat (map ppr imps) function
111 ppr = pprExp noPrec function
115 pprPrefixOcc n = parensIf (isSymOcc n) (ppr n)
130 pprInfixExp e = text "`" <> ppr e <> text "`"
154 <+> text "->" <+> ppr e
156 $ text "\\case" $$ nest nestDepth (ppr ms)
163 pprExp _ (UnboxedSumE e alt arity) = unboxedSumBars (ppr e) alt arity
166 = parensIf (i > noPrec) $ sep [text "if" <+> ppr guard,
167 nest 1 $ text "then" <+> ppr true,
168 nest 1 $ text "else" <+> ppr false]
176 $$ text " in" <+> ppr e
179 pprDecs [d] = ppr d
183 = parensIf (i > noPrec) $ text "case" <+> ppr e <+> text "of"
184 $$ nest nestDepth (ppr ms)
191 pprStms [s] = ppr s
199 pprStms [s] = ppr s
208 then text "[" <> ppr s <> text "]"
209 else text "[" <> ppr s
215 pprExp _ (ArithSeqE d) = ppr d
218 <+> dcolon <+> ppr t
219 pprExp _ (RecConE nm fs) = ppr nm <> braces (pprFields fs)
228 pprFields = sep . punctuate comma . map (\(s,e) -> ppr s <+> equals <+> ppr e)
236 ppr (BindS p e) = ppr p <+> text "<-" <+> ppr e function
237 ppr (LetS ds) = text "let" <+> (braces (semiSep ds)) function
238 ppr (NoBindS e) = ppr e function
239 ppr (ParS sss) = sep $ punctuate bar function
241 ppr (RecS ss) = text "rec" <+> (braces (semiSep ss)) function
245 ppr (Match p rhs ds) = pprMatchPat p <+> pprBody False rhs function
250 pprMatchPat p@(SigP {}) = parens (ppr p)
251 pprMatchPat p = ppr p
256 NormalG guardExpr -> bar <+> ppr guardExpr <+> eqDoc <+> ppr expr
257 PatG stmts -> bar <+> vcat (punctuate comma $ map ppr stmts) $$
258 nest nestDepth (eqDoc <+> ppr expr)
264 NormalB e -> eqDoc <+> ppr e
270 ppr = pprLit noPrec function
300 ppr = pprPat noPrec function
311 pprPat _ (UnboxedSumP p alt arity) = unboxedSumBars (ppr p) alt arity
325 pprPat i (AsP v p) = parensIf (i > noPrec) $ ppr v <> text "@"
329 = parens $ ppr nm
331 map (\(s,p) -> ppr s <+> equals <+> ppr p) fs)
333 pprPat i (SigP p t) = parensIf (i > noPrec) $ ppr p <+> dcolon <+> ppr t
338 ppr = ppr_dec True function
343 ppr_dec _ (FunD f cs) = vcat $ map (\c -> pprPrefixOcc f <+> ppr c) cs
344 ppr_dec _ (ValD p r ds) = ppr p <+> pprBody True r
347 = ppr_tySyn empty (Just t) (hsep (map ppr xs)) rhs
349 = ppr_data empty ctxt (Just t) (hsep (map ppr xs)) ksig cs decs
351 = ppr_newtype empty ctxt (Just t) (sep (map ppr xs)) ksig c decs
353 = text "class" <+> pprCxt ctxt <+> ppr c <+> hsep (map ppr xs) <+> ppr fds
356 text "instance" <+> maybe empty ppr_overlap o <+> pprCxt ctxt <+> ppr i
358 ppr_dec _ (SigD f t) = pprPrefixOcc f <+> dcolon <+> ppr t
359 ppr_dec _ (KiSigD f k) = text "type" <+> pprPrefixOcc f <+> dcolon <+> ppr k
360 ppr_dec _ (ForeignD f) = ppr f
362 ppr_dec _ (PragmaD p) = ppr p
364 = text "data" <+> maybeFamily <+> ppr tc <+> hsep (map ppr tvs) <+> maybeKind
368 maybeKind | (Just k') <- kind = dcolon <+> ppr k'
372 ctxt Nothing (ppr ty) ksig cs decs
378 ctxt Nothing (ppr ty) ksig c decs
384 Nothing (ppr ty) rhs
398 = ppr_bndrs mb_bndrs <+> ppr lhs <+> text "=" <+> ppr rhs
400 = hsep [ text "type role", ppr name ] <+> hsep (map ppr roles)
406 , ppr ty ]
408 = hsep [ text "default", pprPrefixOcc n, dcolon, ppr ty ]
410 = text "pattern" <+> pprNameArgs <+> ppr dir <+> pprPatRHS
412 pprNameArgs | InfixPatSyn a1 a2 <- args = ppr a1 <+> ppr name <+> ppr a2
413 | otherwise = ppr name <+> ppr args
414 pprPatRHS | ExplBidir cls <- dir = hang (ppr pat <+> text "where")
415 nestDepth (ppr name <+> ppr cls)
416 | otherwise = ppr pat
420 = hsep [text ('?' : n), text "=", ppr e]
447 nest nestDepth (sep (pref $ map ppr cs)),
471 Just k -> dcolon <+> ppr k
479 Just n -> ppr n <+> argsDoc
482 nest 2 (char '=' <+> ppr c),
490 Just k -> dcolon <+> ppr k
509 Just n -> ppr n <+> argsDoc
511 <+> text "=" <+> ppr rhs
515 = ppr tc <+> hsep (map ppr tvs) <+> ppr res <+> maybeInj
517 maybeInj | (Just inj') <- inj = ppr inj'
521 ppr_bndrs (Just bndrs) = text "forall" <+> sep (map ppr bndrs) <> text "."
526 ppr (FunDep xs ys) = hsep (map ppr xs) <+> text "->" <+> hsep (map ppr ys) function
532 ppr NoSig = empty function
533 ppr (KindSig k) = dcolon <+> ppr k function
534 ppr (TyVarSig bndr) = text "=" <+> ppr bndr function
538 ppr (InjectivityAnn lhs rhs) =
539 bar <+> ppr lhs <+> text "->" <+> hsep (map ppr rhs)
543 ppr (ImportF callconv safety impent as typ)
548 <+> ppr as
549 <+> dcolon <+> ppr typ
550 ppr (ExportF callconv expent as typ)
554 <+> ppr as
555 <+> dcolon <+> ppr typ
559 ppr (InlineP n inline rm phases)
561 <+> ppr inline
562 <+> ppr rm
563 <+> ppr phases
564 <+> ppr n
566 ppr (SpecialiseP n ty inline phases)
568 <+> maybe empty ppr inline
569 <+> ppr phases
570 <+> sep [ ppr n <+> dcolon
571 , nest 2 $ ppr ty ]
573 ppr (SpecialiseInstP inst)
574 = text "{-# SPECIALISE instance" <+> ppr inst <+> text "#-}"
575 ppr (RuleP n ty_bndrs tm_bndrs lhs rhs phases)
576 = sep [ text "{-# RULES" <+> pprString n <+> ppr phases
578 <+> ppr lhs
579 , nest 4 $ char '=' <+> ppr rhs <+> text "#-}" ]
582 <+> fsep (map ppr bndrs)
586 <+> fsep (map ppr tm_bndrs)
588 ppr (AnnP tgt expr)
589 = text "{-# ANN" <+> target1 tgt <+> ppr expr <+> text "#-}"
591 target1 (TypeAnnotation t) = text "type" <+> ppr t
592 target1 (ValueAnnotation v) = ppr v
593 ppr (LineP line file)
595 ppr (CompleteP cls mty)
596 = text "{-# COMPLETE" <+> (fsep $ punctuate comma $ map ppr cls)
597 <+> maybe empty (\ty -> dcolon <+> ppr ty) mty
601 ppr NoInline = text "NOINLINE" function
602 ppr Inline = text "INLINE" function
603 ppr Inlinable = text "INLINABLE" function
607 ppr ConLike = text "CONLIKE" function
608 ppr FunLike = empty function
612 ppr AllPhases = empty function
613 ppr (FromPhase i) = brackets $ int i function
614 ppr (BeforePhase i) = brackets $ char '~' <> int i function
618 ppr (RuleVar n) = ppr n function
619 ppr (TypedRuleVar n ty) = parens $ ppr n <+> dcolon <+> ppr ty function
623 ppr (Clause ps rhs ds) = hsep (map (pprPat appPrec) ps) <+> pprBody True rhs function
628 ppr (NormalC c sts) = ppr c <+> sep (map pprBangType sts) function
630 ppr (RecC c vsts)
631 = ppr c <+> braces (sep (punctuate comma $ map pprVarBangType vsts))
633 ppr (InfixC st1 c st2) = pprBangType st1 function
637 ppr (ForallC ns ctxt (GadtC c sts ty))
641 ppr (ForallC ns ctxt (RecGadtC c vsts ty))
645 ppr (ForallC ns ctxt con)
646 = pprForall ns ctxt <+> ppr con
648 ppr (GadtC c sts ty)
651 ppr (RecGadtC c vsts ty)
655 ppr Unidir = text "<-" function
656 ppr ImplBidir = text "=" function
657 ppr (ExplBidir _) = text "<-" function
662 ppr (PrefixPatSyn args) = sep $ map ppr args function
663 ppr (InfixPatSyn a1 a2) = ppr a1 <+> ppr a2 function
664 ppr (RecordPatSyn sels) = braces $ sep (punctuate comma (map ppr sels)) function
681 | otherwise = text "forall" <+> hsep (map ppr tvs)
691 <+> arrow <+> ppr ty
695 = ppr ty
698 <+> arrow <+> ppr ty
703 pprVarBangType (v, bang, t) = ppr v <+> dcolon <+> pprBangType (bang, t)
717 pprBangType (bt@(Bang _ NoSourceStrictness), t) = ppr bt <+> pprParendType t
718 pprBangType (bt, t) = ppr bt <> pprParendType t
722 ppr (Bang su ss) = ppr su <+> ppr ss function
726 ppr NoSourceUnpackedness = empty function
727 ppr SourceNoUnpack = text "{-# NOUNPACK #-}" function
728 ppr SourceUnpack = text "{-# UNPACK #-}" function
732 ppr NoSourceStrictness = empty function
733 ppr SourceLazy = char '~' function
734 ppr SourceStrict = char '!' function
738 ppr DecidedLazy = empty function
739 ppr DecidedStrict = char '!' function
740 ppr DecidedUnpack = text "{-# UNPACK #-} !" function
776 pprParendType (SigT ty k) = parens (ppr ty <+> text "::" <+> ppr k)
778 pprParendType (InfixT x n y) = parens (ppr x <+> pprName' Infix n <+> ppr y)
780 pprParendType (ParensT t) = ppr t
784 pprParendType (ImplicitParamT n t)= text ('?':n) <+> text "::" <+> ppr t
786 pprParendType t@(ForallT {}) = parens (ppr t)
787 pprParendType t@(ForallVisT {}) = parens (ppr t)
788 pprParendType t@(AppT {}) = parens (ppr t)
789 pprParendType t@(AppKindT {}) = parens (ppr t)
793 pprUInfixT t = ppr t
796 ppr (ForallT tvars ctxt ty) = sep [pprForall tvars ctxt, ppr ty] function
797 ppr (ForallVisT tvars ty) = sep [pprForallVis tvars [], ppr ty] function
798 ppr ty = pprTyApp (split ty) function
802 ppr (TANormal ty) = parensIf (isStarT ty) (ppr ty) function
803 ppr (TyArg ki) = char '@' <> parensIf (isStarT ki) (ppr ki) function
823 | c == oneName = sep [pprFunArgType arg1 <+> text "%1 ->", ppr arg2]
824 | c == manyName = sep [pprFunArgType arg1 <+> text "->", ppr arg2]
826 sep [pprFunArgType arg1 <+> text "%" <> ppr argm <+> text "->", ppr arg2]
827 pprTyApp (ArrowT, [TANormal arg1, TANormal arg2]) = sep [pprFunArgType arg1 <+> text "->", ppr arg2]
829 sep [pprFunArgType arg1 <+> text "~", ppr arg2]
830 pprTyApp (ListT, [TANormal arg]) = brackets (ppr arg)
847 pprFunArgType ty@(ForallT {}) = parens (ppr ty)
848 pprFunArgType ty@(ForallVisT {}) = parens (ppr ty)
849 pprFunArgType ty@(((MulArrowT `AppT` _) `AppT` _) `AppT` _) = parens (ppr ty)
850 pprFunArgType ty@((ArrowT `AppT` _) `AppT` _) = parens (ppr ty)
851 pprFunArgType ty@(SigT _ _) = parens (ppr ty)
852 pprFunArgType ty = ppr ty
872 ppr = pprTyLit function
879 pprTyVarBndr (PlainTV nm ()) = ppr nm
880 pprTyVarBndr (KindedTV nm () k) = parens (ppr nm <+> dcolon <+> ppr k)
883 pprTyVarBndr (PlainTV nm SpecifiedSpec) = ppr nm
884 pprTyVarBndr (PlainTV nm InferredSpec) = braces (ppr nm)
885 pprTyVarBndr (KindedTV nm SpecifiedSpec k) = parens (ppr nm <+> dcolon <+> ppr k)
886 pprTyVarBndr (KindedTV nm InferredSpec k) = braces (ppr nm <+> dcolon <+> ppr k)
889 ppr bndr = pprTyVarBndr bndr function
892 ppr NominalR = text "nominal" function
893 ppr RepresentationalR = text "representational" function
894 ppr PhantomR = text "phantom" function
895 ppr InferR = text "_" function
904 ppr_cxt_preds [t@ImplicitParamT{}] = parens (ppr t)
905 ppr_cxt_preds [t@ForallT{}] = parens (ppr t)
906 ppr_cxt_preds [t] = ppr t
911 ppr = brackets . pprRange function
913 pprRange (FromR e) = ppr e <> text ".."
914 pprRange (FromThenR e1 e2) = ppr e1 <> text ","
915 <> ppr e2 <> text ".."
916 pprRange (FromToR e1 e2) = ppr e1 <> text ".." <> ppr e2
917 pprRange (FromThenToR e1 e2 e3) = ppr e1 <> text ","
918 <> ppr e2 <> text ".."
919 <> ppr e3
937 ppr (Loc { loc_module = md function
949 commaSep = commaSepWith ppr
959 semiSep = sep . punctuate semi . map ppr