[Git][ghc/ghc][wip/ttg-booleanformula] actualy probably like this
Rodrigo Mesquita (@alt-romes)
gitlab at gitlab.haskell.org
Mon Oct 14 15:48:14 UTC 2024
Rodrigo Mesquita pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC
Commits:
aabf3909 by Hassan Al-Awwadi at 2024-10-14T16:47:57+01:00
actualy probably like this
- - - - -
6 changed files:
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- utils/check-exact/ExactPrint.hs
Changes:
=====================================
compiler/GHC/Hs/Binds.hs
=====================================
@@ -38,7 +38,7 @@ import Language.Haskell.Syntax.Binds
import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprFunBind, pprPatBind )
import {-# SOURCE #-} GHC.Hs.Pat (pprLPat )
-import GHC.Data.BooleanFormula ( BooleanFormula, pprBooleanFormulaNormal )
+import GHC.Data.BooleanFormula ( BooleanFormula )
import GHC.Types.Tickish
import GHC.Hs.Extension
import GHC.Parser.Annotation
=====================================
compiler/GHC/Hs/Instances.hs
=====================================
@@ -34,7 +34,6 @@ import GHC.Hs.Pat
import GHC.Hs.ImpExp
import GHC.Parser.Annotation
import GHC.Data.BooleanFormula (BooleanFormula(..))
-import Language.Haskell.Syntax.Extension (Anno)
-- ---------------------------------------------------------------------
-- Data derivations from GHC.Hs-----------------------------------------
@@ -592,4 +591,4 @@ deriving instance Data XViaStrategyPs
-- ---------------------------------------------------------------------
deriving instance Data a => Data (BooleanFormula a)
----------------------------------------------------------------------
\ No newline at end of file
+---------------------------------------------------------------------
=====================================
compiler/GHC/Iface/Decl.hs
=====================================
@@ -32,23 +32,19 @@ import GHC.Core.DataCon
import GHC.Core.Type
import GHC.Core.Multiplicity
-import GHC.Hs.Extension ( GhcPass )
import GHC.Types.Id
import GHC.Types.Var.Env
import GHC.Types.Var
import GHC.Types.Name
import GHC.Types.Basic
import GHC.Types.TyThing
-import GHC.Types.SrcLoc
import GHC.Utils.Panic.Plain
import GHC.Utils.Misc
import GHC.Data.Maybe
-import GHC.Data.BooleanFormula
import Data.List ( findIndex, mapAccumL )
-import Language.Haskell.Syntax.Extension (IdP, LIdP)
{-
************************************************************************
=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -19,7 +19,7 @@ module GHC.Iface.Syntax (
IfaceInfoItem(..), IfaceRule(..), IfaceAnnotation(..), IfaceAnnTarget,
IfaceWarnings(..), IfaceWarningTxt(..), IfaceStringLiteral(..),
IfaceDefault(..), IfaceClsInst(..), IfaceFamInst(..), IfaceTickish(..),
- IfaceClassBody(..), IfaceBooleanFormula(..),
+ IfaceClassBody(..), IfaceBooleanFormula,
IfaceBang(..),
IfaceSrcBang(..), SrcUnpackedness(..), SrcStrictness(..),
IfaceAxBranch(..),
@@ -100,7 +100,6 @@ import Control.Monad
import System.IO.Unsafe
import Control.DeepSeq
import Data.Proxy
-import Data.List ( intersperse )
infixl 3 &&&
=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -126,13 +126,11 @@ import GHC.Types.Error
import GHC.Fingerprint
import Control.Monad
-import GHC.Parser.Annotation
import GHC.Driver.Env.KnotVars
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)
=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -3011,7 +3011,7 @@ instance ExactPrint (AnnDecl GhcPs) where
-- ---------------------------------------------------------------------
-instance ExactPrint (BF.BooleanFormula RdrName) where
+instance ExactPrint (BF.BooleanFormula (LocatedN RdrName)) where
getAnnotationEntry = const NoEntryVal
setAnnotationAnchor a _ _ _ = a
@@ -4697,7 +4697,7 @@ instance ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) where
(an', fs') <- markAnnList an (markAnnotated fs)
return (L an' fs')
-instance ExactPrint (LocatedL (BF.BooleanFormula RdrName)) where
+instance ExactPrint (LocatedL (BF.BooleanFormula (LocatedN RdrName))) where
getAnnotationEntry = entryFromLocatedA
setAnnotationAnchor = setAnchorAn
exact (L an bf) = do
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aabf390924b41d3c8960e31cc0388c39c9274558
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aabf390924b41d3c8960e31cc0388c39c9274558
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/20241014/37e460a0/attachment-0001.html>
More information about the ghc-commits
mailing list