chp-1.3.2: An implementation of concurrency ideas from Communicating Sequential ProcessesSource codeContentsIndex
Control.Concurrent.CHP.Channels
Contents
Channel Creation
Channel-Ends
Reading and Writing with Channels
Shared Channels
Specific Channel Types
Description

The module containing all the different types of channels in CHP. Unlike JCSP and C++CSP2, CHP does not offer buffered channels directly (see the Control.Concurrent.CHP.Buffers module). There are four different channel types, effectively all possible combinations of:

  • Shared reader vs non-shared reader
  • Shared writer vs non-shared writer

For most applications you probably want just OneToOneChannel.

It is possible for the type system to infer which channel you want when you use newChannel. If the types of the ends are known by the type system, the channel-type can be inferred. So you can usually just write newChannel, and depending on how you use the channel, the type system will figure out which one you needed.

Synopsis
data Chan r w a
class Channel r w where
newChannel :: MonadCHP m => m (Chan r w a)
writeChannelStrict :: (NFData a, WriteableChannel chanEnd) => chanEnd a -> a -> CHP ()
newChannelWithLabel :: (Channel r w, MonadCHP m) => String -> m (Chan r w a)
newChannelWR :: (Channel r w, MonadCHP m) => m (w a, r a)
newChannelRW :: (Channel r w, MonadCHP m) => m (r a, w a)
class ChannelTuple t where
newChannels :: MonadCHP m => m t
newChannelList :: (Channel r w, MonadCHP m) => Int -> m [Chan r w a]
newChannelListWithLabels :: (Channel r w, MonadCHP m) => [String] -> m [Chan r w a]
newChannelListWithStem :: (Channel r w, MonadCHP m) => Int -> String -> m [Chan r w a]
getChannelIdentifier :: Chan r w a -> Unique
data Chanin a
data Chanout a
reader :: Chan r w a -> r a
writer :: Chan r w a -> w a
readers :: [Chan r w a] -> [r a]
writers :: [Chan r w a] -> [w a]
class ReadableChannel chanEnd where
readChannel :: chanEnd a -> CHP a
extReadChannel :: chanEnd a -> (a -> CHP b) -> CHP b
class WriteableChannel chanEnd where
writeChannel :: chanEnd a -> a -> CHP ()
extWriteChannel :: chanEnd a -> CHP a -> CHP ()
claim :: Shared c a -> (c a -> CHP b) -> CHP b
data Shared c a
type OneToOneChannel = Chan Chanin Chanout
oneToOneChannel :: MonadCHP m => m (OneToOneChannel a)
oneToOneChannelWithLabel :: MonadCHP m => String -> m (OneToOneChannel a)
type OneToAnyChannel = Chan (Shared Chanin) Chanout
oneToAnyChannel :: MonadCHP m => m (OneToAnyChannel a)
oneToAnyChannelWithLabel :: MonadCHP m => String -> m (OneToAnyChannel a)
type AnyToOneChannel = Chan Chanin (Shared Chanout)
anyToOneChannel :: MonadCHP m => m (AnyToOneChannel a)
anyToOneChannelWithLabel :: MonadCHP m => String -> m (AnyToOneChannel a)
type AnyToAnyChannel = Chan (Shared Chanin) (Shared Chanout)
anyToAnyChannel :: MonadCHP m => m (AnyToAnyChannel a)
anyToAnyChannelWithLabel :: MonadCHP m => String -> m (AnyToAnyChannel a)
Channel Creation
data Chan r w a Source
A channel type, that can be used to get the ends of the channel via reader and writer
class Channel r w whereSource
A class used for allocating new channels, and getting the reading and writing ends. There is a bijective assocation between the channel, and its pair of end types. You can see the types in the list of instances below. Thus, newChannel may be used, and the compiler will infer which type of channel is required based on what end-types you get from reader and writer. Alternatively, if you explicitly type the return of newChannel, it will be definite which ends you will use. If you do want to fix the type of the channel you are using when you allocate it, consider using one of the many oneToOneChannel-like shorthand functions that fix the type.
Methods
newChannel :: MonadCHP m => m (Chan r w a)Source
Allocates a new channel. Nothing need be done to destroy/de-allocate the channel when it is no longer in use.
show/hide Instances
writeChannelStrict :: (NFData a, WriteableChannel chanEnd) => chanEnd a -> a -> CHP ()Source

