Skip to content

Commit 74695fd

Browse files
Add a Data/CString module
For representing CStrings using MutByteArray.
1 parent 8a6cb39 commit 74695fd

File tree

2 files changed

+110
-0
lines changed

2 files changed

+110
-0
lines changed
Lines changed: 109 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,109 @@
1+
{-# LANGUAGE UnliftedFFITypes #-}
2+
3+
-- |
4+
-- Module : Streamly.Internal.Data.CString
5+
-- Copyright : (c) 2023 Composewell Technologies
6+
-- License : BSD3-3-Clause
7+
-- Maintainer : [email protected]
8+
-- Portability : GHC
9+
--
10+
-- MutByteArray representing null terminated c strings.
11+
-- All APIs in this module are unsafe and caution must be used when using them.
12+
-- Completely experimental. Everything is subject to change without notice.
13+
14+
module Streamly.Internal.Data.CString
15+
(
16+
splice
17+
, spliceCString
18+
, splicePtrN
19+
, putCString
20+
, length
21+
)
22+
23+
where
24+
25+
#ifdef DEBUG
26+
#include "assert.hs"
27+
#endif
28+
29+
import GHC.Ptr (Ptr(..), castPtr)
30+
import Foreign.C (CString, CSize(..))
31+
import GHC.Exts (MutableByteArray#, RealWorld)
32+
import GHC.Word (Word8)
33+
34+
import Streamly.Internal.Data.MutByteArray.Type hiding (length)
35+
36+
import Prelude hiding (length)
37+
38+
-- XXX Use cstringLength# from GHC.CString in ghc-prim
39+
foreign import ccall unsafe "string.h strlen" c_strlen
40+
:: MutableByteArray# RealWorld -> IO CSize
41+
42+
-- XXX Use cstringLength# from GHC.CString in ghc-prim
43+
foreign import ccall unsafe "string.h strlen" c_strlen_pinned
44+
:: CString -> IO CSize
45+
46+
{-# INLINE length #-}
47+
length :: MutByteArray -> IO Int
48+
length (MutByteArray src#) = do
49+
fmap fromIntegral $ c_strlen src#
50+
51+
-- | Join two null terminated cstrings, the null byte of the first string is
52+
-- overwritten. Does not check the destination length or source length.
53+
-- Destination must have enough space to accomodate src.
54+
--
55+
-- Returns the offset of the null byte.
56+
--
57+
-- /Unsafe/
58+
splice :: MutByteArray -> MutByteArray -> IO Int
59+
splice dst@(MutByteArray dst#) src@(MutByteArray src#) = do
60+
srcLen <- fmap fromIntegral $ c_strlen src#
61+
#ifdef DEBUG
62+
srcLen1 <- length src
63+
assertM(srcLen <= srcLen1)
64+
#endif
65+
dstLen <- fmap fromIntegral $ c_strlen dst#
66+
#ifdef DEBUG
67+
dstLen1 <- length dst
68+
assertM(dstLen <= dstLen1)
69+
assertM(dstLen + srcLen + 1 <= dstLen1)
70+
#endif
71+
unsafePutSlice src 0 dst dstLen (srcLen + 1)
72+
return $ dstLen + srcLen
73+
74+
-- | Append specified number of bytes from a Ptr to a MutByteArray CString. The
75+
-- null byte of CString is overwritten and the result is terminated with a null
76+
-- byte.
77+
{-# INLINE splicePtrN #-}
78+
splicePtrN :: MutByteArray -> Ptr Word8 -> Int -> IO Int
79+
splicePtrN dst@(MutByteArray dst#) src srcLen = do
80+
dstLen <- fmap fromIntegral $ c_strlen dst#
81+
#ifdef DEBUG
82+
dstLen1 <- length dst
83+
assertM(dstLen <= dstLen1)
84+
assertM(dstLen + srcLen + 1 <= dstLen1)
85+
#endif
86+
-- unsafePutSlice src 0 dst dstLen srcLen
87+
-- XXX unsafePutPtrN signature consistency with serialization routines
88+
-- XXX unsafePutSlice as well
89+
unsafePutPtrN src dst dstLen (srcLen + 1)
90+
return $ dstLen + srcLen
91+
92+
-- | Join a null terminated cstring MutByteByteArray with a null terminated
93+
-- cstring Ptr.
94+
{-# INLINE spliceCString #-}
95+
spliceCString :: MutByteArray -> CString -> IO Int
96+
spliceCString dst src = do
97+
srcLen <- fmap fromIntegral $ c_strlen_pinned src
98+
splicePtrN dst (castPtr src) srcLen
99+
100+
-- XXX this is CString serialization.
101+
102+
-- | @putCString dst dstOffset cstr@ writes the cstring cstr at dstOffset in
103+
-- the dst MutByteArray. The result is terminated by a null byte.
104+
{-# INLINE putCString #-}
105+
putCString :: MutByteArray -> Int -> CString -> IO Int
106+
putCString dst off src = do
107+
srcLen <- fmap fromIntegral $ c_strlen_pinned src
108+
unsafePutPtrN (castPtr src) dst off (srcLen + 1)
109+
return $ off + srcLen

core/streamly-core.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -341,6 +341,7 @@ library
341341

342342
-- streamly-core-array-types
343343
, Streamly.Internal.Data.MutByteArray
344+
, Streamly.Internal.Data.CString
344345

345346
-- streaming and parsing Haskell types to/from bytes
346347
, Streamly.Internal.Data.Binary.Parser

0 commit comments

Comments
 (0)