[Git][ghc/ghc][wip/mauscheff/ast] AST: Moved definitions that use GHC.Utils.Panic to GHC namespace
Maurice Scheffmacher (@mauscheff)
gitlab at gitlab.haskell.org
Sun Jun 9 13:29:52 UTC 2024
Maurice Scheffmacher pushed to branch wip/mauscheff/ast at Glasgow Haskell Compiler / GHC
Commits:
4cf41715 by Mauricio at 2024-06-09T15:29:46+02:00
AST: Moved definitions that use GHC.Utils.Panic to GHC namespace
- - - - -
2 changed files:
- compiler/GHC/Hs/Lit.hs
- compiler/Language/Haskell/Syntax/Lit.hs
Changes:
=====================================
compiler/GHC/Hs/Lit.hs
=====================================
@@ -34,6 +34,7 @@ import GHC.Hs.Extension
import Language.Haskell.Syntax.Expr ( HsExpr )
import Language.Haskell.Syntax.Extension
import Language.Haskell.Syntax.Lit
+import GHC.Utils.Panic (panic)
{-
************************************************************************
@@ -248,3 +249,19 @@ 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"
+
+instance (Ord (XXOverLit p)) => Ord (HsOverLit p) where
+ compare (OverLit _ val1) (OverLit _ val2) = val1 `compare` val2
+ compare (XOverLit val1) (XOverLit val2) = val1 `compare` val2
+ compare _ _ = panic "Ord HsOverLit"
+
+-- Comparison operations are needed when grouping literals
+-- for compiling pattern-matching (module GHC.HsToCore.Match.Literal)
+instance (Eq (XXOverLit p)) => Eq (HsOverLit p) where
+ (OverLit _ val1) == (OverLit _ val2) = val1 == val2
+ (XOverLit val1) == (XOverLit val2) = val1 == val2
+ _ == _ = panic "Eq HsOverLit"
=====================================
compiler/Language/Haskell/Syntax/Lit.hs
=====================================
@@ -20,8 +20,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,29 +127,12 @@ 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
- (OverLit _ val1) == (OverLit _ val2) = val1 == val2
- (XOverLit val1) == (XOverLit val2) = val1 == val2
- _ == _ = panic "Eq HsOverLit"
-
instance Eq OverLitVal where
(HsIntegral i1) == (HsIntegral i2) = i1 == i2
(HsFractional f1) == (HsFractional f2) = f1 == f2
(HsIsString _ s1) == (HsIsString _ s2) = s1 == s2
_ == _ = False
-instance (Ord (XXOverLit p)) => Ord (HsOverLit p) where
- compare (OverLit _ val1) (OverLit _ val2) = val1 `compare` val2
- compare (XOverLit val1) (XOverLit val2) = val1 `compare` val2
- compare _ _ = panic "Ord HsOverLit"
-
instance Ord OverLitVal where
compare (HsIntegral i1) (HsIntegral i2) = i1 `compare` i2
compare (HsIntegral _) (HsFractional _) = LT
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4cf417153d99426c741195572b65849b8badee18
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4cf417153d99426c741195572b65849b8badee18
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/20240609/ded61ed3/attachment-0001.html>
More information about the ghc-commits
mailing list