1 {-# LANGUAGE CPP, KindSignatures #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types]
4 -- in module PlaceHolder
5 {-# LANGUAGE ConstraintKinds #-}
6 {-# LANGUAGE RoleAnnotations #-}
7 {-# LANGUAGE ExistentialQuantification #-}
8 {-# LANGUAGE FlexibleInstances #-}
12 import SrcLoc ( Located )
13 import Outputable ( SDoc, Outputable )
14 import {-# SOURCE #-} HsPat ( LPat )
15 import BasicTypes ( SpliceExplicitFlag(..))
16 import HsExtension ( OutputableBndrId, DataIdLR, SourceTextX, GhcPass )
17 import Data.Data hiding ( Fixity )
19 type role HsExpr nominal
20 type role HsCmd nominal
21 type role MatchGroup nominal representational
22 type role GRHSs nominal representational
23 type role HsSplice nominal
24 type role SyntaxExpr nominal
27 data HsSplice (i :: *)
28 data MatchGroup (a :: *) (body :: *)
29 data GRHSs (a :: *) (body :: *)
30 data SyntaxExpr (i :: *)
32 instance (DataIdLR p p) => Data (HsSplice p)
33 instance (DataIdLR p p) => Data (HsExpr p)
34 instance (DataIdLR p p) => Data (HsCmd p)
35 instance (Data body,DataIdLR p p) => Data (MatchGroup p body)
36 instance (Data body,DataIdLR p p) => Data (GRHSs p body)
37 instance (DataIdLR p p) => Data (SyntaxExpr p)
39 instance (SourceTextX (GhcPass p), OutputableBndrId (GhcPass p))
40 => Outputable (HsExpr (GhcPass p))
41 instance (SourceTextX (GhcPass p), OutputableBndrId (GhcPass p))
42 => Outputable (HsCmd (GhcPass p))
44 type LHsExpr a = Located (HsExpr a)
46 pprLExpr :: (SourceTextX (GhcPass p), OutputableBndrId (GhcPass p))
47 => LHsExpr (GhcPass p) -> SDoc
49 pprExpr :: (SourceTextX (GhcPass p), OutputableBndrId (GhcPass p))
50 => HsExpr (GhcPass p) -> SDoc
52 pprSplice :: (SourceTextX (GhcPass p), OutputableBndrId (GhcPass p))
53 => HsSplice (GhcPass p) -> SDoc
55 pprSpliceDecl :: (SourceTextX (GhcPass p), OutputableBndrId (GhcPass p))
56 => HsSplice (GhcPass p) -> SpliceExplicitFlag -> SDoc
58 pprPatBind :: forall bndr p body. (SourceTextX (GhcPass p),
59 SourceTextX (GhcPass bndr),
60 OutputableBndrId (GhcPass bndr),
61 OutputableBndrId (GhcPass p),
63 => LPat (GhcPass bndr) -> GRHSs (GhcPass p) body -> SDoc
65 pprFunBind :: (SourceTextX (GhcPass idR), OutputableBndrId (GhcPass idR),
67 => MatchGroup (GhcPass idR) body -> SDoc