import Data.Monoid (mappend)
#endif
import Data.Sequence (viewl, ViewL(..))
+#if __GLASGOW_HASKELL__ >= 709
+import Foreign
+#else
import Foreign.Safe
+#endif
import System.IO.Unsafe
---------------------------------------------
import Data.Either
import Data.List (find)
import Control.Monad
+#if __GLASGOW_HASKELL__ >= 709
+import Foreign
+#else
import Foreign.Safe
+#endif
import Foreign.C
import GHC.Exts
import Data.Array
import GHC.IO ( IO(..), unsafeDupablePerformIO )
+#if __GLASGOW_HASKELL__ >= 709
+import Foreign
+#else
import Foreign.Safe
+#endif
#if STAGE >= 2
import GHC.Conc.Sync (sharedCAF)
import GHC.Exts
+#if __GLASGOW_HASKELL__ >= 709
+import Foreign
+#else
import Foreign.Safe
+#endif
-- -----------------------------------------------------------------------------
-- The StringBuffer type
import Exception hiding (catch)
import Foreign.C
+#if __GLASGOW_HASKELL__ >= 709
+import Foreign
+#else
import Foreign.Safe
+#endif
import System.Directory
import System.Environment
-{-# LANGUAGE Unsafe #-}
+{-# LANGUAGE Safe #-}
{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-{-# LANGUAGE Unsafe #-}
+{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
, mallocForeignPtrArray0
) where
-import Foreign.ForeignPtr.Safe
+import Foreign.ForeignPtr.Imp
--
-----------------------------------------------------------------------------
-module Foreign.ForeignPtr.Safe (
+module Foreign.ForeignPtr.Safe {-# DEPRECATED "Safe is now the default, please use Foreign.ForeignPtr instead" #-} (
-- * Finalised data pointers
ForeignPtr
, FinalizerPtr
-{-# LANGUAGE Unsafe #-}
+{-# LANGUAGE Safe #-}
{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
module Foreign.Marshal
(
- -- | The module "Foreign.Marshal" re-exports the safe content in the
- -- @Foreign.Marshal@ hierarchy:
- module Foreign.Marshal.Safe
+ -- | The module "Foreign.Marshal.Safe" re-exports the other modules in the
+ -- @Foreign.Marshal@ hierarchy (except for @Foreign.Marshal.Unsafe@):
+ module Foreign.Marshal.Alloc
+ , module Foreign.Marshal.Array
+ , module Foreign.Marshal.Error
+ , module Foreign.Marshal.Pool
+ , module Foreign.Marshal.Utils
) where
-import Foreign.Marshal.Safe
+import Foreign.Marshal.Alloc
+import Foreign.Marshal.Array
+import Foreign.Marshal.Error
+import Foreign.Marshal.Pool
+import Foreign.Marshal.Utils
--
-----------------------------------------------------------------------------
-module Foreign.Marshal.Safe
+module Foreign.Marshal.Safe {-# DEPRECATED "Safe is now the default, please use Foreign.Marshal instead" #-}
(
-- | The module "Foreign.Marshal.Safe" re-exports the other modules in the
-- @Foreign.Marshal@ hierarchy:
--
-----------------------------------------------------------------------------
-module Foreign.Safe
+module Foreign.Safe {-# DEPRECATED "Safe is now the default, please use Foreign instead" #-}
( module Data.Bits
, module Data.Int
, module Data.Word
, module Foreign.Ptr
- , module Foreign.ForeignPtr.Safe
+ , module Foreign.ForeignPtr
, module Foreign.StablePtr
, module Foreign.Storable
- , module Foreign.Marshal.Safe
+ , module Foreign.Marshal
) where
import Data.Bits
import Data.Int
import Data.Word
import Foreign.Ptr
-import Foreign.ForeignPtr.Safe
+import Foreign.ForeignPtr
import Foreign.StablePtr
import Foreign.Storable
-import Foreign.Marshal.Safe
+import Foreign.Marshal
import GHC.Base () -- For build ordering
#else
-import Foreign.Safe
+import Foreign
import Foreign.C
import Data.Maybe
import GHC.Base
import GHC.MVar
import Data.Typeable
import Data.Maybe
-import Foreign.Safe
+import Foreign
import System.Posix.Internals hiding (FD)
import Foreign.C
import Data.Ratio
-import Foreign.Safe
+import Foreign
import Foreign.C
-- For struct rusage
getEnvironment,
) where
-import Foreign.Safe
+import Foreign
import Foreign.C
import System.IO.Error (mkIOError)
import Control.Exception.Base (bracket, throwIO)