[Git][ghc/ghc][wip/T23479] Revert "JS: Replace `GHC.unpackCString#` on `GHC.CString.unpackCString#` (fixes #23479)"
Serge S. Gulin (@gulin.serge)
gitlab at gitlab.haskell.org
Sun Aug 25 17:51:11 UTC 2024
Serge S. Gulin pushed to branch wip/T23479 at Glasgow Haskell Compiler / GHC
Commits:
95f15072 by Serge S. Gulin at 2024-08-25T20:50:58+03:00
Revert "JS: Replace `GHC.unpackCString#` on `GHC.CString.unpackCString#` (fixes #23479)"
This reverts commit 734425c7ff0351c125d0fb5f6d03b5b57f8fb9a1.
- - - - -
2 changed files:
- libraries/ghc-internal/src/GHC/Internal/JS/Prim.hs
- libraries/ghc-prim/GHC/CString.hs
Changes:
=====================================
libraries/ghc-internal/src/GHC/Internal/JS/Prim.hs
=====================================
@@ -114,9 +114,9 @@ toJSString = js_toJSString . unsafeCoerce . seqList
{-# INLINE [0] toJSString #-}
{-# RULES
"GHC.JS.PRIM toJSString/literal" forall a.
- toJSString (GHC.CString.unpackCString# a) = JSVal (unsafeUnpackJSStringUtf8## a)
+ toJSString (GHC.unpackCString# a) = JSVal (unsafeUnpackJSStringUtf8## a)
"GHC.JS.PRIM toJSString/literalUtf8" forall a.
- toJSString (GHC.CString.unpackCStringUtf8# a) = JSVal (unsafeUnpackJSStringUtf8## a)
+ toJSString (GHC.unpackCStringUtf8# a) = JSVal (unsafeUnpackJSStringUtf8## a)
#-}
fromJSArray :: JSVal -> IO [JSVal]
@@ -154,9 +154,9 @@ getProp o p = js_getProp o (unsafeCoerce $ seqList p)
{-# INLINE [0] getProp #-}
{-# RULES
"GHC.JS.PRIM getProp/literal" forall o a.
- getProp o (GHC.CString.unpackCString# a) = getProp# o a
+ getProp o (GHC.unpackCString# a) = getProp# o a
"GHC.JS.PRIM getProp/literalUtf8" forall o a.
- getProp o (GHC.CString.unpackCStringUtf8# a) = getPropUtf8# o a
+ getProp o (GHC.unpackCStringUtf8# a) = getPropUtf8# o a
#-}
-- | only safe on immutable object
@@ -165,9 +165,9 @@ unsafeGetProp o p = js_unsafeGetProp o (unsafeCoerce $ seqList p)
{-# INLINE [0] unsafeGetProp #-}
{-# RULES
"GHC.JS.PRIM unsafeGetProp/literal" forall o a.
- unsafeGetProp o (GHC.CString.unpackCString# a) = unsafeGetProp# o a
+ unsafeGetProp o (GHC.unpackCString# a) = unsafeGetProp# o a
"GHC.JS.PRIM unsafeGetProp/literalUtf8" forall o a.
- unsafeGetProp o (GHC.CString.unpackCStringUtf8# a) = unsafeGetPropUtf8# o a
+ unsafeGetProp o (GHC.unpackCStringUtf8# a) = unsafeGetPropUtf8# o a
#-}
getProp' :: JSVal -> JSVal -> IO JSVal
=====================================
libraries/ghc-prim/GHC/CString.hs
=====================================
@@ -119,7 +119,7 @@ to match unpackCString#,
= build (unpackFoldrCString# a)
* stream fusion rules; e.g. in the `text` library,
- unstream (S.map safe (S.streamList (GHC.CString.unpackCString# a)))
+ unstream (S.map safe (S.streamList (GHC.unpackCString# a)))
= unpackCString# a
Moreover, we want to make it CONLIKE, so that:
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/95f15072a7120f88e2662dc06f3bdb7068404a30
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/95f15072a7120f88e2662dc06f3bdb7068404a30
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/20240825/97705a2a/attachment-0001.html>
More information about the ghc-commits
mailing list