[Git][ghc/ghc][wip/T22010] Add comment to genSym and remove invalid TH note
Jaro Reinders (@Noughtmare)
gitlab at gitlab.haskell.org
Thu Jun 29 08:02:30 UTC 2023
Jaro Reinders pushed to branch wip/T22010 at Glasgow Haskell Compiler / GHC
Commits:
5ca4dc96 by Jaro Reinders at 2023-06-29T10:02:22+02:00
Add comment to genSym and remove invalid TH note
- - - - -
4 changed files:
- compiler/GHC/Data/Word64Map/Internal.hs
- compiler/GHC/Data/Word64Set/Internal.hs
- compiler/GHC/Types/Unique/Supply.hs
- testsuite/tests/linters/notes.stdout
Changes:
=====================================
compiler/GHC/Data/Word64Map/Internal.hs
=====================================
@@ -2,7 +2,6 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE PatternGuards #-}
#ifdef __GLASGOW_HASKELL__
--- {-# LANGUAGE DeriveLift #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
@@ -321,9 +320,6 @@ import Data.Data (Data(..), Constr, mkConstr, constrIndex, Fixity(Prefix),
import GHC.Exts (build)
import qualified GHC.Exts as GHCExts
import Text.Read
--- import Language.Haskell.TH.Syntax (Lift)
--- See Note [ Template Haskell Dependencies ]
--- import Language.Haskell.TH ()
#endif
import qualified Control.Category as Category
import Data.Word
@@ -375,9 +371,6 @@ type Mask = Word64
type Word64SetPrefix = Word64
type Word64SetBitMap = Word64
--- | @since 0.6.6
--- deriving instance Lift a => Lift (Word64Map a)
-
bitmapOf :: Word64 -> Word64SetBitMap
bitmapOf x = shiftLL 1 (fromIntegral (x .&. Word64Set.suffixBitMask))
{-# INLINE bitmapOf #-}
=====================================
compiler/GHC/Data/Word64Set/Internal.hs
=====================================
@@ -2,7 +2,6 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE PatternGuards #-}
#ifdef __GLASGOW_HASKELL__
--- {-# LANGUAGE DeriveLift #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
@@ -214,9 +213,6 @@ import Text.Read
#if __GLASGOW_HASKELL__
import qualified GHC.Exts
--- import Language.Haskell.TH.Syntax (Lift)
--- See Note [ Template Haskell Dependencies ]
--- import Language.Haskell.TH ()
#endif
import qualified Data.Foldable as Foldable
@@ -273,11 +269,6 @@ type Mask = Word64
type BitMap = Word64
type Key = Word64
--- #ifdef __GLASGOW_HASKELL__
--- | @since 0.6.6
--- deriving instance Lift Word64Set
--- #endif
-
instance Monoid Word64Set where
mempty = empty
mconcat = unions
=====================================
compiler/GHC/Types/Unique/Supply.hs
=====================================
@@ -228,6 +228,9 @@ mkSplitUniqSupply c
(# s4, MkSplitUniqSupply (tag .|. u) x y #)
}}}}
+-- If a word is not 64 bits then we would need a fetchAddWord64Addr# primitive,
+-- which does not exist. So we fall back on the C implementation in that case.
+
#if !MIN_VERSION_GLASGOW_HASKELL(9,1,0,0) || WORD_SIZE_IN_BITS != 64
foreign import ccall unsafe "genSym" genSym :: IO Word64
#else
=====================================
testsuite/tests/linters/notes.stdout
=====================================
@@ -6,8 +6,6 @@ ref compiler/GHC/Core/Opt/Simplify/Iteration.hs:4018:8: Note [Lambda-boun
ref compiler/GHC/Core/Opt/Simplify/Utils.hs:1343:37: Note [Gentle mode]
ref compiler/GHC/Core/Opt/Specialise.hs:1765:29: Note [Arity decrease]
ref compiler/GHC/Core/TyCo/Rep.hs:1565:31: Note [What prevents a constraint from floating]
-ref compiler/GHC/Data/Word64Map/Internal.hs:330:7: Note [ Template Haskell Dependencies ]
-ref compiler/GHC/Data/Word64Set/Internal.hs:226:7: Note [ Template Haskell Dependencies ]
ref compiler/GHC/Driver/DynFlags.hs:1245:49: Note [Eta-reduction in -O0]
ref compiler/GHC/Driver/Main.hs:1762:34: Note [simpleTidyPgm - mkBootModDetailsTc]
ref compiler/GHC/Hs/Expr.hs:194:63: Note [Pending Splices]
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5ca4dc960ef05856ad862f4925add25d79b056b0
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5ca4dc960ef05856ad862f4925add25d79b056b0
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/20230629/c5700819/attachment-0001.html>
More information about the ghc-commits
mailing list