[Git][ghc/ghc][wip/kirchner/ast] AST: move negateOverLitVal into GHC.Hs.Lit

Fabian Kirchner (@kirchner) gitlab at gitlab.haskell.org
Sat Jun 8 14:53:52 UTC 2024



Fabian Kirchner pushed to branch wip/kirchner/ast at Glasgow Haskell Compiler / GHC


Commits:
f64a7cfb by Fabian Kirchner at 2024-06-08T16:52:33+02:00
AST: move negateOverLitVal into GHC.Hs.Lit

The function negateOverLitVal is not used within Language.Haskell and
therefore can be moved to the respective module inside GHC.Hs.

- - - - -


2 changed files:

- compiler/GHC/Hs/Lit.hs
- compiler/Language/Haskell/Syntax/Lit.hs


Changes:

=====================================
compiler/GHC/Hs/Lit.hs
=====================================
@@ -30,6 +30,7 @@ import GHC.Core.Ppr ( {- instance OutputableBndr TyVar -} )
 import GHC.Types.SourceText
 import GHC.Core.Type
 import GHC.Utils.Outputable
+import GHC.Utils.Panic (panic)
 import GHC.Hs.Extension
 import Language.Haskell.Syntax.Expr ( HsExpr )
 import Language.Haskell.Syntax.Extension
@@ -248,3 +249,7 @@ pmPprHsLit (HsRat _ f _)      = ppr f
 pmPprHsLit (HsFloatPrim _ f)  = ppr f
 pmPprHsLit (HsDoublePrim _ d) = ppr d
 
+negateOverLitVal :: OverLitVal -> OverLitVal
+negateOverLitVal (HsIntegral i) = HsIntegral (negateIntegralLit i)
+negateOverLitVal (HsFractional f) = HsFractional (negateFractionalLit f)
+negateOverLitVal _ = panic "negateOverLitVal: argument is not a number"


=====================================
compiler/Language/Haskell/Syntax/Lit.hs
=====================================
@@ -21,7 +21,7 @@ module Language.Haskell.Syntax.Lit where
 import Language.Haskell.Syntax.Extension
 
 import GHC.Utils.Panic (panic)
-import GHC.Types.SourceText (IntegralLit, FractionalLit, SourceText, negateIntegralLit, negateFractionalLit)
+import GHC.Types.SourceText (IntegralLit, FractionalLit, SourceText)
 import GHC.Core.Type (Type)
 
 import GHC.Data.FastString (FastString, lexicalCompareFS)
@@ -128,11 +128,6 @@ data OverLitVal
   | HsIsString   !SourceText !FastString -- ^ String-looking literals
   deriving Data
 
-negateOverLitVal :: OverLitVal -> OverLitVal
-negateOverLitVal (HsIntegral i) = HsIntegral (negateIntegralLit i)
-negateOverLitVal (HsFractional f) = HsFractional (negateFractionalLit f)
-negateOverLitVal _ = panic "negateOverLitVal: argument is not a number"
-
 -- Comparison operations are needed when grouping literals
 -- for compiling pattern-matching (module GHC.HsToCore.Match.Literal)
 instance (Eq (XXOverLit p)) => Eq (HsOverLit p) where



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f64a7cfbc933834e2e1c5d795da41b0bde5514ca
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/20240608/28f34ea4/attachment-0001.html>


More information about the ghc-commits mailing list