expose strlen from Foreign.C.String
chessai
chessai1996 at gmail.com
Thu Jan 21 03:39:19 UTC 2021
I forgot about that addition. In that case we would just need the lifted
wrapper
On Wed, Jan 20, 2021, 17:01 Viktor Dukhovni <ietf-dane at dukhovni.org> wrote:
> On Wed, Jan 20, 2021 at 09:54:30AM -0800, chessai wrote:
>
> > I've wanted the following before:
> >
> > foreign import ccall unsafe "strlen"
> > cstringLength# :: Addr# -> Int#
> >
> > cstringLength :: CString -> Int
> > cstringLength (Ptr s) = I# (cstringLength# s)
> >
> > A natural place for this seems to be Foreign.C.String.
>
> Why a new FFI call, rather than `cstringLength#` from ghc-prim: GHC.CString
> (as of GHC 9.0.1):
>
> 9.0.1-notes.rst: ``ghc-prim`` library
> 9.0.1-notes.rst: ~~~~~~~~~~~~~~~~~~~~
> 9.0.1-notes.rst:
> 9.0.1-notes.rst: - Add a known-key ``cstringLength#`` to
> ``GHC.CString`` that is eligible
> 9.0.1-notes.rst: for constant folding by a built-in rule.
>
> ghc-prim/changelog.md: - Add known-key `cstringLength#` to
> `GHC.CString`. This is just the
> ghc-prim/changelog.md: C function `strlen`, but a built-in rewrite
> rule allows GHC to
> ghc-prim/changelog.md: compute the result at compile time when the
> argument is known.
>
> CString.hs: -- | Compute the length of a NUL-terminated string. This
> address
> CString.hs: -- must refer to immutable memory. GHC includes a
> built-in rule for
> CString.hs: -- constant folding when the argument is a
> statically-known literal.
> CString.hs: -- That is, a core-to-core pass reduces the expression
> CString.hs: -- @cstringLength# "hello"#@ to the constant @5#@.
> CString.hs: cstringLength# :: Addr# -> Int#
> CString.hs: {-# INLINE[0] cstringLength# #-}
> CString.hs: cstringLength# = c_strlen
>
> Which is in turn re-exported by GHC.Exts:
>
> GHC/Exts.hs: -- * CString
> GHC/Exts.hs: unpackCString#,
> GHC/Exts.hs: unpackAppendCString#,
> GHC/Exts.hs: unpackFoldrCString#,
> GHC/Exts.hs: unpackCStringUtf8#,
> GHC/Exts.hs: unpackNBytes#,
> GHC/Exts.hs: cstringLength#,
>
> It is perhaps somewhat disappointing that the cstringLength#
> optimisations for `bytestring` (in master) aren't included in the
> `bytestring` version in 9.0.1.
>
> --
> Viktor.
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20210120/80019afa/attachment.html>
More information about the Libraries
mailing list