--- /dev/null
+{-# LANGUAGE StandaloneDeriving #-}
+module CoreShow where
+
+-- This module derives Show instances for CoreSyn types.
+
+import qualified CoreSyn
+import qualified TypeRep
+
+import Outputable ( 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)
+
+-- 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) ++ ")"
--- Needed for the Show deriving for Core types
-{-# LANGUAGE StandaloneDeriving #-}
-
module Pretty (prettyShow) where
import qualified Data.Foldable as Foldable
import qualified List
-import qualified Var
import qualified CoreSyn
-import qualified TypeRep
import qualified Module
import qualified HscTypes
import Text.PrettyPrint.HughesPJClass
import FlattenTypes
import TranslatorTypes
import VHDLTypes
+import CoreShow
-- | A version of the default pPrintList method, which uses a custom function
-- f instead of pPrint to print elements.
where
b' = show b
expr' = show expr
-
--- 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)
-
--- 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) ++ ")"