raw-feldspar-0.2.1: Resource-Aware Feldspar

Safe HaskellNone
LanguageHaskell2010

Feldspar.Run.Concurrent

Synopsis

Documentation

data ThreadId :: * #

Instances

data Chan k k1 t a :: forall k k1. k1 -> k -> * #

A bounded channel.

data Closeable :: * #

data Uncloseable :: * #

class Transferable a where Source #

Minimal complete definition

calcChanSize, untypedReadChan, untypedWriteChan

Associated Types

type SizeSpec a :: * Source #

Size specification of a channel. In most of the cases, it is a natural number representing how many elements could be stored at the same time in the channel.

Methods

calcChanSize :: proxy a -> SizeSpec a -> ChanSize Data PrimType' Length Source #

Maps a size specification to an internal channel size representation, that is a map from primitive types to quantities. The byte size of the channel will be calculated as the sum of multiplying the byte size of each type with its quantity.

newChan :: SizeSpec a -> Run (Chan Uncloseable a) Source #

Create a new channel. Writing a reference type to a channel will copy contents into the channel, so modifying it post-write is completely safe.

newCloseableChan :: SizeSpec a -> Run (Chan Closeable a) Source #

readChan :: Chan t a -> Run a Source #

Read an element from a channel. If channel is empty, blocks until there is an item available. If closeChan has been called on the channel *and* if the channel is empty, readChan returns an undefined value immediately.

untypedReadChan :: Chan t c -> Run a Source #

Reads a value from any kind of channel. Instances should define this, but the user should never call it.

writeChan :: Chan t a -> a -> Run (Data Bool) Source #

Write a data element to a channel. If closeChan has been called on the channel, all calls to writeChan become non-blocking no-ops and return False, otherwise returns True. If the channel is full, this function blocks until there's space in the queue.

untypedWriteChan :: Chan t c -> a -> Run (Data Bool) Source #

Writes a value to any kind of channel. Instances should define this, but the user should never call it.

Instances

PrimType' a => Transferable (Data a) Source # 
(Syntax a, BulkTransferable a, (~) * (ContainerType a) (Arr a)) => Transferable (Pull a) Source # 
(Transferable a, Transferable b, (~) * (SizeSpec a) (SizeSpec b)) => Transferable (a, b) Source # 

Associated Types

type SizeSpec (a, b) :: * Source #

Methods

calcChanSize :: proxy (a, b) -> SizeSpec (a, b) -> ChanSize * Data PrimType' Length Source #

newChan :: SizeSpec (a, b) -> Run (Chan * * Uncloseable (a, b)) Source #

newCloseableChan :: SizeSpec (a, b) -> Run (Chan * * Closeable (a, b)) Source #

readChan :: Chan * * t (a, b) -> Run (a, b) Source #

untypedReadChan :: Chan * * t c -> Run (a, b) Source #

writeChan :: Chan * * t (a, b) -> (a, b) -> Run (Data Bool) Source #

untypedWriteChan :: Chan * * t c -> (a, b) -> Run (Data Bool) Source #

(Transferable a, Transferable b, Transferable c, (~) * (SizeSpec a) (SizeSpec b), (~) * (SizeSpec b) (SizeSpec c)) => Transferable (a, b, c) Source # 

Associated Types

type SizeSpec (a, b, c) :: * Source #

Methods

calcChanSize :: proxy (a, b, c) -> SizeSpec (a, b, c) -> ChanSize * Data PrimType' Length Source #

newChan :: SizeSpec (a, b, c) -> Run (Chan * * Uncloseable (a, b, c)) Source #

newCloseableChan :: SizeSpec (a, b, c) -> Run (Chan * * Closeable (a, b, c)) Source #

readChan :: Chan * * t (a, b, c) -> Run (a, b, c) Source #

untypedReadChan :: Chan * * t c -> Run (a, b, c) Source #

writeChan :: Chan * * t (a, b, c) -> (a, b, c) -> Run (Data Bool) Source #

untypedWriteChan :: Chan * * t c -> (a, b, c) -> Run (Data Bool) Source #

(Transferable a, Transferable b, Transferable c, Transferable d, (~) * (SizeSpec a) (SizeSpec b), (~) * (SizeSpec b) (SizeSpec c), (~) * (SizeSpec c) (SizeSpec d)) => Transferable (a, b, c, d) Source # 

Associated Types

type SizeSpec (a, b, c, d) :: * Source #

Methods

calcChanSize :: proxy (a, b, c, d) -> SizeSpec (a, b, c, d) -> ChanSize * Data PrimType' Length Source #

newChan :: SizeSpec (a, b, c, d) -> Run (Chan * * Uncloseable (a, b, c, d)) Source #

newCloseableChan :: SizeSpec (a, b, c, d) -> Run (Chan * * Closeable (a, b, c, d)) Source #

readChan :: Chan * * t (a, b, c, d) -> Run (a, b, c, d) Source #

untypedReadChan :: Chan * * t c -> Run (a, b, c, d) Source #

writeChan :: Chan * * t (a, b, c, d) -> (a, b, c, d) -> Run (Data Bool) Source #

untypedWriteChan :: Chan * * t c -> (a, b, c, d) -> Run (Data Bool) Source #

class Transferable a => BulkTransferable a where Source #

Minimal complete definition

untypedReadChanBuf, untypedWriteChanBuf

Associated Types

type ContainerType a :: * Source #

Methods

readChanBuf :: Chan t a -> Data Index -> Data Index -> ContainerType a -> Run (Data Bool) Source #

Read an arbitrary number of elements from a channel into an array. The semantics are the same as for readChan, where "channel is empty" is defined as "channel contains less data than requested". Returns False without reading any data if the channel is closed.

untypedReadChanBuf :: proxy a -> Chan t c -> Data Index -> Data Index -> ContainerType a -> Run (Data Bool) Source #

Read an arbitrary number of elements from any channel into an array. Instances should define this, but the user should never call it.

writeChanBuf :: Chan t a -> Data Index -> Data Index -> ContainerType a -> Run (Data Bool) Source #

Write an arbitrary number of elements from an array into an channel. The semantics are the same as for writeChan, where "channel is full" is defined as "channel has insufficient free space to store all written data".

untypedWriteChanBuf :: proxy a -> Chan t c -> Data Index -> Data Index -> ContainerType a -> Run (Data Bool) Source #

Write an arbitrary number of elements from an array into any channel. Instances should define this, but the user should never call it.

Instances

fork :: Run () -> Run ThreadId Source #

Fork off a computation as a new thread.

forkWithId :: (ThreadId -> Run ()) -> Run ThreadId Source #

Fork off a computation as a new thread, with access to its own thread ID.

asyncKillThread :: ThreadId -> Run () Source #

Forcibly terminate a thread, then continue execution immediately.

killThread :: ThreadId -> Run () Source #

Forcibly terminate a thread. Blocks until the thread is actually dead.

waitThread :: ThreadId -> Run () Source #

Wait for a thread to terminate.

delayThread :: Integral i => Data i -> Run () Source #

Sleep for a given amount of microseconds. Implemented with usleep. A C compiler might require a feature test macro to be defined, otherwise it emits a warning about an implicitly declared function. For more details, see: http://man7.org/linux/man-pages/man3/usleep.3.html

closeChan :: Chan Closeable a -> Run () Source #

Close a channel. All subsequent write operations will be no-ops. After the channel is drained, all subsequent read operations will be no-ops as well.

lastChanReadOK :: Chan Closeable a -> Run (Data Bool) Source #

When readChan was last called on the given channel, did the read succeed? Always returns True unless closeChan has been called on the channel. Always returns True if the channel has never been read.