Add Haskell types for C types useconds_t and suseconds_t, which are respectively...
[ghc-base.git] / Foreign / C / Types.hs
1 {-# LANGUAGE CPP
2            , NoImplicitPrelude
3            , MagicHash
4            , GeneralizedNewtypeDeriving
5   #-}
6 {-# OPTIONS_GHC -fno-warn-unused-binds #-}
7 #ifdef __GLASGOW_HASKELL__
8 {-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
9 #endif
10 -- XXX -fno-warn-unused-binds stops us warning about unused constructors,
11 -- but really we should just remove them if we don't want them
12
13 -----------------------------------------------------------------------------
14 -- |
15 -- Module      :  Foreign.C.Types
16 -- Copyright   :  (c) The FFI task force 2001
17 -- License     :  BSD-style (see the file libraries/base/LICENSE)
18 -- 
19 -- Maintainer  :  ffi@haskell.org
20 -- Stability   :  provisional
21 -- Portability :  portable
22 --
23 -- Mapping of C types to corresponding Haskell types.
24 --
25 -----------------------------------------------------------------------------
26
27 module Foreign.C.Types
28         ( -- * Representations of C types
29 #ifndef __NHC__
30           -- $ctypes
31
32           -- ** Integral types
33           -- | These types are are represented as @newtype@s of
34           -- types in "Data.Int" and "Data.Word", and are instances of
35           -- 'Prelude.Eq', 'Prelude.Ord', 'Prelude.Num', 'Prelude.Read',
36           -- 'Prelude.Show', 'Prelude.Enum', 'Typeable', 'Storable',
37           -- 'Prelude.Bounded', 'Prelude.Real', 'Prelude.Integral' and
38           -- 'Bits'.
39           CChar,  CSChar,  CUChar
40         , CShort, CUShort, CInt,   CUInt
41         , CLong,  CULong
42         , CPtrdiff, CSize, CWchar, CSigAtomic
43         , CLLong, CULLong
44         , CIntPtr, CUIntPtr
45         , CIntMax, CUIntMax
46
47           -- ** Numeric types
48           -- | These types are are represented as @newtype@s of basic
49           -- foreign types, and are instances of
50           -- 'Prelude.Eq', 'Prelude.Ord', 'Prelude.Num', 'Prelude.Read',
51           -- 'Prelude.Show', 'Prelude.Enum', 'Typeable' and 'Storable'.
52         , CClock,   CTime, CUSeconds, CSUSeconds
53
54         -- extracted from CTime, because we don't want this comment in
55         -- the Haskell 2010 report:
56
57         -- | To convert 'CTime' to 'Data.Time.UTCTime', use the following formula:
58         --
59         -- >  posixSecondsToUTCTime (realToFrac :: POSIXTime)
60         --
61
62           -- ** Floating types
63           -- | These types are are represented as @newtype@s of
64           -- 'Prelude.Float' and 'Prelude.Double', and are instances of
65           -- 'Prelude.Eq', 'Prelude.Ord', 'Prelude.Num', 'Prelude.Read',
66           -- 'Prelude.Show', 'Prelude.Enum', 'Typeable', 'Storable',
67           -- 'Prelude.Real', 'Prelude.Fractional', 'Prelude.Floating',
68           -- 'Prelude.RealFrac' and 'Prelude.RealFloat'.
69         , CFloat,  CDouble
70 -- GHC doesn't support CLDouble yet
71 #ifndef __GLASGOW_HASKELL__
72         , CLDouble
73 #endif
74 #else
75           -- Exported non-abstractly in nhc98 to fix an interface file problem.
76           CChar(..),    CSChar(..),  CUChar(..)
77         , CShort(..),   CUShort(..), CInt(..),   CUInt(..)
78         , CLong(..),    CULong(..)
79         , CPtrdiff(..), CSize(..),   CWchar(..), CSigAtomic(..)
80         , CLLong(..),   CULLong(..)
81         , CClock(..),   CTime(..),   CUSeconds(..), CSUSeconds(..)
82         , CFloat(..),   CDouble(..), CLDouble(..)
83         , CIntPtr(..), CUIntPtr(..), CIntMax(..), CUIntMax(..)
84 #endif
85           -- ** Other types
86
87           -- Instances of: Eq and Storable
88         , CFile,        CFpos,     CJmpBuf
89         ) where
90
91 #ifndef __NHC__
92
93 import Foreign.Storable
94 import Data.Bits        ( Bits(..) )
95 import Data.Int         ( Int8,  Int16,  Int32,  Int64  )
96 import Data.Word        ( Word8, Word16, Word32, Word64 )
97 import {-# SOURCE #-} Data.Typeable
98
99 #ifdef __GLASGOW_HASKELL__
100 import GHC.Base
101 import GHC.Float
102 import GHC.Enum
103 import GHC.Real
104 import GHC.Show
105 import GHC.Read
106 import GHC.Num
107 #else
108 import Control.Monad    ( liftM )
109 #endif
110
111 #ifdef __HUGS__
112 import Hugs.Ptr         ( castPtr )
113 #endif
114
115 #include "HsBaseConfig.h"
116 #include "CTypes.h"
117
118 -- | Haskell type representing the C @char@ type.
119 INTEGRAL_TYPE(CChar,tyConCChar,"CChar",HTYPE_CHAR)
120 -- | Haskell type representing the C @signed char@ type.
121 INTEGRAL_TYPE(CSChar,tyConCSChar,"CSChar",HTYPE_SIGNED_CHAR)
122 -- | Haskell type representing the C @unsigned char@ type.
123 INTEGRAL_TYPE(CUChar,tyConCUChar,"CUChar",HTYPE_UNSIGNED_CHAR)
124
125 -- | Haskell type representing the C @short@ type.
126 INTEGRAL_TYPE(CShort,tyConCShort,"CShort",HTYPE_SHORT)
127 -- | Haskell type representing the C @unsigned short@ type.
128 INTEGRAL_TYPE(CUShort,tyConCUShort,"CUShort",HTYPE_UNSIGNED_SHORT)
129
130 -- | Haskell type representing the C @int@ type.
131 INTEGRAL_TYPE(CInt,tyConCInt,"CInt",HTYPE_INT)
132 -- | Haskell type representing the C @unsigned int@ type.
133 INTEGRAL_TYPE(CUInt,tyConCUInt,"CUInt",HTYPE_UNSIGNED_INT)
134
135 -- | Haskell type representing the C @long@ type.
136 INTEGRAL_TYPE(CLong,tyConCLong,"CLong",HTYPE_LONG)
137 -- | Haskell type representing the C @unsigned long@ type.
138 INTEGRAL_TYPE(CULong,tyConCULong,"CULong",HTYPE_UNSIGNED_LONG)
139
140 -- | Haskell type representing the C @long long@ type.
141 INTEGRAL_TYPE(CLLong,tyConCLLong,"CLLong",HTYPE_LONG_LONG)
142 -- | Haskell type representing the C @unsigned long long@ type.
143 INTEGRAL_TYPE(CULLong,tyConCULLong,"CULLong",HTYPE_UNSIGNED_LONG_LONG)
144
145 {-# RULES
146 "fromIntegral/a->CChar"   fromIntegral = \x -> CChar   (fromIntegral x)
147 "fromIntegral/a->CSChar"  fromIntegral = \x -> CSChar  (fromIntegral x)
148 "fromIntegral/a->CUChar"  fromIntegral = \x -> CUChar  (fromIntegral x)
149 "fromIntegral/a->CShort"  fromIntegral = \x -> CShort  (fromIntegral x)
150 "fromIntegral/a->CUShort" fromIntegral = \x -> CUShort (fromIntegral x)
151 "fromIntegral/a->CInt"    fromIntegral = \x -> CInt    (fromIntegral x)
152 "fromIntegral/a->CUInt"   fromIntegral = \x -> CUInt   (fromIntegral x)
153 "fromIntegral/a->CLong"   fromIntegral = \x -> CLong   (fromIntegral x)
154 "fromIntegral/a->CULong"  fromIntegral = \x -> CULong  (fromIntegral x)
155 "fromIntegral/a->CLLong"  fromIntegral = \x -> CLLong  (fromIntegral x)
156 "fromIntegral/a->CULLong" fromIntegral = \x -> CULLong (fromIntegral x)
157
158 "fromIntegral/CChar->a"   fromIntegral = \(CChar   x) -> fromIntegral x
159 "fromIntegral/CSChar->a"  fromIntegral = \(CSChar  x) -> fromIntegral x
160 "fromIntegral/CUChar->a"  fromIntegral = \(CUChar  x) -> fromIntegral x
161 "fromIntegral/CShort->a"  fromIntegral = \(CShort  x) -> fromIntegral x
162 "fromIntegral/CUShort->a" fromIntegral = \(CUShort x) -> fromIntegral x
163 "fromIntegral/CInt->a"    fromIntegral = \(CInt    x) -> fromIntegral x
164 "fromIntegral/CUInt->a"   fromIntegral = \(CUInt   x) -> fromIntegral x
165 "fromIntegral/CLong->a"   fromIntegral = \(CLong   x) -> fromIntegral x
166 "fromIntegral/CULong->a"  fromIntegral = \(CULong  x) -> fromIntegral x
167 "fromIntegral/CLLong->a"  fromIntegral = \(CLLong  x) -> fromIntegral x
168 "fromIntegral/CULLong->a" fromIntegral = \(CULLong x) -> fromIntegral x
169  #-}
170
171 -- | Haskell type representing the C @float@ type.
172 FLOATING_TYPE(CFloat,tyConCFloat,"CFloat",HTYPE_FLOAT)
173 -- | Haskell type representing the C @double@ type.
174 FLOATING_TYPE(CDouble,tyConCDouble,"CDouble",HTYPE_DOUBLE)
175 -- GHC doesn't support CLDouble yet
176 #ifndef __GLASGOW_HASKELL__
177 -- HACK: Currently no long double in the FFI, so we simply re-use double
178 -- | Haskell type representing the C @long double@ type.
179 FLOATING_TYPE(CLDouble,tyConCLDouble,"CLDouble",HTYPE_DOUBLE)
180 #endif
181
182 {-# RULES
183 "realToFrac/a->CFloat"    realToFrac = \x -> CFloat   (realToFrac x)
184 "realToFrac/a->CDouble"   realToFrac = \x -> CDouble  (realToFrac x)
185
186 "realToFrac/CFloat->a"    realToFrac = \(CFloat   x) -> realToFrac x
187 "realToFrac/CDouble->a"   realToFrac = \(CDouble  x) -> realToFrac x
188  #-}
189
190 -- GHC doesn't support CLDouble yet
191 -- "realToFrac/a->CLDouble"  realToFrac = \x -> CLDouble (realToFrac x)
192 -- "realToFrac/CLDouble->a"  realToFrac = \(CLDouble x) -> realToFrac x
193
194 -- | Haskell type representing the C @ptrdiff_t@ type.
195 INTEGRAL_TYPE(CPtrdiff,tyConCPtrdiff,"CPtrdiff",HTYPE_PTRDIFF_T)
196 -- | Haskell type representing the C @size_t@ type.
197 INTEGRAL_TYPE(CSize,tyConCSize,"CSize",HTYPE_SIZE_T)
198 -- | Haskell type representing the C @wchar_t@ type.
199 INTEGRAL_TYPE(CWchar,tyConCWchar,"CWchar",HTYPE_WCHAR_T)
200 -- | Haskell type representing the C @sig_atomic_t@ type.
201 INTEGRAL_TYPE(CSigAtomic,tyConCSigAtomic,"CSigAtomic",HTYPE_SIG_ATOMIC_T)
202
203 {-# RULES
204 "fromIntegral/a->CPtrdiff"   fromIntegral = \x -> CPtrdiff   (fromIntegral x)
205 "fromIntegral/a->CSize"      fromIntegral = \x -> CSize      (fromIntegral x)
206 "fromIntegral/a->CWchar"     fromIntegral = \x -> CWchar     (fromIntegral x)
207 "fromIntegral/a->CSigAtomic" fromIntegral = \x -> CSigAtomic (fromIntegral x)
208
209 "fromIntegral/CPtrdiff->a"   fromIntegral = \(CPtrdiff   x) -> fromIntegral x
210 "fromIntegral/CSize->a"      fromIntegral = \(CSize      x) -> fromIntegral x
211 "fromIntegral/CWchar->a"     fromIntegral = \(CWchar     x) -> fromIntegral x
212 "fromIntegral/CSigAtomic->a" fromIntegral = \(CSigAtomic x) -> fromIntegral x
213  #-}
214
215 -- | Haskell type representing the C @clock_t@ type.
216 ARITHMETIC_TYPE(CClock,tyConCClock,"CClock",HTYPE_CLOCK_T)
217 -- | Haskell type representing the C @time_t@ type.
218 --
219 ARITHMETIC_TYPE(CTime,tyConCTime,"CTime",HTYPE_TIME_T)
220 -- | Haskell type representing the C @useconds_t@ type.
221 ARITHMETIC_TYPE(CUSeconds,tyConCUSeconds,"CUSeconds",HTYPE_USECONDS_T)
222 -- | Haskell type representing the C @suseconds_t@ type.
223 ARITHMETIC_TYPE(CSUSeconds,tyConCSUSeconds,"CSUSeconds",HTYPE_SUSECONDS_T)
224
225 -- FIXME: Implement and provide instances for Eq and Storable
226 -- | Haskell type representing the C @FILE@ type.
227 data CFile = CFile
228 -- | Haskell type representing the C @fpos_t@ type.
229 data CFpos = CFpos
230 -- | Haskell type representing the C @jmp_buf@ type.
231 data CJmpBuf = CJmpBuf
232
233 INTEGRAL_TYPE(CIntPtr,tyConCIntPtr,"CIntPtr",HTYPE_INTPTR_T)
234 INTEGRAL_TYPE(CUIntPtr,tyConCUIntPtr,"CUIntPtr",HTYPE_UINTPTR_T)
235 INTEGRAL_TYPE(CIntMax,tyConCIntMax,"CIntMax",HTYPE_INTMAX_T)
236 INTEGRAL_TYPE(CUIntMax,tyConCUIntMax,"CUIntMax",HTYPE_UINTMAX_T)
237
238 {-# RULES
239 "fromIntegral/a->CIntPtr"  fromIntegral = \x -> CIntPtr  (fromIntegral x)
240 "fromIntegral/a->CUIntPtr" fromIntegral = \x -> CUIntPtr (fromIntegral x)
241 "fromIntegral/a->CIntMax"  fromIntegral = \x -> CIntMax  (fromIntegral x)
242 "fromIntegral/a->CUIntMax" fromIntegral = \x -> CUIntMax (fromIntegral x)
243  #-}
244
245 -- C99 types which are still missing include:
246 -- wint_t, wctrans_t, wctype_t
247
248 {- $ctypes
249
250 These types are needed to accurately represent C function prototypes,
251 in order to access C library interfaces in Haskell.  The Haskell system
252 is not required to represent those types exactly as C does, but the
253 following guarantees are provided concerning a Haskell type @CT@
254 representing a C type @t@:
255
256 * If a C function prototype has @t@ as an argument or result type, the
257   use of @CT@ in the corresponding position in a foreign declaration
258   permits the Haskell program to access the full range of values encoded
259   by the C type; and conversely, any Haskell value for @CT@ has a valid
260   representation in C.
261
262 * @'sizeOf' ('Prelude.undefined' :: CT)@ will yield the same value as
263   @sizeof (t)@ in C.
264
265 * @'alignment' ('Prelude.undefined' :: CT)@ matches the alignment
266   constraint enforced by the C implementation for @t@.
267
268 * The members 'peek' and 'poke' of the 'Storable' class map all values
269   of @CT@ to the corresponding value of @t@ and vice versa.
270
271 * When an instance of 'Prelude.Bounded' is defined for @CT@, the values
272   of 'Prelude.minBound' and 'Prelude.maxBound' coincide with @t_MIN@
273   and @t_MAX@ in C.
274
275 * When an instance of 'Prelude.Eq' or 'Prelude.Ord' is defined for @CT@,
276   the predicates defined by the type class implement the same relation
277   as the corresponding predicate in C on @t@.
278
279 * When an instance of 'Prelude.Num', 'Prelude.Read', 'Prelude.Integral',
280   'Prelude.Fractional', 'Prelude.Floating', 'Prelude.RealFrac', or
281   'Prelude.RealFloat' is defined for @CT@, the arithmetic operations
282   defined by the type class implement the same function as the
283   corresponding arithmetic operations (if available) in C on @t@.
284
285 * When an instance of 'Bits' is defined for @CT@, the bitwise operation
286   defined by the type class implement the same function as the
287   corresponding bitwise operation in C on @t@.
288
289 -}
290
291 #else   /* __NHC__ */
292
293 import NHC.FFI
294   ( CChar(..),    CSChar(..),  CUChar(..)
295   , CShort(..),   CUShort(..), CInt(..),   CUInt(..)
296   , CLong(..),    CULong(..),  CLLong(..), CULLong(..)
297   , CPtrdiff(..), CSize(..),   CWchar(..), CSigAtomic(..)
298   , CClock(..),   CTime(..),   CUSeconds(..), CSUSeconds(..)
299   , CFloat(..),   CDouble(..), CLDouble(..)
300   , CIntPtr(..),  CUIntPtr(..),CIntMax(..), CUIntMax(..)
301   , CFile,        CFpos,       CJmpBuf
302   , Storable(..)
303   )
304 import Data.Bits
305 import NHC.SizedTypes
306
307 #define INSTANCE_BITS(T) \
308 instance Bits T where { \
309   (T x) .&.     (T y)   = T (x .&.   y) ; \
310   (T x) .|.     (T y)   = T (x .|.   y) ; \
311   (T x) `xor`   (T y)   = T (x `xor` y) ; \
312   complement    (T x)   = T (complement x) ; \
313   shift         (T x) n = T (shift x n) ; \
314   rotate        (T x) n = T (rotate x n) ; \
315   bit                 n = T (bit n) ; \
316   setBit        (T x) n = T (setBit x n) ; \
317   clearBit      (T x) n = T (clearBit x n) ; \
318   complementBit (T x) n = T (complementBit x n) ; \
319   testBit       (T x) n = testBit x n ; \
320   bitSize       (T x)   = bitSize x ; \
321   isSigned      (T x)   = isSigned x }
322
323 INSTANCE_BITS(CChar)
324 INSTANCE_BITS(CSChar)
325 INSTANCE_BITS(CUChar)
326 INSTANCE_BITS(CShort)
327 INSTANCE_BITS(CUShort)
328 INSTANCE_BITS(CInt)
329 INSTANCE_BITS(CUInt)
330 INSTANCE_BITS(CLong)
331 INSTANCE_BITS(CULong)
332 INSTANCE_BITS(CLLong)
333 INSTANCE_BITS(CULLong)
334 INSTANCE_BITS(CPtrdiff)
335 INSTANCE_BITS(CWchar)
336 INSTANCE_BITS(CSigAtomic)
337 INSTANCE_BITS(CSize)
338 INSTANCE_BITS(CIntPtr)
339 INSTANCE_BITS(CUIntPtr)
340 INSTANCE_BITS(CIntMax)
341 INSTANCE_BITS(CUIntMax)
342
343 #endif