[Git][ghc/ghc][wip/romes/egraphs-pmc-2] Better Outputable instance

Rodrigo Mesquita (@alt-romes) gitlab at gitlab.haskell.org
Sun Oct 29 10:33:43 UTC 2023



Rodrigo Mesquita pushed to branch wip/romes/egraphs-pmc-2 at Glasgow Haskell Compiler / GHC


Commits:
ecccae24 by Rodrigo Mesquita at 2023-10-29T10:33:37+00:00
Better Outputable instance

- - - - -


1 changed file:

- compiler/GHC/HsToCore/Pmc/Solver/Types.hs


Changes:

=====================================
compiler/GHC/HsToCore/Pmc/Solver/Types.hs
=====================================
@@ -1,4 +1,5 @@
 {-# LANGUAGE ApplicativeDo       #-}
+{-# LANGUAGE FlexibleInstances   #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE ViewPatterns        #-}
 {-# LANGUAGE MultiWayIf          #-}
@@ -79,6 +80,7 @@ import GHC.Real (Ratio(..))
 import qualified Data.Semigroup as Semi
 
 import GHC.Core.Equality
+import Data.Functor.Const
 import Data.Functor.Compose
 import Data.Equality.Graph (EGraph, ClassId)
 import Data.Equality.Graph.Lens
@@ -240,11 +242,15 @@ instance Outputable BotInfo where
 
 -- | Not user-facing.
 instance Outputable TmState where
-  -- TODO: Proper outputable instance for e-graphs?
-  ppr (TmSt state _dirty) = text (show state) -- $$ ppr dirty
--- ROMES:TODO: Don't leave this here, it's just for debug
--- instance Outputable IntSet where
---   ppr = text . show
+  ppr (TmSt state _dirty) =
+    -- $$ text (show dirty)
+    vcat $ getConst $ _iclasses (\(i,cl) -> Const [ppr i <> text ":" <+> ppr cl]) state
+
+instance Outputable (EG.EClass (Maybe VarInfo) CoreExprF) where
+  ppr cl = ppr (cl^._nodes) $$ ppr (cl^._data)
+
+instance Outputable (EG.ENode CoreExprF) where
+  ppr (EG.Node n) = text (show n)
 
 -- | Not user-facing.
 instance Outputable VarInfo where



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ecccae248111160477266bed963d68f335b31f83

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ecccae248111160477266bed963d68f335b31f83
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20231029/3e0bc376/attachment-0001.html>


More information about the ghc-commits mailing list