Merge git://github.com/darchon/clash into cλash
[matthijs/master-project/cλash.git] / CoreShow.hs
index 522fd39cb5c7277e817d50afc355ec5e2dd92da3..75bacefe3b278f493177007e13dbb6c64209ef05 100644 (file)
@@ -1,22 +1,60 @@
-{-# LANGUAGE StandaloneDeriving #-}
+{-# LANGUAGE StandaloneDeriving,FlexibleInstances, UndecidableInstances, OverlappingInstances #-}
 module CoreShow where
 
 -- This module derives Show instances for CoreSyn types.
 
+import qualified BasicTypes
+
 import qualified CoreSyn
 import qualified TypeRep
+import qualified TyCon
+
+import qualified HsTypes
+import qualified HsExpr
+import qualified HsBinds
+import qualified SrcLoc
+import qualified RdrName
 
-import Outputable ( showSDoc, ppr)
+import Outputable ( Outputable, OutputableBndr, showSDoc, ppr)
 
 
 -- Derive Show for core expressions and binders, so we can see the actual
 -- structure.
 deriving instance (Show b) => Show (CoreSyn.Expr b)
 deriving instance (Show b) => Show (CoreSyn.Bind b)
+deriving instance Show TypeRep.Type
+deriving instance (Show n, OutputableBndr n) => Show (HsTypes.HsType n)
+deriving instance (Show x) => Show (SrcLoc.Located x)
+deriving instance (Show x, OutputableBndr x) => Show (HsExpr.StmtLR x x)
+deriving instance (Show x, OutputableBndr x) => Show (HsExpr.HsExpr x)
+deriving instance Show (RdrName.RdrName)
+deriving instance (Show idL, Show idR, OutputableBndr idL, OutputableBndr idR) => Show (HsBinds.HsBindLR idL idR)
+deriving instance Show CoreSyn.Note
+
+
+-- Implement dummy shows, since deriving them will need loads of other shows
+-- as well.
+instance Show TypeRep.PredType where
+  show t = "_PredType:(" ++ (showSDoc $ ppr t) ++ ")"
+instance Show TyCon.TyCon where
+  show t = "_TyCon:(" ++ (showSDoc $ ppr t) ++ ")"
+instance Show BasicTypes.Boxity where
+  show b = "_Boxity"
+instance Show HsTypes.HsExplicitForAll where
+  show b = "_HsExplicitForAll"
+instance Show HsExpr.HsArrAppType where
+  show b = "_HsArrAppType"
+instance Show (HsExpr.MatchGroup x) where
+  show b = "_HsMatchGroup"
+instance Show (HsExpr.GroupByClause x) where
+  show b = "_GroupByClause"
+instance Show (HsExpr.HsStmtContext x) where
+  show b = "_HsStmtContext"
+instance Show (HsBinds.Prag) where
+  show b = "_Prag"
+instance Show (HsExpr.GRHSs id) where
+  show b = "_GRHSs"
+
 
--- Implement dummy shows for Note and Type, so we can at least use show on
--- expressions.
-instance Show CoreSyn.Note where
-  show n = "<note>"
-instance Show TypeRep.Type where
-  show t = "_type:(" ++ (showSDoc $ ppr t) ++ ")"
+instance (Outputable x) => Show x where
+  show x = "__" ++  (showSDoc $ ppr x) ++ "__"