{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, RoleAnnotations #-}
{-# LANGUAGE UnboxedTuples #-}
{-# OPTIONS_HADDOCK not-home #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  GHC.Ptr
-- Copyright   :  (c) The FFI Task Force, 2000-2002
-- License     :  see libraries/base/LICENSE
--
-- Maintainer  :  ffi@haskell.org
-- Stability   :  internal
-- Portability :  non-portable (GHC Extensions)
--
-- The 'Ptr' and 'FunPtr' types and operations.
--
-----------------------------------------------------------------------------

module GHC.Ptr (
        Ptr(..), FunPtr(..),
        nullPtr, castPtr, plusPtr, alignPtr, minusPtr,
        nullFunPtr, castFunPtr,

        -- * Unsafe functions
        castFunPtrToPtr, castPtrToFunPtr,

    ) where

import GHC.Base
import GHC.Show
import GHC.Num
import GHC.List ( length, replicate )
import Numeric          ( showHex )

#include "MachDeps.h"

------------------------------------------------------------------------
-- Data pointers.

-- The role of Ptr's parameter is phantom, as there is no relation between
-- the Haskell representation and whathever the user puts at the end of the
-- pointer. And phantom is useful to implement castPtr (see #9163)

-- redundant role annotation checks that this doesn't change
type role Ptr phantom
data Ptr a = Ptr Addr#
  deriving ( Ptr a -> Ptr a -> Bool
(Ptr a -> Ptr a -> Bool) -> (Ptr a -> Ptr a -> Bool) -> Eq (Ptr a)
forall a. Ptr a -> Ptr a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Ptr a -> Ptr a -> Bool
== :: Ptr a -> Ptr a -> Bool
$c/= :: forall a. Ptr a -> Ptr a -> Bool
/= :: Ptr a -> Ptr a -> Bool
Eq  -- ^ @since 2.01
           , Eq (Ptr a)
Eq (Ptr a)
-> (Ptr a -> Ptr a -> Ordering)
-> (Ptr a -> Ptr a -> Bool)
-> (Ptr a -> Ptr a -> Bool)
-> (Ptr a -> Ptr a -> Bool)
-> (Ptr a -> Ptr a -> Bool)
-> (Ptr a -> Ptr a -> Ptr a)
-> (Ptr a -> Ptr a -> Ptr a)
-> Ord (Ptr a)
Ptr a -> Ptr a -> Bool
Ptr a -> Ptr a -> Ordering
Ptr a -> Ptr a -> Ptr a
forall a. Eq (Ptr a)
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ptr a -> Ptr a -> Bool
forall a. Ptr a -> Ptr a -> Ordering
forall a. Ptr a -> Ptr a -> Ptr a
$ccompare :: forall a. Ptr a -> Ptr a -> Ordering
compare :: Ptr a -> Ptr a -> Ordering
$c< :: forall a. Ptr a -> Ptr a -> Bool
< :: Ptr a -> Ptr a -> Bool
$c<= :: forall a. Ptr a -> Ptr a -> Bool
<= :: Ptr a -> Ptr a -> Bool
$c> :: forall a. Ptr a -> Ptr a -> Bool
> :: Ptr a -> Ptr a -> Bool
$c>= :: forall a. Ptr a -> Ptr a -> Bool
>= :: Ptr a -> Ptr a -> Bool
$cmax :: forall a. Ptr a -> Ptr a -> Ptr a
max :: Ptr a -> Ptr a -> Ptr a
$cmin :: forall a. Ptr a -> Ptr a -> Ptr a
min :: Ptr a -> Ptr a -> Ptr a
Ord -- ^ @since 2.01
           )
-- ^ A value of type @'Ptr' a@ represents a pointer to an object, or an
-- array of objects, which may be marshalled to or from Haskell values
-- of type @a@.
--
-- The type @a@ will often be an instance of class
-- 'Foreign.Storable.Storable' which provides the marshalling operations.
-- However this is not essential, and you can provide your own operations
-- to access the pointer.  For example you might write small foreign
-- functions to get or set the fields of a C @struct@.

-- |The constant 'nullPtr' contains a distinguished value of 'Ptr'
-- that is not associated with a valid memory location.
nullPtr :: Ptr a
nullPtr :: forall a. Ptr a
nullPtr = Addr# -> Ptr a
forall a. Addr# -> Ptr a
Ptr Addr#
nullAddr#

-- |The 'castPtr' function casts a pointer from one type to another.
castPtr :: Ptr a -> Ptr b
castPtr :: forall a b. Ptr a -> Ptr b
castPtr = Ptr a -> Ptr b
forall a b. Coercible a b => a -> b
coerce

-- |Advances the given address by the given offset in bytes.
plusPtr :: Ptr a -> Int -> Ptr b
plusPtr :: forall a b. Ptr a -> Int -> Ptr b
plusPtr (Ptr Addr#
addr) (I# Int#
d) = Addr# -> Ptr b
forall a. Addr# -> Ptr a
Ptr (Addr# -> Int# -> Addr#
plusAddr# Addr#
addr Int#
d)

-- |Given an arbitrary address and an alignment constraint,
-- 'alignPtr' yields the next higher address that fulfills the
-- alignment constraint.  An alignment constraint @x@ is fulfilled by
-- any address divisible by @x@.  This operation is idempotent.
alignPtr :: Ptr a -> Int -> Ptr a
alignPtr :: forall a. Ptr a -> Int -> Ptr a
alignPtr addr :: Ptr a
addr@(Ptr Addr#
a) (I# Int#
i)
  = case Addr# -> Int# -> Int#
remAddr# Addr#
a Int#
i of {
      Int#
0# -> Ptr a
addr;
      Int#
n -> Addr# -> Ptr a
forall a. Addr# -> Ptr a
Ptr (Addr# -> Int# -> Addr#
plusAddr# Addr#
a (Int#
i Int# -> Int# -> Int#
-# Int#
n)) }

-- |Computes the offset required to get from the second to the first
-- argument.  We have
--
-- > p2 == p1 `plusPtr` (p2 `minusPtr` p1)
minusPtr :: Ptr a -> Ptr b -> Int
minusPtr :: forall a b. Ptr a -> Ptr b -> Int
minusPtr (Ptr Addr#
a1) (Ptr Addr#
a2) = Int# -> Int
I# (Addr# -> Addr# -> Int#
minusAddr# Addr#
a1 Addr#
a2)

------------------------------------------------------------------------
-- Function pointers for the default calling convention.

-- 'FunPtr' has a phantom role for similar reasons to 'Ptr'.
type role FunPtr phantom
data FunPtr a = FunPtr Addr# deriving (FunPtr a -> FunPtr a -> Bool
(FunPtr a -> FunPtr a -> Bool)
-> (FunPtr a -> FunPtr a -> Bool) -> Eq (FunPtr a)
forall a. FunPtr a -> FunPtr a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. FunPtr a -> FunPtr a -> Bool
== :: FunPtr a -> FunPtr a -> Bool
$c/= :: forall a. FunPtr a -> FunPtr a -> Bool
/= :: FunPtr a -> FunPtr a -> Bool
Eq, Eq (FunPtr a)
Eq (FunPtr a)
-> (FunPtr a -> FunPtr a -> Ordering)
-> (FunPtr a -> FunPtr a -> Bool)
-> (FunPtr a -> FunPtr a -> Bool)
-> (FunPtr a -> FunPtr a -> Bool)
-> (FunPtr a -> FunPtr a -> Bool)
-> (FunPtr a -> FunPtr a -> FunPtr a)
-> (FunPtr a -> FunPtr a -> FunPtr a)
-> Ord (FunPtr a)
FunPtr a -> FunPtr a -> Bool
FunPtr a -> FunPtr a -> Ordering
FunPtr a -> FunPtr a -> FunPtr a
forall a. Eq (FunPtr a)
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. FunPtr a -> FunPtr a -> Bool
forall a. FunPtr a -> FunPtr a -> Ordering
forall a. FunPtr a -> FunPtr a -> FunPtr a
$ccompare :: forall a. FunPtr a -> FunPtr a -> Ordering
compare :: FunPtr a -> FunPtr a -> Ordering
$c< :: forall a. FunPtr a -> FunPtr a -> Bool
< :: FunPtr a -> FunPtr a -> Bool
$c<= :: forall a. FunPtr a -> FunPtr a -> Bool
<= :: FunPtr a -> FunPtr a -> Bool
$c> :: forall a. FunPtr a -> FunPtr a -> Bool
> :: FunPtr a -> FunPtr a -> Bool
$c>= :: forall a. FunPtr a -> FunPtr a -> Bool
>= :: FunPtr a -> FunPtr a -> Bool
$cmax :: forall a. FunPtr a -> FunPtr a -> FunPtr a
max :: FunPtr a -> FunPtr a -> FunPtr a
$cmin :: forall a. FunPtr a -> FunPtr a -> FunPtr a
min :: FunPtr a -> FunPtr a -> FunPtr a
Ord)
-- ^ A value of type @'FunPtr' a@ is a pointer to a function callable
-- from foreign code.  The type @a@ will normally be a /foreign type/,
-- a function type with zero or more arguments where
--
-- * the argument types are /marshallable foreign types/,
--   i.e. 'Char', 'Int', 'Double', 'Float',
--   'Bool', 'Data.Int.Int8', 'Data.Int.Int16', 'Data.Int.Int32',
--   'Data.Int.Int64', 'Data.Word.Word8', 'Data.Word.Word16',
--   'Data.Word.Word32', 'Data.Word.Word64', @'Ptr' a@, @'FunPtr' a@,
--   @'Foreign.StablePtr.StablePtr' a@ or a renaming of any of these
--   using @newtype@.
--
-- * the return type is either a marshallable foreign type or has the form
--   @'IO' t@ where @t@ is a marshallable foreign type or @()@.
--
-- A value of type @'FunPtr' a@ may be a pointer to a foreign function,
-- either returned by another foreign function or imported with a
-- a static address import like
--
-- > foreign import ccall "stdlib.h &free"
-- >   p_free :: FunPtr (Ptr a -> IO ())
--
-- or a pointer to a Haskell function created using a /wrapper/ stub
-- declared to produce a 'FunPtr' of the correct type.  For example:
--
-- > type Compare = Int -> Int -> Bool
-- > foreign import ccall "wrapper"
-- >   mkCompare :: Compare -> IO (FunPtr Compare)
--
-- Calls to wrapper stubs like @mkCompare@ allocate storage, which
-- should be released with 'Foreign.Ptr.freeHaskellFunPtr' when no
-- longer required.
--
-- To convert 'FunPtr' values to corresponding Haskell functions, one
-- can define a /dynamic/ stub for the specific foreign type, e.g.
--
-- > type IntFunction = CInt -> IO ()
-- > foreign import ccall "dynamic"
-- >   mkFun :: FunPtr IntFunction -> IntFunction

-- |The constant 'nullFunPtr' contains a
-- distinguished value of 'FunPtr' that is not
-- associated with a valid memory location.
nullFunPtr :: FunPtr a
nullFunPtr :: forall a. FunPtr a
nullFunPtr = Addr# -> FunPtr a
forall a. Addr# -> FunPtr a
FunPtr Addr#
nullAddr#

-- |Casts a 'FunPtr' to a 'FunPtr' of a different type.
castFunPtr :: FunPtr a -> FunPtr b
castFunPtr :: forall a b. FunPtr a -> FunPtr b
castFunPtr = FunPtr a -> FunPtr b
forall a b. Coercible a b => a -> b
coerce

-- |Casts a 'FunPtr' to a 'Ptr'.
--
-- /Note:/ this is valid only on architectures where data and function
-- pointers range over the same set of addresses, and should only be used
-- for bindings to external libraries whose interface already relies on
-- this assumption.
castFunPtrToPtr :: FunPtr a -> Ptr b
castFunPtrToPtr :: forall a b. FunPtr a -> Ptr b
castFunPtrToPtr (FunPtr Addr#
addr) = Addr# -> Ptr b
forall a. Addr# -> Ptr a
Ptr Addr#
addr

-- |Casts a 'Ptr' to a 'FunPtr'.
--
-- /Note:/ this is valid only on architectures where data and function
-- pointers range over the same set of addresses, and should only be used
-- for bindings to external libraries whose interface already relies on
-- this assumption.
castPtrToFunPtr :: Ptr a -> FunPtr b
castPtrToFunPtr :: forall a b. Ptr a -> FunPtr b
castPtrToFunPtr (Ptr Addr#
addr) = Addr# -> FunPtr b
forall a. Addr# -> FunPtr a
FunPtr Addr#
addr

------------------------------------------------------------------------
-- Show instances for Ptr and FunPtr

-- | @since 2.01
instance Show (Ptr a) where
   showsPrec :: Int -> Ptr a -> ShowS
showsPrec Int
_ (Ptr Addr#
a) String
rs = ShowS
pad_out (Integer -> ShowS
forall a. Integral a => a -> ShowS
showHex (Word# -> Integer
integerFromWord#(Int# -> Word#
int2Word#(Addr# -> Int#
addr2Int# Addr#
a))) String
"")
     where
        -- want 0s prefixed to pad it out to a fixed length.
       pad_out :: ShowS
pad_out String
ls =
          Char
'0'Char -> ShowS
forall a. a -> [a] -> [a]
:Char
'x'Char -> ShowS
forall a. a -> [a] -> [a]
:(Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
2Int -> Int -> Int
forall a. Num a => a -> a -> a
*SIZEOF_HSPTR - length ls) '0') ++ ls ++ rs

-- | @since 2.01
instance Show (FunPtr a) where
   showsPrec :: Int -> FunPtr a -> ShowS
showsPrec Int
p = Int -> Ptr Any -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
p (Ptr Any -> ShowS) -> (FunPtr a -> Ptr Any) -> FunPtr a -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunPtr a -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr