Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- flint_malloc :: Ptr CSize -> IO ()
- flint_realloc :: Ptr () -> Ptr CSize -> IO ()
- flint_calloc :: Ptr CSize -> Ptr CSize -> IO ()
- flint_bits :: CULong
- data FRandState = FRandState !(ForeignPtr CFRandState)
- type CFRandState = CFlint FRandState
- newFRandState :: IO FRandState
- withFRandState :: FRandState -> (Ptr CFRandState -> IO a) -> IO (FRandState, a)
- flint_rand_alloc :: IO (Ptr CFRandState)
- flint_rand_free :: Ptr CFRandState -> IO ()
- flint_randinit :: Ptr CFRandState -> IO ()
- flint_randclear :: Ptr CFRandState -> IO ()
- flint_set_num_threads :: CInt -> IO ()
- flint_get_num_threads :: IO ()
- flint_set_num_workers :: CInt -> IO CInt
- flint_reset_num_workers :: CInt -> IO ()
- module Data.Number.Flint.Flint.Internal
- module Data.Number.Flint.Flint.External
Allocation Functions
flint_realloc :: Ptr () -> Ptr CSize -> IO () Source #
flint_realloc ptr size
Reallocate an area of memory previously allocated by flint_malloc
,
flint_realloc
, or flint_calloc
.
flint_calloc :: Ptr CSize -> Ptr CSize -> IO () Source #
flint_calloc num size
Allocate num
objects of size
bytes each, and zero the allocated
memory.
Constants
flint_bits :: CULong Source #
Random Numbers
data FRandState Source #
Instances
Storable CFRandState Source # | |
Defined in Data.Number.Flint.Flint.FFI sizeOf :: CFRandState -> Int # alignment :: CFRandState -> Int # peekElemOff :: Ptr CFRandState -> Int -> IO CFRandState # pokeElemOff :: Ptr CFRandState -> Int -> CFRandState -> IO () # peekByteOff :: Ptr b -> Int -> IO CFRandState # pokeByteOff :: Ptr b -> Int -> CFRandState -> IO () # peek :: Ptr CFRandState -> IO CFRandState # poke :: Ptr CFRandState -> CFRandState -> IO () # |
type CFRandState = CFlint FRandState Source #
withFRandState :: FRandState -> (Ptr CFRandState -> IO a) -> IO (FRandState, a) Source #
flint_rand_alloc :: IO (Ptr CFRandState) Source #
flint_rand_alloc
Allocates a flint_rand_t
object to be used like a heap-allocated
flint_rand_t
in external libraries. The random state is not
initialised.
flint_rand_free :: Ptr CFRandState -> IO () Source #
flint_rand_free state
Frees a random state object as allocated using flint_rand_alloc
.
flint_randinit :: Ptr CFRandState -> IO () Source #
flint_randinit state
Initialize a flint_rand_t
.
flint_randclear :: Ptr CFRandState -> IO () Source #
flint_randclear state
Free all memory allocated by flint_rand_init
.
Thread functions
flint_set_num_threads :: CInt -> IO () Source #
flint_set_num_threads num_threads
Set up a thread pool of num_threads - 1
worker threads (in addition to
the master thread) and set the maximum number of worker threads the
master thread can start to num_threads - 1
.
This function may only be called globally from the master thread. It can also be called at a global level to change the size of the thread pool, but an exception is raised if the thread pool is in use (threads have been woken but not given back). The function cannot be called from inside worker threads.
flint_get_num_threads :: IO () Source #
flint_get_num_threads
When called at the global level, this function returns one more than the number of worker threads in the Flint thread pool, i.e. it counts the workers in the thread pool plus one more for the master thread.
In general, this function returns one more than the number of additional worker threads that can be started by the current thread.
Use thread_pool_wake
to set this number for a given worker thread.
flint_set_num_workers :: CInt -> IO CInt Source #
flint_set_num_workers num_workers
Restricts the number of worker threads that can be started by the
current thread to num_workers
. This function can be called from any
thread.
Assumes that the Flint thread pool is already set up.
The function returns the old number of worker threads that can be started.
The function can only be used to reduce the number of workers that can be started from a thread. It cannot be used to increase the number. If a higher number is passed, the function has no effect.
The number of workers must be restored to the original value by a call
to flint_reset_num_workers
before the thread is returned to the thread
pool.
The main use of this function and flint_reset_num_workers
is to
cheaply and temporarily restrict the number of workers that can be
started, e.g. by a function that one wishes to call from a thread, and
cheaply restore the number of workers to its original value before
exiting the current thread.
flint_reset_num_workers :: CInt -> IO () Source #
flint_reset_num_workers num_workers
After a call to flint_set_num_workers
this function must be called to
set the number of workers that may be started by the current thread back
to its original value.