update cabal file to upload to hackage
[matthijs/master-project/cλash.git] / cλash / CLasH / Utils / Core / CoreShow.hs
index 1db286ec6a7ff27d76826f77da891c4679333b33..ca2a7fba193094a06c30fe9a337918d6b80d1a55 100644 (file)
@@ -1,23 +1,21 @@
 {-# LANGUAGE StandaloneDeriving,FlexibleInstances, UndecidableInstances, OverlappingInstances #-}
-module CLasH.Utils.Core.CoreShow where
-
+--
 -- This module derives Show instances for CoreSyn types.
+--
+module CLasH.Utils.Core.CoreShow where
 
+-- GHC API
 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 ( 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)
@@ -38,7 +36,7 @@ deriving instance Show TyCon.SynTyConRhs
 -- 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) ++ ")"
+  show t = "_PredType:(" ++ showSDoc (ppr t) ++ ")"
 instance Show TyCon.TyCon where
   show t | TyCon.isAlgTyCon t && not (TyCon.isTupleTyCon t) =
            showtc "AlgTyCon" ""
@@ -55,7 +53,7 @@ instance Show TyCon.TyCon where
          | TyCon.isSuperKindTyCon t =
            showtc "SuperKindTyCon" ""
          | otherwise = 
-           "_Nonexistant tycon?:(" ++ (showSDoc $ ppr t) ++ ")_"
+           "_Nonexistant tycon?:(" ++ showSDoc (ppr t) ++ ")_"
       where
         showtc con extra = "(" ++ con ++ " {tyConName = " ++ name ++ extra ++ ", ...})"
         name = show (TyCon.tyConName t)
@@ -79,4 +77,4 @@ instance Show (HsExpr.GRHSs id) where
 
 
 instance (Outputable x) => Show x where
-  show x = "__" ++  (showSDoc $ ppr x) ++ "__"
+  show x = "__" ++ showSDoc (ppr x) ++ "__"