Z-Data-0.8.3.0: Array, vector and text
Copyright(c) Dong Han 2020
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.Foreign.CPtr

Description

This module provide a lightweight foreign pointer, support c initializer and finalizer only.

Synopsis

CPtr type

data CPtr a Source #

Lightweight foreign pointers.

Instances

Instances details
Eq (CPtr a) Source # 
Instance details

Defined in Z.Foreign.CPtr

Methods

(==) :: CPtr a -> CPtr a -> Bool #

(/=) :: CPtr a -> CPtr a -> Bool #

Ord (CPtr a) Source # 
Instance details

Defined in Z.Foreign.CPtr

Methods

compare :: CPtr a -> CPtr a -> Ordering #

(<) :: CPtr a -> CPtr a -> Bool #

(<=) :: CPtr a -> CPtr a -> Bool #

(>) :: CPtr a -> CPtr a -> Bool #

(>=) :: CPtr a -> CPtr a -> Bool #

max :: CPtr a -> CPtr a -> CPtr a #

min :: CPtr a -> CPtr a -> CPtr a #

Show (CPtr a) Source # 
Instance details

Defined in Z.Foreign.CPtr

Methods

showsPrec :: Int -> CPtr a -> ShowS #

show :: CPtr a -> String #

showList :: [CPtr a] -> ShowS #

Print (CPtr a) Source # 
Instance details

Defined in Z.Foreign.CPtr

Methods

toUTF8BuilderP :: Int -> CPtr a -> Builder () Source #

newCPtr' Source #

Arguments

:: IO (Ptr a)

initializer

-> FunPtr (Ptr a -> IO b)

finalizer

-> IO (CPtr a) 

Initialize a CPtr with initializer which return an allocated pointer.

newCPtrUnsafe Source #

Arguments

:: (MutableByteArray# RealWorld -> IO r)

initializer

-> FunPtr (Ptr a -> IO b)

finalizer

-> IO (CPtr a, r) 

Initialize a CPtr with initializer(must be unsafe FFI) and finalizer.

The initializer will receive a pointer of pointer so that it can do allocation and write pointer back.

newCPtr Source #

Arguments

:: (Ptr (Ptr a) -> IO r)

initializer

-> FunPtr (Ptr a -> IO b)

finalizer

-> IO (CPtr a, r) 

Initialize a CPtr with initializer and finalizer.

The initializer will receive a pointer of pointer so that it can do allocation and write pointer back.

withCPtr :: CPtr a -> (Ptr a -> IO b) -> IO b Source #

The only way to use CPtr as a Ptr in FFI is to use withCPtr.

withCPtrsUnsafe :: forall a b. [CPtr a] -> (BA# (Ptr a) -> Int -> IO b) -> IO b Source #

Pass a list of 'CPtr Foo' as foo**. USE THIS FUNCTION WITH UNSAFE FFI ONLY!

withCPtrs :: forall a b. [CPtr a] -> (Ptr (Ptr a) -> Int -> IO b) -> IO b Source #

Pass a list of 'CPtr Foo' as foo**.

Ptr type

data Ptr a #

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 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.

Instances

Instances details
NFData1 Ptr

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Ptr a -> () #

Generic1 (URec (Ptr ()) :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec (Ptr ())) :: k -> Type #

Methods

from1 :: forall (a :: k0). URec (Ptr ()) a -> Rep1 (URec (Ptr ())) a #

to1 :: forall (a :: k0). Rep1 (URec (Ptr ())) a -> URec (Ptr ()) a #

Eq (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

(==) :: Ptr a -> Ptr a -> Bool #

(/=) :: Ptr a -> Ptr a -> Bool #

Data a => Data (Ptr a)

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ptr a -> c (Ptr a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ptr a) #

toConstr :: Ptr a -> Constr #

dataTypeOf :: Ptr a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ptr a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ptr a)) #

gmapT :: (forall b. Data b => b -> b) -> Ptr a -> Ptr a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ptr a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ptr a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) #

