[Git][ghc/ghc][master] Remove most of `GHC.Internal.Pack`

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Mon Mar 3 20:28:03 UTC 2025



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00
Remove most of `GHC.Internal.Pack`

Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was
deleted, it is no longer used except for one function by the RTS.

- - - - -


1 changed file:

- libraries/ghc-internal/src/GHC/Internal/Pack.hs


Changes:

=====================================
libraries/ghc-internal/src/GHC/Internal/Pack.hs
=====================================
@@ -12,95 +12,20 @@
 -- Stability   :  internal
 -- Portability :  non-portable (GHC Extensions)
 --
--- ⚠ Warning: Starting @base-4.18@, this module is being deprecated.
--- See https://gitlab.haskell.org/ghc/ghc/-/issues/21461 for more information.
---
---
---
--- This module provides a small set of low-level functions for packing
--- and unpacking a chunk of bytes. Used by code emitted by the compiler
--- plus the prelude libraries.
---
--- The programmer level view of packed strings is provided by a GHC
--- system library PackedString.
+-- This function is just used by `rts_mkString`
 --
 -----------------------------------------------------------------------------
 
 module GHC.Internal.Pack
        (
-        -- (**) - emitted by compiler.
-
-        packCString#,
         unpackCString,
-        unpackCString#,
-        unpackNBytes#,
-        unpackFoldrCString#,  -- (**)
-        unpackAppendCString#,  -- (**)
        )
         where
 
 import GHC.Internal.Base
-import GHC.Internal.List ( length )
-import GHC.Internal.ST
 import GHC.Internal.Ptr
 
-data ByteArray ix              = ByteArray        ix ix ByteArray#
-data MutableByteArray s ix     = MutableByteArray ix ix (MutableByteArray# s)
-
 unpackCString :: Ptr a -> [Char]
 unpackCString a@(Ptr addr)
   | a == nullPtr  = []
   | otherwise      = unpackCString# addr
-
-packCString#         :: [Char]          -> ByteArray#
-packCString# str = case (packString str) of { ByteArray _ _ bytes -> bytes }
-
-packString :: [Char] -> ByteArray Int
-packString str = runST (packStringST str)
-
-packStringST :: [Char] -> ST s (ByteArray Int)
-packStringST str =
-  let len = length str  in
-  packNBytesST len str
-
-packNBytesST :: Int -> [Char] -> ST s (ByteArray Int)
-packNBytesST (I# length#) str =
-  {-
-   allocate an array that will hold the string
-   (not forgetting the NUL byte at the end)
-  -}
- new_ps_array (length# +# 1#) >>= \ ch_array ->
-   -- fill in packed string from "str"
- fill_in ch_array 0# str   >>
-   -- freeze the puppy:
- freeze_ps_array ch_array length#
- where
-  fill_in :: MutableByteArray s Int -> Int# -> [Char] -> ST s ()
-  fill_in arr_in# idx [] =
-   write_ps_array arr_in# idx (chr# 0#) >>
-   return ()
-
-  fill_in arr_in# idx (C# c : cs) =
-   write_ps_array arr_in# idx c  >>
-   fill_in arr_in# (idx +# 1#) cs
-
--- (Very :-) ``Specialised'' versions of some CharArray things...
-
-new_ps_array    :: Int# -> ST s (MutableByteArray s Int)
-write_ps_array  :: MutableByteArray s Int -> Int# -> Char# -> ST s ()
-freeze_ps_array :: MutableByteArray s Int -> Int# -> ST s (ByteArray Int)
-
-new_ps_array size = ST $ \ s ->
-    case (newByteArray# size s)   of { (# s2#, barr# #) ->
-    (# s2#, MutableByteArray bot bot barr# #) }
-  where
-    bot = errorWithoutStackTrace "new_ps_array"
-
-write_ps_array (MutableByteArray _ _ barr#) n ch = ST $ \ s# ->
-    case writeCharArray# barr# n ch s#  of { s2#   ->
-    (# s2#, () #) }
-
--- same as unsafeFreezeByteArray
-freeze_ps_array (MutableByteArray _ _ arr#) len# = ST $ \ s# ->
-    case unsafeFreezeByteArray# arr# s# of { (# s2#, frozen# #) ->
-    (# s2#, ByteArray 0 (I# len#) frozen# #) }



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3b78e139033ab07232313888cc503712799fa76c
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/20250303/876d85bb/attachment-0001.html>


More information about the ghc-commits mailing list