[Git][ghc/ghc][wip/ttg-booleanformula] unavoidable duplication of mkOr.

Hassan Al-Awwadi (@hassan.awwadi) gitlab at gitlab.haskell.org
Mon Oct 28 12:12:29 UTC 2024



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
31f8781e by Hassan Al-Awwadi at 2024-10-28T13:12:08+01:00
unavoidable duplication of mkOr.

- - - - -


2 changed files:

- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs


Changes:

=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -222,9 +222,12 @@ data IfaceBooleanFormula
   | IfAnd [IfaceBooleanFormula]
   | IfOr [IfaceBooleanFormula]
   | IfParens IfaceBooleanFormula
+  deriving Eq
 
 -- | note that this makes unbound names, so if you actually want
 -- proper Names, you'll need to properly Rename it (lookupIfaceTop).
+-- You want proper Names for most things, except pretty printing
+-- and the like.
 fromIfaceBooleanFormula :: IfaceBooleanFormula -> BooleanFormula GhcRn
 fromIfaceBooleanFormula = go
   where


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -135,13 +135,13 @@ import GHC.Unit.Module.WholeCoreBindings
 import Data.IORef
 import Data.Foldable
 import Data.Function ( on )
+import Data.List(nub)
 import Data.List.NonEmpty ( NonEmpty )
 import qualified Data.List.NonEmpty as NE
 import GHC.Builtin.Names (ioTyConName, rOOT_MAIN)
 import GHC.Iface.Errors.Types
-import GHC.CoreToIface(toIfaceBooleanFormula)
 
-import Language.Haskell.Syntax.BooleanFormula (mkOr, BooleanFormula)
+import Language.Haskell.Syntax.BooleanFormula (BooleanFormula)
 import Language.Haskell.Syntax.BooleanFormula qualified as BF(BooleanFormula(..))
 import Language.Haskell.Syntax.Extension (NoExtField (NoExtField))
 
@@ -306,12 +306,35 @@ mergeIfaceDecl d1 d2
 
       in d1 { ifBody = (ifBody d1) {
                 ifSigs  = ops,
-                ifMinDef = toIfaceBooleanFormula . mkOr . map (noLocA . fromIfaceBooleanFormula) $ [ bf1, bf2]
+                ifMinDef = mkOr [ bf1, bf2]
                 }
             } `withRolesFrom` d2
     -- It doesn't matter; we'll check for consistency later when
     -- we merge, see 'mergeSignatures'
     | otherwise              = d1 `withRolesFrom` d2
+      where
+        -- | the reason we need to duplicate mkOr here, instead of
+        -- using BooleanFormula's mkOr and just doing the loop like:
+        -- `toIfaceBooleanFormula . mkOr . fromIfaceBooleanFormula`
+        -- is quite subtle. Say we have the following minimal pragma:
+        -- {-# MINIMAL f | g #-}. If we use fromIfaceBooleanFormula
+        -- first, we will end up doing
+        -- `nub [Var (mkUnboundName f), Var (mkUnboundName g)]`,
+        -- which might seem fine, but Name equallity is decided by
+        -- their Unique, which will be identical since mkUnboundName
+        -- just stuffs the mkUnboundKey unqiue into both.
+        -- So the result will be {-# MINIMAL f #-}, oopsie.
+        -- Duplication it is.
+        mkOr :: [IfaceBooleanFormula] -> IfaceBooleanFormula
+        mkOr = maybe (IfAnd []) (mkOr' . nub . concat) . mapM fromOr
+          where
+          -- See Note [Simplification of BooleanFormulas]
+          fromOr bf = case bf of
+            (IfOr xs)  -> Just xs
+            (IfAnd []) -> Nothing
+            _        -> Just [bf]
+          mkOr' [x] = x
+          mkOr' xs = IfOr xs
 
 -- Note [Role merging]
 -- ~~~~~~~~~~~~~~~~~~~



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/31f8781e90f6c1fa484f356f77f0ac0df19c895a
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/20241028/5170f552/attachment-0001.html>


More information about the ghc-commits mailing list