Ord (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

compare :: 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 #

max :: Ptr a -> Ptr a -> Ptr a #

min :: Ptr a -> Ptr a -> Ptr a #

Show (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

showsPrec :: Int -> Ptr a -> ShowS #

show :: Ptr a -> String #

showList :: [Ptr a] -> ShowS #

Foldable (UAddr :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UAddr m -> m #

foldMap :: Monoid m => (a -> m) -> UAddr a -> m #

foldMap' :: Monoid m => (a -> m) -> UAddr a -> m #

foldr :: (a -> b -> b) -> b -> UAddr a -> b #

foldr' :: (a -> b -> b) -> b -> UAddr a -> b #

foldl :: (b -> a -> b) -> b -> UAddr a -> b #

foldl' :: (b -> a -> b) -> b -> UAddr a -> b #

foldr1 :: (a -> a -> a) -> UAddr a -> a #

foldl1 :: (a -> a -> a) -> UAddr a -> a #

toList :: UAddr a -> [a] #

null :: UAddr a -> Bool #

length :: UAddr a -> Int #

elem :: Eq a => a -> UAddr a -> Bool #

maximum :: Ord a => UAddr a -> a #

minimum :: Ord a => UAddr a -> a #

sum :: Num a => UAddr a -> a #

product :: Num a => UAddr a -> a #

Traversable (UAddr :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UAddr a -> f (UAddr b) #

sequenceA :: Applicative f => UAddr (f a) -> f (UAddr a) #

mapM :: Monad m => (a -> m b) -> UAddr a -> m (UAddr b) #

sequence :: Monad m => UAddr (m a) -> m (UAddr a) #

NFData (Ptr a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Ptr a -> () #

Hashable (Ptr a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Ptr a -> Int #

hash :: Ptr a -> Int #

Prim (Ptr a) 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Ptr a -> Int# #

alignment# :: Ptr a -> Int# #

indexByteArray# :: ByteArray# -> Int# -> Ptr a #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Ptr a #) #

writeByteArray# :: MutableByteArray# s -> Int# -> Ptr a -> State# s -> State# s #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Ptr a -> State# s -> State# s #

indexOffAddr# :: Addr# -> Int# -> Ptr a #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Ptr a #) #

writeOffAddr# :: Addr# -> Int# -> Ptr a -> State# s -> State# s #

setOffAddr# :: Addr# -> Int# -> Int# -> Ptr a -> State# s -> State# s #

Unaligned (Ptr a) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Print (Ptr a) Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Ptr a -> Builder () Source #

Functor (URec (Ptr ()) :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b #

(<$) :: a -> URec (Ptr ()) b -> URec (Ptr ()) a #

Eq (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(/=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

Ord (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering #

(<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p #

min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p #

Generic (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: Type -> Type #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p #

data URec (Ptr ()) (p :: k)

Used for marking occurrences of Addr#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec (Ptr ()) (p :: k) = UAddr {}
type Rep1 (URec (Ptr ()) :: k -> Type) 
Instance details

Defined in GHC.Generics

type Rep1 (URec (Ptr ()) :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: k -> Type)))
type Rep (URec (Ptr ()) p) 
Instance details

Defined in GHC.Generics

type Rep (URec (Ptr ()) p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: Type -> Type)))

nullPtr :: Ptr a #

The constant nullPtr contains a distinguished value of Ptr that is not associated with a valid memory location.

data FunPtr a #

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

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 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

Instances

Instances details
NFData1 FunPtr

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> FunPtr a -> () #

Eq (FunPtr a) 
Instance details

Defined in GHC.Ptr

Methods

(==) :: FunPtr a -> FunPtr a -> Bool #

(/=) :: FunPtr a -> FunPtr a -> Bool #

Ord (FunPtr a) 
Instance details

Defined in GHC.Ptr

Methods

compare :: 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 #

max :: FunPtr a -> FunPtr a -> FunPtr a #

min :: FunPtr a -> FunPtr a -> FunPtr a #

Show (FunPtr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

showsPrec :: Int -> FunPtr a -> ShowS #

show :: FunPtr a -> String #

showList :: [FunPtr a] -> ShowS #

NFData (FunPtr a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: FunPtr a -> () #

Hashable (FunPtr a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> FunPtr a -> Int #

hash :: FunPtr a -> Int #

Prim (FunPtr a) 
Instance details

Defined in Data.Primitive.Types