1 {-# LANGUAGE StandaloneDeriving,FlexibleInstances, UndecidableInstances, OverlappingInstances #-}
4 -- This module derives Show instances for CoreSyn types.
6 import qualified BasicTypes
8 import qualified CoreSyn
9 import qualified TypeRep
10 import qualified TyCon
12 import qualified HsTypes
13 import qualified HsExpr
14 import qualified HsBinds
15 import qualified SrcLoc
16 import qualified RdrName
18 import Outputable ( Outputable, OutputableBndr, showSDoc, ppr)
21 -- Derive Show for core expressions and binders, so we can see the actual
23 deriving instance (Show b) => Show (CoreSyn.Expr b)
24 deriving instance (Show b) => Show (CoreSyn.Bind b)
25 deriving instance Show TypeRep.Type
26 deriving instance (Show n, OutputableBndr n) => Show (HsTypes.HsType n)
27 deriving instance (Show x) => Show (SrcLoc.Located x)
28 deriving instance (Show x, OutputableBndr x) => Show (HsExpr.StmtLR x x)
29 deriving instance (Show x, OutputableBndr x) => Show (HsExpr.HsExpr x)
30 deriving instance Show (RdrName.RdrName)
31 deriving instance (Show idL, Show idR, OutputableBndr idL, OutputableBndr idR) => Show (HsBinds.HsBindLR idL idR)
32 deriving instance Show CoreSyn.Note
35 -- Implement dummy shows, since deriving them will need loads of other shows
37 instance Show TypeRep.PredType where
38 show t = "_PredType:(" ++ (showSDoc $ ppr t) ++ ")"
39 instance Show TyCon.TyCon where
40 show t = "_TyCon:(" ++ (showSDoc $ ppr t) ++ ")"
41 instance Show BasicTypes.Boxity where
43 instance Show HsTypes.HsExplicitForAll where
44 show b = "_HsExplicitForAll"
45 instance Show HsExpr.HsArrAppType where
46 show b = "_HsArrAppType"
47 instance Show (HsExpr.MatchGroup x) where
48 show b = "_HsMatchGroup"
49 instance Show (HsExpr.GroupByClause x) where
50 show b = "_GroupByClause"
51 instance Show (HsExpr.HsStmtContext x) where
52 show b = "_HsStmtContext"
53 instance Show (HsBinds.Prag) where
55 instance Show (HsExpr.GRHSs id) where
59 instance (Outputable x) => Show x where
60 show x = "__" ++ (showSDoc $ ppr x) ++ "__"