[project @ 2001-01-11 17:25:56 by simonmar]
[ghc-hetmet.git] / ghc / lib / std / PrelCString.lhs
1 % -----------------------------------------------------------------------------
2 % $Id: PrelCString.lhs,v 1.1 2001/01/11 17:25:57 simonmar Exp $
3 %
4 % (c) The FFI task force, 2000
5 %
6
7 Utilities for primitive marshaling
8
9 \begin{code}
10 module PrelCString where
11
12 import Monad
13
14 import PrelMarshalArray
15 import PrelMarshalAlloc
16 import PrelException
17 import PrelPtr
18 import PrelStorable
19 import PrelCTypes
20 import PrelCTypesISO
21 import PrelInt
22 import PrelByteArr
23 import PrelPack
24 import PrelBase
25
26 #ifdef __GLASGOW_HASKELL__
27 import PrelIOBase hiding (malloc, _malloc)
28 #endif
29
30 -----------------------------------------------------------------------------
31 -- Strings
32
33 -- representation of strings in C
34 -- ------------------------------
35
36 type CString    = Ptr CChar             -- conventional NUL terminates strings
37 type CStringLen = (CString, Int)        -- strings with explicit length
38
39
40 -- exported functions
41 -- ------------------
42 --
43 -- * the following routines apply the default conversion when converting the
44 --   C-land character encoding into the Haskell-land character encoding
45 --
46 --   ** NOTE: The current implementation doesn't handle conversions yet! **
47 --
48 -- * the routines using an explicit length tolerate NUL characters in the
49 --   middle of a string
50 --
51
52 -- marshal a NUL terminated C string into a Haskell string 
53 --
54 peekCString    :: CString -> IO String
55 peekCString cp  = liftM cCharsToChars $ peekArray0 nUL cp
56
57 -- marshal a C string with explicit length into a Haskell string 
58 --
59 peekCStringLen           :: CStringLen -> IO String
60 peekCStringLen (cp, len)  = liftM cCharsToChars $ peekArray len cp
61
62 -- marshal a Haskell string into a NUL terminated C strings
63 --
64 -- * the Haskell string may *not* contain any NUL characters
65 --
66 -- * new storage is allocated for the C string and must be explicitly freed
67 --
68 newCString :: String -> IO CString
69 newCString  = newArray0 nUL . charsToCChars
70
71 -- marshal a Haskell string into a C string (ie, character array) with
72 -- explicit length information
73 --
74 -- * new storage is allocated for the C string and must be explicitly freed
75 --
76 newCStringLen     :: String -> IO CStringLen
77 newCStringLen str  = liftM (pairLength str) $ newArray (charsToCChars str)
78
79 -- marshal a Haskell string into a NUL terminated C strings using temporary
80 -- storage
81 --
82 -- * the Haskell string may *not* contain any NUL characters
83 --
84 -- * see the lifetime constraints of `MarshalAlloc.alloca'
85 --
86 withCString :: String -> (CString -> IO a) -> IO a
87 withCString  = withArray0 nUL . charsToCChars
88
89 -- marshal a Haskell string into a NUL terminated C strings using temporary
90 -- storage
91 --
92 -- * the Haskell string may *not* contain any NUL characters
93 --
94 -- * see the lifetime constraints of `MarshalAlloc.alloca'
95 --
96 withCStringLen         :: String -> (CStringLen -> IO a) -> IO a
97 withCStringLen str act  = withArray (charsToCChars str) $ act . pairLength str
98
99 -- auxilliary definitions
100 -- ----------------------
101
102 -- C's end of string character
103 --
104 nUL :: CChar
105 nUL  = castCharToCChar '\0'
106
107 -- pair a C string with the length of the given Haskell string
108 --
109 pairLength :: String -> CString -> CStringLen
110 pairLength  = flip (,) . length
111
112 -- cast [CChar] to [Char]
113 --
114 cCharsToChars :: [CChar] -> [Char]
115 cCharsToChars  = map castCCharToChar
116
117 -- cast [Char] to [CChar]
118 --
119 charsToCChars :: [Char] -> [CChar]
120 charsToCChars  = map castCharToCChar
121
122 castCCharToChar :: CChar -> Char
123 -- castCCharToChar ch = chr (fromIntegral (fromIntegral ch :: Word8))
124 -- The above produces horrible code. Word and Int modules really
125 -- should be cleaned up... Here is an ugly but fast version:
126 castCCharToChar ch = case fromIntegral (fromIntegral ch :: Int32) of
127     I# i# -> C# (chr# (word2Int# (int2Word# i# `and#` int2Word# 0xFF#)))
128
129 castCharToCChar :: Char -> CChar
130 castCharToCChar ch = fromIntegral (ord ch)
131
132
133 -- unsafe CStrings
134 -- ---------------
135
136 #if __GLASGOW_HASKELL__
137 newtype UnsafeCString = UnsafeCString (ByteArray Int)
138 withUnsafeCString s f = f (UnsafeCString (packString s))
139 #else
140 newtype UnsafeCString = UnsafeCString (Ptr CChar)
141 withUnsafeCString s f = withCString s (\p -> f (UnsafeCString p))
142 #endif
143 \end{code}