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.State

Contents

Description

 

Synopsis

Documentation

data AsyncState s Source #

Internal state of asynchronious core module

s
- state of next module, they are chained until bottom, that is usually an empty data type.

Instances

Generic (AsyncState s) Source # 

Associated Types

type Rep (AsyncState s) :: * -> * #

Methods

from :: AsyncState s -> Rep (AsyncState s) x #

to :: Rep (AsyncState s) x -> AsyncState s #

NFData s => NFData (AsyncState s) Source # 

Methods

rnf :: AsyncState s -> () #

Monad m => MonadState (AsyncState s) (AsyncT s m) 

Methods

get :: AsyncT s m (AsyncState s)

put :: AsyncState s -> AsyncT s m ()

state :: (AsyncState s -> (a, AsyncState s)) -> AsyncT s m a

type Rep (AsyncState s) Source # 
type Rep (AsyncState s) = D1 (MetaData "AsyncState" "Game.GoreAndAsh.Async.State" "gore-and-ash-async-1.1.1.0-2OVkZlWWiw2AoycryFpZ3T" False) (C1 (MetaCons "AsyncState" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "asyncAValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 AsyncValueMap)) (S1 (MetaSel (Just Symbol "asyncScheduled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SyncSheduled))) ((:*:) (S1 (MetaSel (Just Symbol "asyncSValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SyncFinished)) ((:*:) (S1 (MetaSel (Just Symbol "asyncNextId") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int)) (S1 (MetaSel (Just Symbol "asyncNextState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 s))))))

emptyAsyncState :: s -> AsyncState s Source #

Create inital async state

s
- state of next module

Async helpers

newtype AsyncId Source #

Id of async value, it is used to poll info about the value

Constructors

AsyncId 

Fields

Instances

Eq AsyncId Source # 

Methods

(==) :: AsyncId -> AsyncId -> Bool #

(/=) :: AsyncId -> AsyncId -> Bool #

Show AsyncId Source # 
Generic AsyncId Source # 

Associated Types

type Rep AsyncId :: * -> * #

Methods

from :: AsyncId -> Rep AsyncId x #

to :: Rep AsyncId x -> AsyncId #

NFData AsyncId Source # 

Methods

rnf :: AsyncId -> () #

Hashable AsyncId Source # 

Methods

hashWithSalt :: Int -> AsyncId -> Int

hash :: AsyncId -> Int

type Rep AsyncId Source # 
type Rep AsyncId = D1 (MetaData "AsyncId" "Game.GoreAndAsh.Async.State" "gore-and-ash-async-1.1.1.0-2OVkZlWWiw2AoycryFpZ3T" True) (C1 (MetaCons "AsyncId" PrefixI True) (S1 (MetaSel (Just Symbol "unAsyncId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

type AsyncValueMap = HashMap AsyncId (Either (Async Dynamic) (Either SomeException Dynamic)) Source #

Container for async values

registerAsyncValue :: Typeable a => Async a -> AsyncState s -> (AsyncId, AsyncState s) Source #

Put async value into internal state

getFinishedAsyncValue :: AsyncId -> AsyncState s -> Maybe (Maybe (Either SomeException Dynamic)) Source #

Try to get value of given async value

Note: first Maybe layer is test for existense of given async value

Note: second Maybe layer is test is the value is finished

cancelAsyncValue :: AsyncId -> AsyncState s -> (Maybe (Async Dynamic), AsyncState s) Source #

Unregister given id and return stored async

purgeAsyncs :: AsyncState s -> AsyncState s Source #

Deletes calculated values

Sync helpers

newtype SyncId Source #

Id of sync value, it is used to identify return value

Constructors

SyncId 

Fields

Instances

Eq SyncId Source # 

Methods

(==) :: SyncId -> SyncId -> Bool #

(/=) :: SyncId -> SyncId -> Bool #

Ord SyncId Source # 
Show SyncId Source # 
Generic SyncId Source # 

Associated Types

type Rep SyncId :: * -> * #

Methods

from :: SyncId -> Rep SyncId x #

to :: Rep SyncId x -> SyncId #

NFData SyncId Source # 

Methods

rnf :: SyncId -> () #

Hashable SyncId Source # 

Methods

hashWithSalt :: Int -> SyncId -> Int

hash :: SyncId -> Int

type Rep SyncId Source # 
type Rep SyncId = D1 (MetaData "SyncId" "Game.GoreAndAsh.Async.State" "gore-and-ash-async-1.1.1.0-2OVkZlWWiw2AoycryFpZ3T" True) (C1 (MetaCons "SyncId" PrefixI True) (S1 (MetaSel (Just Symbol "unSyncId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

type SyncSheduled = Seq (SyncId, IO Dynamic) Source #

Container for scheduled sync values

type SyncFinished = HashMap SyncId (Either SomeException Dynamic) Source #

Container for finished sync values

registerSyncValue :: Typeable a => IO a -> AsyncState s -> (SyncId, AsyncState s) Source #

Put sync value into internal state

getFinishedSyncValue :: SyncId -> AsyncState s -> Maybe (Either SomeException Dynamic) Source #

Try to get value of given sync value

Note: first Maybe layer is test for existense of given async value

cancelSyncValue :: SyncId -> AsyncState s -> AsyncState s Source #

Unregister given sheduled sync action

purgeSyncs :: AsyncState s -> AsyncState s Source #

Deletes calculated values