[Git][ghc/ghc][master] template-haskell: Remove `addrToByteArrayName` and `addrToByteArray`

Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 386f1854 by Teo Camarasu at 2025-04-17T04:31:55-04:00 template-haskell: Remove `addrToByteArrayName` and `addrToByteArray` These were part of the implementation of the `Lift ByteArray` instance and were errornously exported because this module lacked an explicit export list. They have no usages on Hackage. Resolves #24782 - - - - - 3 changed files: - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/changelog.md - testsuite/tests/interface-stability/template-haskell-exports.stdout Changes: ===================================== libraries/template-haskell/Language/Haskell/TH/Syntax.hs ===================================== @@ -1,6 +1,6 @@ {-# LANGUAGE MagicHash #-} {-# LANGUAGE TemplateHaskellQuotes #-} -{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE Safe #-} {-# LANGUAGE UnboxedTuples #-} module Language.Haskell.TH.Syntax ( @@ -190,16 +190,11 @@ module Language.Haskell.TH.Syntax ( nothingName, rightName, trueName, - addrToByteArrayName, - addrToByteArray, ) where -import Data.Array.Byte import GHC.Boot.TH.Lift import GHC.Boot.TH.Syntax -import GHC.Exts -import GHC.ST import System.FilePath -- This module completely re-exports 'GHC.Boot.TH.Syntax', @@ -211,17 +206,3 @@ makeRelativeToProject fp | isRelative fp = do root <- getPackageRoot return (root > fp) makeRelativeToProject fp = return fp - --- The following two defintions are copied from 'Data.Byte.Array' --- in order to preserve the old export list of 'TH.Syntax'. --- They will soon be removed as part of #24782. - -addrToByteArrayName :: Name -addrToByteArrayName = 'addrToByteArray - -addrToByteArray :: Int -> Addr# -> ByteArray -addrToByteArray (I# len) addr = runST $ ST $ - \s -> case newByteArray# len s of - (# s', mb #) -> case copyAddrToByteArray# addr mb 0# len s' of - s'' -> case unsafeFreezeByteArray# mb s'' of - (# s''', ret #) -> (# s''', ByteArray ret #) ===================================== libraries/template-haskell/changelog.md ===================================== @@ -13,6 +13,8 @@ * Remove the `Language.Haskell.TH.Lib.Internal` module. This module has long been deprecated, and exposes compiler internals. Users should use `Language.Haskell.TH.Lib` instead, which exposes a stable version of this API. + + * Remove `addrToByteArrayName` and `addrToByteArray` from `Language.Haskell.TH.Syntax`. These were part of the implementation of the `Lift ByteArray` instance and were errornously exported because this module lacked an explicit export list. They have no usages on Hackage. ## 2.23.0.0 ===================================== testsuite/tests/interface-stability/template-haskell-exports.stdout ===================================== @@ -1369,7 +1369,7 @@ module Language.Haskell.TH.Quote where quoteFile :: QuasiQuoter -> QuasiQuoter module Language.Haskell.TH.Syntax where - -- Safety: Trustworthy + -- Safety: Safe type AnnLookup :: * data AnnLookup = AnnLookupModule Module | AnnLookupName Name type AnnTarget :: * @@ -1780,8 +1780,6 @@ module Language.Haskell.TH.Syntax where addModFinalizer :: Q () -> Q () addTempFile :: GHC.Internal.Base.String -> Q GHC.Internal.IO.FilePath addTopDecls :: [Dec] -> Q () - addrToByteArray :: GHC.Internal.Types.Int -> GHC.Internal.Prim.Addr# -> Data.Array.Byte.ByteArray - addrToByteArrayName :: Name badIO :: forall a. GHC.Internal.Base.String -> GHC.Internal.Types.IO a bindCode :: forall (m :: * -> *) a (r :: GHC.Internal.Types.RuntimeRep) (b :: TYPE r). GHC.Internal.Base.Monad m => m a -> (a -> Code m b) -> Code m b bindCode_ :: forall (m :: * -> *) a (r :: GHC.Internal.Types.RuntimeRep) (b :: TYPE r). GHC.Internal.Base.Monad m => m a -> Code m b -> Code m b View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/386f18548e3c66d04f648a9d34f167a0... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/386f18548e3c66d04f648a9d34f167a0... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)