Use data-accessor-transformers package to remove deprecation warnings
[matthijs/master-project/cλash.git] / cλash / CLasH / Utils / Core / CoreShow.hs
index 09abed667003cdcbca4493245ed7f3ba9ae81019..1db286ec6a7ff27d76826f77da891c4679333b33 100644 (file)
@@ -1,5 +1,5 @@
 {-# LANGUAGE StandaloneDeriving,FlexibleInstances, UndecidableInstances, OverlappingInstances #-}
-module CoreShow where
+module CLasH.Utils.Core.CoreShow where
 
 -- This module derives Show instances for CoreSyn types.
 
@@ -27,10 +27,12 @@ deriving instance (Show n, OutputableBndr n) => Show (HsTypes.HsType n)
 deriving instance (Show n, OutputableBndr n) => Show (HsTypes.ConDeclField 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.HsTupArg 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
+deriving instance Show TyCon.SynTyConRhs
 
 
 -- Implement dummy shows, since deriving them will need loads of other shows
@@ -38,7 +40,26 @@ deriving instance Show CoreSyn.Note
 instance Show TypeRep.PredType where
   show t = "_PredType:(" ++ (showSDoc $ ppr t) ++ ")"
 instance Show TyCon.TyCon where
-  show t = "_TyCon:(" ++ (showSDoc $ ppr t) ++ ")"
+  show t | TyCon.isAlgTyCon t && not (TyCon.isTupleTyCon t) =
+           showtc "AlgTyCon" ""
+         | TyCon.isCoercionTyCon t =
+           showtc "CoercionTyCon" ""
+         | TyCon.isSynTyCon t =
+           showtc "SynTyCon" (", synTcRhs = " ++ synrhs)
+         | TyCon.isTupleTyCon t =
+           showtc "TupleTyCon" ""
+         | TyCon.isFunTyCon t =
+           showtc "FunTyCon" ""
+         | TyCon.isPrimTyCon t =
+           showtc "PrimTyCon" ""
+         | TyCon.isSuperKindTyCon t =
+           showtc "SuperKindTyCon" ""
+         | otherwise = 
+           "_Nonexistant tycon?:(" ++ (showSDoc $ ppr t) ++ ")_"
+      where
+        showtc con extra = "(" ++ con ++ " {tyConName = " ++ name ++ extra ++ ", ...})"
+        name = show (TyCon.tyConName t)
+        synrhs = show (TyCon.synTyConRhs t)
 instance Show BasicTypes.Boxity where
   show b = "_Boxity"
 instance Show HsTypes.HsExplicitForAll where