A helper function that uses the parallel strategies library (see the paper: "Algorithm + Strategy = Parallelism", P.W. Trinder et al, JFP 8(1) 1998, http://www.macs.hw.ac.uk/~dsg/gph/papers/html/Strategies/strategies.html) to make sure that the value sent down a channel is strictly evaluated by the sender before transmission.

This is useful when you want to write worker processes that evaluate data and send it back to some "harvester" process. By default the values sent back may be unevaluated, and thus the harvester might end up doing the evaluation. If you use this function, the value is guaranteed to be completely evaluated before sending.

Added in version 1.0.2.

newChannelWithLabel :: (Channel r w, MonadCHP m) => String -> m (Chan r w a)Source
Like newChannel but also associates a label with that channel in a trace. You can use this function whether tracing is turned on or not, so if you ever use tracing, you should use this rather than newChannel.
newChannelWR :: (Channel r w, MonadCHP m) => m (w a, r a)Source
A helper that is like newChannel but returns the writing and reading end of the channels directly.
newChannelRW :: (Channel r w, MonadCHP m) => m (r a, w a)Source
A helper that is like newChannel but returns the reading and writing end of the channels directly.
class ChannelTuple t whereSource

A helper class for easily creating several channels of the same type. The same type refers not only to what type the channel carries, but also to the type of channel (one-to-one no poison, one-to-any with poison, etc). You can write code like this:

 (a, b, c, d, e) <- newChannels

To create five channels of the same type.

Methods
newChannels :: MonadCHP m => m tSource
show/hide Instances
Channel r w => ChannelTuple ((,) (Chan r w a) (Chan r w a))
Channel r w => ChannelTuple ((,,) (Chan r w a) (Chan r w a) (Chan r w a))
Channel r w => ChannelTuple ((,,,) (Chan r w a) (Chan r w a) (Chan r w a) (Chan r w a))
Channel r w => ChannelTuple ((,,,,) (Chan r w a) (Chan r w a) (Chan r w a) (Chan r w a) (Chan r w a))
Channel r w => ChannelTuple ((,,,,,) (Chan r w a) (Chan r w a) (Chan r w a) (Chan r w a) (Chan r w a) (Chan r w a))
newChannelList :: (Channel r w, MonadCHP m) => Int -> m [Chan r w a]Source
Creates a list of channels of the same type with the given length. If you need to access some channels by index, use this function. Otherwise you may find using newChannels to be easier.
newChannelListWithLabels :: (Channel r w, MonadCHP m) => [String] -> m [Chan r w a]Source
A helper that is like newChannelList, but labels the channels with the given list. The number of channels returned is the same as the length of the list of labels
newChannelListWithStem :: (Channel r w, MonadCHP m) => Int -> String -> m [Chan r w a]Source
A helper that is like newChannelList, but labels the channels according to a pattern. Given a stem such as foo, it names the channels in the list foo0, foo1, foo2, etc.
getChannelIdentifier :: Chan r w a -> UniqueSource
Gets the channel's identifier. Useful if you need to be able to identify a channel in the trace later on.
Channel-Ends
data Chanin a Source

A reading channel-end type that allows poison to be thrown

Eq instance added in version 1.1.1

show/hide Instances
data Chanout a Source

A writing channel-end type that allows poison to be thrown

Eq instance added in version 1.1.1

show/hide Instances
reader :: Chan r w a -> r aSource
Gets the reading end of a channel from its Chan type.
writer :: Chan r w a -> w aSource
Gets the writing end of a channel from its Chan type.
readers :: [Chan r w a] -> [r a]Source
Gets all the reading ends of a list of channels. A shorthand for map reader.
writers :: [Chan r w a] -> [w a]Source
Gets all the writing ends of a list of channels. A shorthand for map writer.
Reading and Writing with Channels
class ReadableChannel chanEnd whereSource
A class indicating that a channel can be read from.
Methods
readChannel :: chanEnd a -> CHP aSource
Reads from the given reading channel-end
extReadChannel :: chanEnd a -> (a -> CHP b) -> CHP bSource
Performs an extended read from the channel, performing the given action before freeing the writer
show/hide Instances
class WriteableChannel chanEnd whereSource
A class indicating that a channel can be written to.
Methods
writeChannel :: chanEnd a -> a -> CHP ()Source
Writes from the given writing channel-end
extWriteChannel :: chanEnd a -> CHP a -> CHP ()Source
Starts the communication, then performs the given extended action, then sends the result of that down the channel
show/hide Instances
Shared Channels
claim :: Shared c a -> (c a -> CHP b) -> CHP bSource
Claims the given channel-end, executes the given block, then releases the channel-end and returns the output value. If poison or an IO exception is thrown inside the block, the channel is released and the poison/exception re-thrown.
data Shared c a Source
A wrapper (usually around a channel-end) indicating that the inner item is shared. Use the claim function to use this type.
show/hide Instances
Specific Channel Types
All the functions here are equivalent to newChannel (or newChannelWithLabel), but typed. So for example, oneToOneChannel = newChannel :: MonadCHP m => m OneToOneChannel.
type OneToOneChannel = Chan Chanin ChanoutSource
oneToOneChannel :: MonadCHP m => m (OneToOneChannel a)Source
A type-constrained version of newChannel.
oneToOneChannelWithLabel :: MonadCHP m => String -> m (OneToOneChannel a)Source

A type-constrained version of newChannelWithLabel.

Added in version 1.2.0.

type OneToAnyChannel = Chan (Shared Chanin) ChanoutSource
oneToAnyChannel :: MonadCHP m => m (OneToAnyChannel a)Source
A type-constrained version of newChannel.
oneToAnyChannelWithLabel :: MonadCHP m => String -> m (OneToAnyChannel a)Source

A type-constrained version of newChannelWithLabel.

Added in version 1.2.0.

type AnyToOneChannel = Chan Chanin (Shared Chanout)Source
anyToOneChannel :: MonadCHP m => m (AnyToOneChannel a)Source
A type-constrained version of newChannel.
anyToOneChannelWithLabel :: MonadCHP m => String -> m (AnyToOneChannel a)Source

A type-constrained version of newChannelWithLabel.

Added in version 1.2.0.

type AnyToAnyChannel = Chan (Shared Chanin) (Shared Chanout)Source
anyToAnyChannel :: MonadCHP m => m (AnyToAnyChannel a)Source
A type-constrained version of newChannel.
anyToAnyChannelWithLabel :: MonadCHP m => String -> m (AnyToAnyChannel a)Source

A type-constrained version of newChannelWithLabel.

Added in version 1.2.0.

Produced by Haddock version 2.4.2