Use explicit language extensions & remove extension fields from base.cabal
[ghc-base.git] / Foreign / Ptr.hs
index e6eb205..b46acc1 100644 (file)
@@ -1,4 +1,10 @@
-{-# OPTIONS_GHC -fno-implicit-prelude #-}
+{-# LANGUAGE CPP
+           , NoImplicitPrelude
+           , ForeignFunctionInterface
+           , MagicHash
+           , GeneralizedNewtypeDeriving
+  #-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Foreign.Ptr
 module Foreign.Ptr (
 
     -- * Data pointers
-    
+
     Ptr,      -- data Ptr a
     nullPtr,      -- :: Ptr a
     castPtr,      -- :: Ptr a -> Ptr b
     plusPtr,      -- :: Ptr a -> Int -> Ptr b
     alignPtr,     -- :: Ptr a -> Int -> Ptr a
     minusPtr,     -- :: Ptr a -> Ptr b -> Int
-    
+
     -- * Function pointers
-    
+
     FunPtr,      -- data FunPtr a
     nullFunPtr,      -- :: FunPtr a
     castFunPtr,      -- :: FunPtr a -> FunPtr b
     castFunPtrToPtr, -- :: FunPtr a -> Ptr b
     castPtrToFunPtr, -- :: Ptr a -> FunPtr b
-    
+
     freeHaskellFunPtr, -- :: FunPtr a -> IO ()
     -- Free the function pointer created by foreign export dynamic.
 
-    -- * Integral types with lossless conversion to/from pointers
+#ifndef __NHC__
+    -- * Integral types with lossless conversion to and from pointers
     IntPtr,
     ptrToIntPtr,
     intPtrToPtr,
     WordPtr,
     ptrToWordPtr,
     wordPtrToPtr
+#endif
  ) where
 
 #ifdef __GLASGOW_HASKELL__
 import GHC.Ptr
-import GHC.IOBase
 import GHC.Base
 import GHC.Num
-import GHC.List
 import GHC.Read
 import GHC.Real
 import GHC.Show
 import GHC.Enum
-import GHC.Word                ( Word(..) )
-import Data.Bits
-import Data.Typeable   ( Typeable(..), mkTyCon, mkTyConApp )
-import Numeric
-import Foreign.C.Types
+import GHC.Word         ( Word(..) )
 
-import Foreign.Storable
-import Data.Int
+-- import Data.Int
 import Data.Word
+#else
+import Control.Monad    ( liftM )
+import Foreign.C.Types
 #endif
 
+import Data.Bits
+import Data.Typeable
+import Foreign.Storable ( Storable(..) )
+
 #ifdef __NHC__
 import NHC.FFI
   ( Ptr
@@ -95,19 +103,24 @@ import Hugs.Ptr
 -- no longer required; otherwise, the storage it uses will leak.
 foreign import ccall unsafe "freeHaskellFunctionPtr"
     freeHaskellFunPtr :: FunPtr a -> IO ()
+#endif
 
-#include "HsBaseConfig.h"
-#include "CTypes.h"
+#ifndef __NHC__
+# include "HsBaseConfig.h"
+# include "CTypes.h"
 
--- | An unsigend integral type that can be losslessly converted to and from
--- @Ptr@.
+# ifdef __GLASGOW_HASKELL__
+-- | An unsigned integral type that can be losslessly converted to and from
+-- @Ptr@. This type is also compatible with the C99 type @uintptr_t@, and
+-- can be marshalled to and from that type safely.
 INTEGRAL_TYPE(WordPtr,tyConWordPtr,"WordPtr",Word)
-       -- Word and Int are guaranteed pointer-sized in GHC
+        -- Word and Int are guaranteed pointer-sized in GHC
 
--- | A sigend integral type that can be losslessly converted to and from
--- @Ptr@.
+-- | A signed integral type that can be losslessly converted to and from
+-- @Ptr@.  This type is also compatible with the C99 type @intptr_t@, and
+-- can be marshalled to and from that type safely.
 INTEGRAL_TYPE(IntPtr,tyConIntPtr,"IntPtr",Int)
-       -- Word and Int are guaranteed pointer-sized in GHC
+        -- Word and Int are guaranteed pointer-sized in GHC
 
 -- | casts a @Ptr@ to a @WordPtr@
 ptrToWordPtr :: Ptr a -> WordPtr
@@ -124,4 +137,25 @@ ptrToIntPtr (Ptr a#) = IntPtr (I# (addr2Int# a#))
 -- | casts an @IntPtr@ to a @Ptr@
 intPtrToPtr :: IntPtr -> Ptr a
 intPtrToPtr (IntPtr (I# i#)) = Ptr (int2Addr# i#)
-#endif
+
+# else /* !__GLASGOW_HASKELL__ */
+
+INTEGRAL_TYPE(WordPtr,tyConWordPtr,"WordPtr",CUIntPtr)
+INTEGRAL_TYPE(IntPtr,tyConIntPtr,"IntPtr",CIntPtr)
+
+{-# CFILES cbits/PrelIOUtils.c #-}
+
+foreign import ccall unsafe "__hscore_to_uintptr"
+    ptrToWordPtr :: Ptr a -> WordPtr
+
+foreign import ccall unsafe "__hscore_from_uintptr"
+    wordPtrToPtr :: WordPtr -> Ptr a
+
+foreign import ccall unsafe "__hscore_to_intptr"
+    ptrToIntPtr :: Ptr a -> IntPtr
+
+foreign import ccall unsafe "__hscore_from_intptr"
+    intPtrToPtr :: IntPtr -> Ptr a
+
+# endif /* !__GLASGOW_HASKELL__ */
+#endif /* !__NHC_ */