This module provides the ForeignObj
type, which is a Haskell
reference to an object in the outside world. Foreign objects are
boxed versions of Addr#
, the only reason for their existence is
so that they can be used with finalisers (see Section
Finalisation for foreign objects).
module Foreign where
data ForeignObj -- abstract, instance of: Eq
makeForeignObj :: Addr{-object-} -> IO ForeignObj
writeForeignObj :: ForeignObj -> Addr{-new value-} -> IO ()
In addition to the above, the following operations for indexing via
a ForeignObj
are also, mirrored on the same operations provided
over Addr
s:
indexCharOffForeignObj :: ForeignObj -> Int -> Char
indexIntOffForeignObj :: ForeignObj -> Int -> Int
indexAddrOffForeignObj :: ForeignObj -> Int -> Addr
indexFloatOffForeignObj :: ForeignObj -> Int -> Float
indexDoubleOffForeignObj :: ForeignObj -> Int -> Double
indexWord8OffForeignObj :: ForeignObj -> Int -> Word8
indexWord16OffForeignObj :: ForeignObj -> Int -> Word16
indexWord32OffForeignObj :: ForeignObj -> Int -> Word32
indexWord64OffForeignObj :: ForeignObj -> Int -> Word64
indexInt8OffForeignObj :: ForeignObj -> Int -> Int8
indexInt16OffForeignObj :: ForeignObj -> Int -> Int16
indexInt32OffForeignObj :: ForeignObj -> Int -> Int32
indexInt64OffForeignObj :: ForeignObj -> Int -> Int64
-- read value out of mutable memory
readCharOffForeignObj :: ForeignObj -> Int -> IO Char
readIntOffForeignObj :: ForeignObj -> Int -> IO Int
readAddrOffForeignObj :: ForeignObj -> Int -> IO Addr
readFloatOffForeignObj :: ForeignObj -> Int -> IO Float
readDoubleOffForeignObj :: ForeignObj -> Int -> IO Double
readWord8OffForeignObj :: ForeignObj -> Int -> IO Word8
readWord16OffForeignObj :: ForeignObj -> Int -> IO Word16
readWord32OffForeignObj :: ForeignObj -> Int -> IO Word32
readWord64OffForeignObj :: ForeignObj -> Int -> IO Word64
readInt8OffForeignObj :: ForeignObj -> Int -> IO Int8
readInt16OffForeignObj :: ForeignObj -> Int -> IO Int16
readInt32OffForeignObj :: ForeignObj -> Int -> IO Int32
readInt64OffForeignObj :: ForeignObj -> Int -> IO Int64
writeCharOffForeignObj :: ForeignObj -> Int -> Char -> IO ()
writeIntOffForeignObj :: ForeignObj -> Int -> Int -> IO ()
writeAddrOffForeignObj :: ForeignObj -> Int -> Addr -> IO ()
writeFloatOffForeignObj :: ForeignObj -> Int -> Float -> IO ()
writeDoubleOffForeignObj :: ForeignObj -> Int -> Double -> IO ()
writeWord8OffForeignObj :: ForeignObj -> Int -> Word8 -> IO ()
writeWord16OffForeignObj :: ForeignObj -> Int -> Word16 -> IO ()
writeWord32OffForeignObj :: ForeignObj -> Int -> Word32 -> IO ()
writeWord64OffForeignObj :: ForeignObj -> Int -> Word64 -> IO ()
writeInt8OffForeignObj :: ForeignObj -> Int -> Int8 -> IO ()
writeInt16OffForeignObj :: ForeignObj -> Int -> Int16 -> IO ()
writeInt32OffForeignObj :: ForeignObj -> Int -> Int32 -> IO ()
writeInt64OffForeignObj :: ForeignObj -> Int -> Int64 -> IO ()