Ignore .swp files.
[matthijs/master-project/cλash.git] / CoreShow.hs
1 {-# LANGUAGE StandaloneDeriving,FlexibleInstances, UndecidableInstances, OverlappingInstances #-}
2 module CoreShow where
3
4 -- This module derives Show instances for CoreSyn types.
5
6 import qualified BasicTypes
7
8 import qualified CoreSyn
9 import qualified TypeRep
10 import qualified TyCon
11
12 import qualified HsTypes
13 import qualified HsExpr
14 import qualified SrcLoc
15 import qualified RdrName
16
17 import Outputable ( Outputable, OutputableBndr, showSDoc, ppr)
18
19
20 -- Derive Show for core expressions and binders, so we can see the actual
21 -- structure.
22 deriving instance (Show b) => Show (CoreSyn.Expr b)
23 deriving instance (Show b) => Show (CoreSyn.Bind b)
24 deriving instance Show TypeRep.Type
25 deriving instance (Show n, OutputableBndr n) => Show (HsTypes.HsType n)
26 deriving instance (Show x) => Show (SrcLoc.Located x)
27 deriving instance (Show x, OutputableBndr x) => Show (HsExpr.StmtLR x x)
28 deriving instance (Show x, OutputableBndr x) => Show (HsExpr.HsExpr x)
29 deriving instance Show (RdrName.RdrName)
30
31
32 -- Implement dummy shows, since deriving them will need loads of other shows
33 -- as well.
34 instance Show CoreSyn.Note where
35   show n = "<note>"
36 instance Show TypeRep.PredType where
37   show t = "_PredType:(" ++ (showSDoc $ ppr t) ++ ")"
38 instance Show TyCon.TyCon where
39   show t = "_TyCon:(" ++ (showSDoc $ ppr t) ++ ")"
40 instance Show BasicTypes.Boxity where
41   show b = "_Boxity"
42 instance Show HsTypes.HsExplicitForAll where
43   show b = "_HsExplicitForAll"
44 instance Show HsExpr.HsArrAppType where
45   show b = "_HsArrAppType"
46 instance Show (HsExpr.MatchGroup x) where
47   show b = "_HsMatchGroup"
48 instance Show (HsExpr.GroupByClause x) where
49   show b = "_GroupByClause"
50 instance Show (HsExpr.HsStmtContext x) where
51   show b = "_HsStmtContext"
52
53
54 instance (Outputable x) => Show x where
55   show x = "__" ++  (showSDoc $ ppr x) ++ "__"