gore-and-ash-async-1.1.1.0: Core module for Gore&Ash engine that embeds async IO actions into game loop.

Copyright(c) Anton Gushcha, 2016
LicenseBSD3
Maintainerncrashed@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Game.GoreAndAsh.Async.API

Contents

Description

 

Synopsis

Monadic API

class (MonadIO m, MonadThrow m) => MonadAsync m where Source #

Low level monadic API for module.

Note: does not require m to be IO monad.

Methods

asyncActionM :: Typeable a => IO a -> m AsyncId Source #

Start execution of IO action concurrently and return its id

asyncActionBoundM :: Typeable a => IO a -> m AsyncId Source #

Start execution of IO action concurrently and return its id

Note: forks thread within same OS thread.

asyncPollM :: Typeable a => AsyncId -> m (Maybe (Either SomeException a)) Source #

Check state of concurrent value

Could throw MonadAsyncExcepion, AsyncWrongType and AsyncNotFound constructors.

asyncCancelM :: AsyncId -> m () Source #

Stops given async execution

asyncSyncActionM :: Typeable a => IO a -> m SyncId Source #

Schedule action to be executed at the end of frame.

Use asyncSyncPollM to get result at next frame.

Note: order of IO actions is preserved.

asyncSyncPollM :: Typeable a => SyncId -> m (Maybe (Either SomeException a)) Source #

Fires when given synchronious action is completed (at next frame after scheduling)

Could throw MonadAsyncExcepion, SyncWrongType constructor.

asyncSyncCanceM :: SyncId -> m () Source #

Unshedule given action from execution

Actually you can unshedule it until end of frame when corresponding asyncSyncActionM was called.

data MonadAsyncExcepion Source #

Exception of the async monadic API

Constructors

AsyncWrongType TypeRep TypeRep

Expected type doesn't match stored in async value

AsyncNotFound AsyncId

There is no async value with the id

SyncWrongType TypeRep TypeRep

Expected type doesn't match stored in sync value

Instances

Show MonadAsyncExcepion Source # 
Generic MonadAsyncExcepion Source # 
Exception MonadAsyncExcepion Source # 
NFData MonadAsyncExcepion Source # 

Methods

rnf :: MonadAsyncExcepion -> () #

type Rep MonadAsyncExcepion Source # 

Arrow API

Not bounded async

asyncAction :: (MonadAsync m, Typeable a) => IO a -> GameWire m b (Event a) Source #

Execute given IO action concurrently. Event fires once when the action is finished. Exceptions are rethrown into main thread.

asyncActionC :: (MonadAsync m, Typeable a) => IO a -> GameWire m (Event b) (Event a) Source #

Execute given IO action concurrently. Event fires once when the action is finished. Exceptions are rethrown into main thread.

The concurrent action can be canceled by input event.

asyncActionEx :: (MonadAsync m, Typeable a) => IO a -> GameWire m b (Event (Either SomeException a)) Source #

Execute given IO action concurrently.

Event fires once when the action is finished. Exceptions in the concurrent action are returned in event payload.

asyncActionExC :: (MonadAsync m, Typeable a) => IO a -> GameWire m (Event b) (Event (Either SomeException a)) Source #

Execute given IO action concurrently.

Event fires once when the action is finished. Exceptions in the concurrent action are returned in event payload.

The concurrent action can be canceled by input event.

asyncActionFactory :: (MonadAsync m, Typeable a) => GameWire m (Event (Seq (IO a))) (Event (Seq a)) Source #

Wire that executes incoming IO actions concurrently and then produces events with results once for each action.

Exceptions are rethrown into main thread.

asyncActionFactoryEx :: (MonadAsync m, Typeable a) => GameWire m (Event (Seq (IO a))) (Event (Seq (Either SomeException a))) Source #

Wire that executes incoming IO actions concurrently and then produces events with results once for each action.

Exceptions are returned in event payload.

Bounded async

asyncActionBound :: (MonadAsync m, Typeable a) => IO a -> GameWire m b (Event a) Source #

Execute given IO action concurrently. Event fires once when the action is finished. Exceptions are rethrown into main thread.

Note: forks thread within same OS thread.

asyncActionBoundC :: (MonadAsync m, Typeable a) => IO a -> GameWire m (Event b) (Event a) Source #

Execute given IO action concurrently. Event fires once when the action is finished. Exceptions are rethrown into main thread.

The concurrent action can be canceled by input event.

Note: forks thread within same OS thread.

asyncActionBoundEx :: (MonadAsync m, Typeable a) => IO a -> GameWire m b (Event (Either SomeException a)) Source #

Execute given IO action concurrently.

Event fires once when the action is finished. Exceptions in the concurrent action are returned in event payload.

Note: forks thread within same OS thread.

asyncActionBoundExC :: (MonadAsync m, Typeable a) => IO a -> GameWire m (Event b) (Event (Either SomeException a)) Source #

Execute given IO action concurrently.

Event fires once when the action is finished. Exceptions in the concurrent action are returned in event payload.

The concurrent action can be canceled by input event.

Note: forks thread within same OS thread.`

asyncActionBoundFactory :: (MonadAsync m, Typeable a) => GameWire m (Event (Seq (IO a))) (Event (Seq a)) Source #

Wire that executes incoming IO actions concurrently and then produces events with results once for each action.

Exceptions are rethrown into main thread.

Note: forks thread within same OS thread.

asyncActionBoundFactoryEx :: (MonadAsync m, Typeable a) => GameWire m (Event (Seq (IO a))) (Event (Seq (Either SomeException a))) Source #

Wire that executes incoming IO actions concurrently and then produces events with results once for each action.

Exceptions are returned in event payload.

Note: forks thread within same OS thread.

Sync actions

asyncSyncAction :: (MonadAsync m, Typeable a) => IO a -> GameWire m b (Event a) Source #

Execute given IO action at end of current frame. Event fires once at next frame.

Exceptions are rethrown into main thread.

asyncSyncActionEx :: (MonadAsync m, Typeable a) => IO a -> GameWire m b (Event (Either SomeException a)) Source #

Execute given IO action at end of current frame. Event fires once at next frame.

Exceptions are returned in event payload.

asyncSyncActionC :: (MonadAsync m, Typeable a) => IO a -> GameWire m (Event b) (Event a) Source #

Execute given IO action at end of current frame. Event fires once at next frame.

Exceptions are rethrown into main thread.

Action can be canceled with input event, although you have only the frame to do this.

asyncSyncActionExC :: (MonadAsync m, Typeable a) => IO a -> GameWire m (Event b) (Event (Either SomeException a)) Source #

Execute given IO action at end of current frame. Event fires once at next frame.

Exceptions are rethrown into main thread.

Action can be canceled with input event, although you have only the frame to do this.

asyncSyncActionFactory :: forall m a. (MonadAsync m, Typeable a) => GameWire m (Event (Seq (IO a))) (Event (Seq a)) Source #

Wire that executes incoming IO actions at end of current frame and then produces events with results once for each action.

Exceptions are rethrown into main thread.

asyncSyncActionFactoryEx :: forall m a. (MonadAsync m, Typeable a) => GameWire m (Event (Seq (IO a))) (Event (Seq (Either SomeException a))) Source #

Wire that executes incoming IO actions at end of current frame and then produces events with results once for each action.

Exceptions are rethrown into main thread.