unagi-chan-0.4.1.3: Fast concurrent queues with a Chan-like API, and more

Safe HaskellNone
LanguageHaskell2010

Control.Concurrent.Chan.Unagi.Unboxed

Contents

Synopsis

Creating channels

newChan :: UnagiPrim a => IO (InChan a, OutChan a) Source #

Create a new channel, returning its write and read ends.

data InChan a Source #

The write end of a channel created with newChan.

Instances
Eq (InChan a) Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.Unboxed.Internal

Methods

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

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

data OutChan a Source #

The read end of a channel created with newChan.

Instances
Eq (OutChan a) Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.Unboxed.Internal

Methods

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

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

class (Prim a, Eq a) => UnagiPrim a where Source #

Our class of types supporting primitive array operations. Instance method definitions are architecture-dependent.

Minimal complete definition

Nothing

Methods

atomicUnicorn :: Maybe a Source #

When the read and write operations of the underlying Prim instances on aligned memory are atomic, this may be set to Just x where x is some rare (i.e. unlikely to occur frequently in your data) magic value; this might help speed up some UnagiPrim operations.

Where those Prim instance operations are not atomic, this *must* be set to Nothing.

Instances
UnagiPrim Char Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.Unboxed.Internal

UnagiPrim Double Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.Unboxed.Internal

UnagiPrim Float Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.Unboxed.Internal

UnagiPrim Int Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.Unboxed.Internal

UnagiPrim Int8 Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.Unboxed.Internal

UnagiPrim Int16 Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.Unboxed.Internal

UnagiPrim Int32 Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.Unboxed.Internal

UnagiPrim Int64 Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.Unboxed.Internal

UnagiPrim Word Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.Unboxed.Internal

UnagiPrim Word8 Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.Unboxed.Internal

UnagiPrim Word16 Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.Unboxed.Internal

UnagiPrim Word32 Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.Unboxed.Internal

UnagiPrim Word64 Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.Unboxed.Internal

Channel operations

Reading

readChan :: UnagiPrim a => OutChan a -> IO a Source #

Read an element from the chan, blocking if the chan is empty.

Note re. exceptions: When an async exception is raised during a readChan the message that the read would have returned is likely to be lost, even when the read is known to be blocked on an empty queue. If you need to handle this scenario, you can use readChanOnException.

readChanOnException :: UnagiPrim a => OutChan a -> (IO a -> IO ()) -> IO a Source #

Like readChan but allows recovery of the queue element which would have been read, in the case that an async exception is raised during the read. To be precise exceptions are raised, and the handler run, only when readChanOnException is blocking.

The second argument is a handler that takes a blocking IO action returning the element, and performs some recovery action. When the handler is called, the passed IO a is the only way to access the element.

tryReadChan :: UnagiPrim a => OutChan a -> IO (Element a, IO a) Source #

Returns immediately with:

  • an Element a future, which returns one unique element when it becomes available via tryRead.
  • a blocking IO action that returns the element when it becomes available.

Note: This is a destructive operation. See Element for more details.

If you're using this function exclusively you might find the implementation in Control.Concurrent.Chan.Unagi.NoBlocking.Unboxed is faster.

Note re. exceptions: When an async exception is raised during a tryReadChan the message that the read would have returned is likely to be lost, just as it would be when raised directly after this function returns.

newtype Element a Source #

An IO action that returns a particular enqueued element when and if it becomes available.

Each Element corresponds to a particular enqueued element, i.e. a returned Element always offers the only means to access one particular enqueued item. The value returned by tryRead moves monotonically from Nothing to Just a when and if an element becomes available, and is idempotent at that point.

So for instance:

   (in, out) <- newChan
   (el, _) <- tryReadChan out  -- READ FROM EMPTY CHAN
   writeChan in "msg1"
   writeChan in "msg2"
   readChan out        -- RETURNS "msg2"
   tryRead el          -- RETURNS "msg1" (which would otherwise be lost)

Constructors

Element 

Fields

Instances
Monad Element Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.NoBlocking.Types

Methods

(>>=) :: Element a -> (a -> Element b) -> Element b #

(>>) :: Element a -> Element b -> Element b #

return :: a -> Element a #

fail :: String -> Element a #

Functor Element Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.NoBlocking.Types

Methods

fmap :: (a -> b) -> Element a -> Element b #

(<$) :: a -> Element b -> Element a #

MonadFix Element Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.NoBlocking.Types

Methods

mfix :: (a -> Element a) -> Element a #

MonadFail Element Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.NoBlocking.Types

Methods

fail :: String -> Element a #

Applicative Element Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.NoBlocking.Types

Methods

pure :: a -> Element a #

(<*>) :: Element (a -> b) -> Element a -> Element b #

liftA2 :: (a -> b -> c) -> Element a -> Element b -> Element c #

(*>) :: Element a -> Element b -> Element b #

(<*) :: Element a -> Element b -> Element a #

Alternative Element Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.NoBlocking.Types

Methods

empty :: Element a #

(<|>) :: Element a -> Element a -> Element a #

some :: Element a -> Element [a] #

many :: Element a -> Element [a] #

MonadPlus Element Source # 
Instance details

Defined in Control.Concurrent.Chan.Unagi.NoBlocking.Types

Methods

mzero :: Element a #

mplus :: Element a -> Element a -> Element a #

getChanContents :: UnagiPrim a => OutChan a -> IO [a] Source #

Return a lazy infinite list representing the contents of the supplied OutChan, much like System.IO.hGetContents.

Writing

writeChan :: UnagiPrim a => InChan a -> a -> IO () Source #

Write a value to the channel.

writeList2Chan :: UnagiPrim a => InChan a -> [a] -> IO () Source #

Write an entire list of items to a chan type. Writes here from multiple threads may be interleaved, and infinite lists are supported.

Broadcasting

dupChan :: InChan a -> IO (OutChan a) Source #

Duplicate a chan: the returned OutChan begins empty, but data written to the argument InChan from then on will be available from both the original OutChan and the one returned here, creating a kind of broadcast channel.