[Git][ghc/ghc][wip/T14030] Make fields of GHC.Internal.TH.Syntax.Bytes strict

Sebastian Graf (@sgraf812) gitlab at gitlab.haskell.org
Mon Jun 17 12:22:32 UTC 2024



Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC


Commits:
d525d829 by Sebastian Graf at 2024-06-17T14:22:26+02:00
Make fields of GHC.Internal.TH.Syntax.Bytes strict

There is no use case where this would not make sense.

- - - - -


2 changed files:

- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
- testsuite/tests/interface-stability/template-haskell-exports.stdout


Changes:

=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
=====================================
@@ -1712,9 +1712,9 @@ data Lit = CharL Char           -- ^ @\'c\'@
 -- Avoid using Bytes constructor directly as it is likely to change in the
 -- future. Use helpers such as `mkBytes` in Language.Haskell.TH.Lib instead.
 data Bytes = Bytes
-   { bytesPtr    :: ForeignPtr Word8 -- ^ Pointer to the data
-   , bytesOffset :: Word             -- ^ Offset from the pointer
-   , bytesSize   :: Word             -- ^ Number of bytes
+   { bytesPtr    :: !(ForeignPtr Word8)  -- ^ Pointer to the data
+   , bytesOffset :: {-# UNPACK #-} !Word -- ^ Offset from the pointer
+   , bytesSize   :: {-# UNPACK #-} !Word -- ^ Number of bytes
 
    -- Maybe someday:
    -- , bytesAlignement  :: Word -- ^ Alignement constraint


=====================================
testsuite/tests/interface-stability/template-haskell-exports.stdout
=====================================
@@ -1705,7 +1705,7 @@ module Language.Haskell.TH.Syntax where
   type Body :: *
   data Body = GuardedB [(Guard, Exp)] | NormalB Exp
   type Bytes :: *
-  data Bytes = Bytes {bytesPtr :: GHC.Internal.ForeignPtr.ForeignPtr GHC.Internal.Word.Word8, bytesOffset :: GHC.Types.Word, bytesSize :: GHC.Types.Word}
+  data Bytes = Bytes {bytesPtr :: !(GHC.Internal.ForeignPtr.ForeignPtr GHC.Internal.Word.Word8), bytesOffset :: {-# UNPACK #-}GHC.Types.Word, bytesSize :: {-# UNPACK #-}GHC.Types.Word}
   type Callconv :: *
   data Callconv = CCall | StdCall | CApi | Prim | JavaScript
   type CharPos :: *



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d525d829a76b4a6ecf54ef91d06c9e7b24042085
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/20240617/bdf15235/attachment-0001.html>


More information about the ghc-commits mailing list