Add Haskell types for C types useconds_t and suseconds_t, which are respectively...
[ghc-base.git] / Foreign / C / Types.hs
index 625c4b3..f6bdec1 100644 (file)
@@ -1,4 +1,15 @@
-{-# OPTIONS_GHC -fno-implicit-prelude #-}
+{-# LANGUAGE CPP
+           , NoImplicitPrelude
+           , MagicHash
+           , GeneralizedNewtypeDeriving
+  #-}
+{-# OPTIONS_GHC -fno-warn-unused-binds #-}
+#ifdef __GLASGOW_HASKELL__
+{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
+#endif
+-- XXX -fno-warn-unused-binds stops us warning about unused constructors,
+-- but really we should just remove them if we don't want them
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Foreign.C.Types
 -----------------------------------------------------------------------------
 
 module Foreign.C.Types
-       ( -- * Representations of C types
+        ( -- * Representations of C types
 #ifndef __NHC__
-         -- $ctypes
-
-         -- ** Integral types
-         -- | These types are are represented as @newtype@s of
-         -- types in "Data.Int" and "Data.Word", and are instances of
-         -- 'Prelude.Eq', 'Prelude.Ord', 'Prelude.Num', 'Prelude.Read',
-         -- 'Prelude.Show', 'Prelude.Enum', 'Typeable', 'Storable',
-         -- 'Prelude.Bounded', 'Prelude.Real', 'Prelude.Integral' and
-         -- 'Bits'.
-         CChar,  CSChar,  CUChar
-       , CShort, CUShort, CInt,   CUInt
-       , CLong,  CULong
-       , CPtrdiff, CSize, CWchar, CSigAtomic
+          -- $ctypes
+
+          -- ** Integral types
+          -- | These types are are represented as @newtype@s of
+          -- types in "Data.Int" and "Data.Word", and are instances of
+          -- 'Prelude.Eq', 'Prelude.Ord', 'Prelude.Num', 'Prelude.Read',
+          -- 'Prelude.Show', 'Prelude.Enum', 'Typeable', 'Storable',
+          -- 'Prelude.Bounded', 'Prelude.Real', 'Prelude.Integral' and
+          -- 'Bits'.
+          CChar,  CSChar,  CUChar
+        , CShort, CUShort, CInt,   CUInt
+        , CLong,  CULong
+        , CPtrdiff, CSize, CWchar, CSigAtomic
         , CLLong, CULLong
-       , CIntPtr, CUIntPtr
-       , CIntMax, CUIntMax
-
-         -- ** Numeric types
-         -- | These types are are represented as @newtype@s of basic
-         -- foreign types, and are instances of
-         -- 'Prelude.Eq', 'Prelude.Ord', 'Prelude.Num', 'Prelude.Read',
-         -- 'Prelude.Show', 'Prelude.Enum', 'Typeable' and 'Storable'.
-       , CClock,   CTime
-
-         -- ** Floating types
-         -- | These types are are represented as @newtype@s of
-         -- 'Prelude.Float' and 'Prelude.Double', and are instances of
-         -- 'Prelude.Eq', 'Prelude.Ord', 'Prelude.Num', 'Prelude.Read',
-         -- 'Prelude.Show', 'Prelude.Enum', 'Typeable', 'Storable',
-         -- 'Prelude.Real', 'Prelude.Fractional', 'Prelude.Floating',
-         -- 'Prelude.RealFrac' and 'Prelude.RealFloat'.
-       , CFloat,  CDouble, CLDouble
+        , CIntPtr, CUIntPtr
+        , CIntMax, CUIntMax
+
+          -- ** Numeric types
+          -- | These types are are represented as @newtype@s of basic
+          -- foreign types, and are instances of
+          -- 'Prelude.Eq', 'Prelude.Ord', 'Prelude.Num', 'Prelude.Read',
+          -- 'Prelude.Show', 'Prelude.Enum', 'Typeable' and 'Storable'.
+        , CClock,   CTime, CUSeconds, CSUSeconds
+
+        -- extracted from CTime, because we don't want this comment in
+        -- the Haskell 2010 report:
+
+        -- | To convert 'CTime' to 'Data.Time.UTCTime', use the following formula:
+        --
+        -- >  posixSecondsToUTCTime (realToFrac :: POSIXTime)
+        --
+
+          -- ** Floating types
+          -- | These types are are represented as @newtype@s of
+          -- 'Prelude.Float' and 'Prelude.Double', and are instances of
+          -- 'Prelude.Eq', 'Prelude.Ord', 'Prelude.Num', 'Prelude.Read',
+          -- 'Prelude.Show', 'Prelude.Enum', 'Typeable', 'Storable',
+          -- 'Prelude.Real', 'Prelude.Fractional', 'Prelude.Floating',
+          -- 'Prelude.RealFrac' and 'Prelude.RealFloat'.
+        , CFloat,  CDouble
+-- GHC doesn't support CLDouble yet
+#ifndef __GLASGOW_HASKELL__
+        , CLDouble
+#endif
 #else
-         -- Exported non-abstractly in nhc98 to fix an interface file problem.
-         CChar(..),    CSChar(..),  CUChar(..)
-       , CShort(..),   CUShort(..), CInt(..),   CUInt(..)
-       , CLong(..),    CULong(..)
-       , CPtrdiff(..), CSize(..),   CWchar(..), CSigAtomic(..)
+          -- Exported non-abstractly in nhc98 to fix an interface file problem.
+          CChar(..),    CSChar(..),  CUChar(..)
+        , CShort(..),   CUShort(..), CInt(..),   CUInt(..)
+        , CLong(..),    CULong(..)
+        , CPtrdiff(..), CSize(..),   CWchar(..), CSigAtomic(..)
         , CLLong(..),   CULLong(..)
-       , CClock(..),   CTime(..)
-       , CFloat(..),   CDouble(..), CLDouble(..)
+        , CClock(..),   CTime(..),   CUSeconds(..), CSUSeconds(..)
+        , CFloat(..),   CDouble(..), CLDouble(..)
+        , CIntPtr(..), CUIntPtr(..), CIntMax(..), CUIntMax(..)
 #endif
-         -- ** Other types
+          -- ** Other types
 
           -- Instances of: Eq and Storable
-       , CFile,        CFpos,     CJmpBuf
-       ) where
+        , CFile,        CFpos,     CJmpBuf
+        ) where
 
 #ifndef __NHC__
 
 import Foreign.Storable
-import Data.Bits       ( Bits(..) )
-import Data.Int                ( Int8,  Int16,  Int32,  Int64  )
-import Data.Word       ( Word8, Word16, Word32, Word64 )
-import Data.Typeable
+import Data.Bits        ( Bits(..) )
+import Data.Int         ( Int8,  Int16,  Int32,  Int64  )
+import Data.Word        ( Word8, Word16, Word32, Word64 )
+import {-# SOURCE #-} Data.Typeable
 
 #ifdef __GLASGOW_HASKELL__
 import GHC.Base
@@ -81,8 +105,11 @@ import GHC.Show
 import GHC.Read
 import GHC.Num
 #else
-import Control.Monad
-import Foreign.Ptr
+import Control.Monad    ( liftM )
+#endif
+
+#ifdef __HUGS__
+import Hugs.Ptr         ( castPtr )
 #endif
 
 #include "HsBaseConfig.h"
@@ -145,20 +172,25 @@ INTEGRAL_TYPE(CULLong,tyConCULLong,"CULLong",HTYPE_UNSIGNED_LONG_LONG)
 FLOATING_TYPE(CFloat,tyConCFloat,"CFloat",HTYPE_FLOAT)
 -- | Haskell type representing the C @double@ type.
 FLOATING_TYPE(CDouble,tyConCDouble,"CDouble",HTYPE_DOUBLE)
+-- GHC doesn't support CLDouble yet
+#ifndef __GLASGOW_HASKELL__
 -- HACK: Currently no long double in the FFI, so we simply re-use double
 -- | Haskell type representing the C @long double@ type.
 FLOATING_TYPE(CLDouble,tyConCLDouble,"CLDouble",HTYPE_DOUBLE)
+#endif
 
 {-# RULES
 "realToFrac/a->CFloat"    realToFrac = \x -> CFloat   (realToFrac x)
 "realToFrac/a->CDouble"   realToFrac = \x -> CDouble  (realToFrac x)
-"realToFrac/a->CLDouble"  realToFrac = \x -> CLDouble (realToFrac x)
 
 "realToFrac/CFloat->a"    realToFrac = \(CFloat   x) -> realToFrac x
 "realToFrac/CDouble->a"   realToFrac = \(CDouble  x) -> realToFrac x
-"realToFrac/CLDouble->a"  realToFrac = \(CLDouble x) -> realToFrac x
  #-}
 
+-- GHC doesn't support CLDouble yet
+-- "realToFrac/a->CLDouble"  realToFrac = \x -> CLDouble (realToFrac x)
+-- "realToFrac/CLDouble->a"  realToFrac = \(CLDouble x) -> realToFrac x
+
 -- | Haskell type representing the C @ptrdiff_t@ type.
 INTEGRAL_TYPE(CPtrdiff,tyConCPtrdiff,"CPtrdiff",HTYPE_PTRDIFF_T)
 -- | Haskell type representing the C @size_t@ type.
@@ -183,7 +215,12 @@ INTEGRAL_TYPE(CSigAtomic,tyConCSigAtomic,"CSigAtomic",HTYPE_SIG_ATOMIC_T)
 -- | Haskell type representing the C @clock_t@ type.
 ARITHMETIC_TYPE(CClock,tyConCClock,"CClock",HTYPE_CLOCK_T)
 -- | Haskell type representing the C @time_t@ type.
+--
 ARITHMETIC_TYPE(CTime,tyConCTime,"CTime",HTYPE_TIME_T)
+-- | Haskell type representing the C @useconds_t@ type.
+ARITHMETIC_TYPE(CUSeconds,tyConCUSeconds,"CUSeconds",HTYPE_USECONDS_T)
+-- | Haskell type representing the C @suseconds_t@ type.
+ARITHMETIC_TYPE(CSUSeconds,tyConCSUSeconds,"CSUSeconds",HTYPE_SUSECONDS_T)
 
 -- FIXME: Implement and provide instances for Eq and Storable
 -- | Haskell type representing the C @FILE@ type.
@@ -251,15 +288,16 @@ representing a C type @t@:
 
 -}
 
-#else  /* __NHC__ */
+#else   /* __NHC__ */
 
 import NHC.FFI
   ( CChar(..),    CSChar(..),  CUChar(..)
   , CShort(..),   CUShort(..), CInt(..),   CUInt(..)
   , CLong(..),    CULong(..),  CLLong(..), CULLong(..)
   , CPtrdiff(..), CSize(..),   CWchar(..), CSigAtomic(..)
-  , CClock(..),   CTime(..)
+  , CClock(..),   CTime(..),   CUSeconds(..), CSUSeconds(..)
   , CFloat(..),   CDouble(..), CLDouble(..)
+  , CIntPtr(..),  CUIntPtr(..),CIntMax(..), CUIntMax(..)
   , CFile,        CFpos,       CJmpBuf
   , Storable(..)
   )
@@ -297,5 +335,9 @@ INSTANCE_BITS(CPtrdiff)
 INSTANCE_BITS(CWchar)
 INSTANCE_BITS(CSigAtomic)
 INSTANCE_BITS(CSize)
+INSTANCE_BITS(CIntPtr)
+INSTANCE_BITS(CUIntPtr)
+INSTANCE_BITS(CIntMax)
+INSTANCE_BITS(CUIntMax)
 
 #endif