aivika-lattice-0.6.2: Nested discrete event simulation module for the Aivika library using lattice
CopyrightCopyright (c) 2016-2017 David Sorokin <david.sorokin@gmail.com>
LicenseBSD3
MaintainerDavid Sorokin <david.sorokin@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Simulation.Aivika.Lattice.LIO

Description

Tested with: GHC 7.10.3

This module defines LIO as an instance of the MonadDES and EventIOQueueing type classes.

Synopsis

Documentation

data LIO a Source #

The LIO computation that can be run as nested one on the lattice node.

Instances

Instances details
Monad LIO Source # 
Instance details

Defined in Simulation.Aivika.Lattice.Internal.LIO

Methods

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

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

return :: a -> LIO a #

Functor LIO Source # 
Instance details

Defined in Simulation.Aivika.Lattice.Internal.LIO

Methods

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

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

MonadFix LIO Source # 
Instance details

Defined in Simulation.Aivika.Lattice.Internal.LIO

Methods

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

Applicative LIO Source # 
Instance details

Defined in Simulation.Aivika.Lattice.Internal.LIO

Methods

pure :: a -> LIO a #

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

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

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

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

EventIOQueueing LIO Source #

An implementation of the EventIOQueueing type class.

Instance details

Defined in Simulation.Aivika.Lattice.LIO

Methods

enqueueEventIO :: Double -> Event LIO () -> Event LIO () #

MonadDES LIO Source # 
Instance details

Defined in Simulation.Aivika.Lattice.LIO

MonadRef LIO Source #

The implementation of mutable references.

Instance details

Defined in Simulation.Aivika.Lattice.Ref.Base.Strict

Associated Types

data Ref LIO a #

Methods

newRef :: a -> Simulation LIO (Ref LIO a) #

readRef :: Ref LIO a -> Event LIO a #

writeRef :: Ref LIO a -> a -> Event LIO () #

modifyRef :: Ref LIO a -> (a -> a) -> Event LIO () #

equalRef :: Ref LIO a -> Ref LIO a -> Bool #

MonadRef0 LIO Source #

A subtype of mutable references that can be created under more weak conditions.

Instance details

Defined in Simulation.Aivika.Lattice.Ref.Base.Strict

Methods

newRef0 :: a -> LIO (Ref LIO a) #

MonadRef LIO Source #

The implementation of mutable references.

Instance details

Defined in Simulation.Aivika.Lattice.Ref.Base.Lazy

Associated Types

data Ref LIO a #

Methods

newRef :: a -> Simulation LIO (Ref LIO a) #

readRef :: Ref LIO a -> Event LIO a #

writeRef :: Ref LIO a -> a -> Event LIO () #

modifyRef :: Ref LIO a -> (a -> a) -> Event LIO () #

equalRef :: Ref LIO a -> Ref LIO a -> Bool #

MonadRef0 LIO Source #

A subtype of mutable references that can be created under more weak conditions.

Instance details

Defined in Simulation.Aivika.Lattice.Ref.Base.Lazy

Methods

newRef0 :: a -> LIO (Ref LIO a) #

MonadComp LIO Source # 
Instance details

Defined in Simulation.Aivika.Lattice.LIO

EventQueueing LIO Source #

An implementation of the EventQueueing type class.

Instance details

Defined in Simulation.Aivika.Lattice.Internal.Event

Associated Types

data EventQueue LIO #

MonadGenerator LIO Source # 
Instance details

Defined in Simulation.Aivika.Lattice.Generator

Associated Types

data Generator LIO #

MonadException LIO Source # 
Instance details

Defined in Simulation.Aivika.Lattice.Internal.LIO

Methods

catchComp :: Exception e => LIO a -> (e -> LIO a) -> LIO a #

finallyComp :: LIO a -> LIO b -> LIO a #

throwComp :: Exception e => e -> LIO a #

MonadIO LIO Source # 
Instance details

Defined in Simulation.Aivika.Lattice.Internal.LIO

Methods

liftIO :: IO a -> LIO a #

QueueStrategy LIO FCFS Source #

An implementation of the FCFS queue strategy.

Instance details

Defined in Simulation.Aivika.Lattice.QueueStrategy

Associated Types

data StrategyQueue LIO FCFS :: Type -> Type #

QueueStrategy LIO LCFS Source #

An implementation of the LCFS queue strategy.

Instance details

Defined in Simulation.Aivika.Lattice.QueueStrategy

Associated Types

data StrategyQueue LIO LCFS :: Type -> Type #

DequeueStrategy LIO FCFS Source #

An implementation of the FCFS queue strategy.

Instance details

Defined in Simulation.Aivika.Lattice.QueueStrategy

DequeueStrategy LIO LCFS Source #

An implementation of the LCFS queue strategy.

Instance details

Defined in Simulation.Aivika.Lattice.QueueStrategy

EnqueueStrategy LIO FCFS Source #

An implementation of the FCFS queue strategy.

Instance details

Defined in Simulation.Aivika.Lattice.QueueStrategy

EnqueueStrategy LIO LCFS Source #

An implementation of the LCFS queue strategy.

Instance details

Defined in Simulation.Aivika.Lattice.QueueStrategy

Observable (Ref LIO) (Estimate LIO) Source #

An instance of the specified type class.

Instance details

Defined in Simulation.Aivika.Lattice.Ref.Base.Strict

Methods

readObservable :: Ref LIO a -> Estimate LIO a #

Observable (Ref LIO) (Estimate LIO) Source #

An instance of the specified type class.

Instance details

Defined in Simulation.Aivika.Lattice.Ref.Base.Lazy

Methods

readObservable :: Ref LIO a -> Estimate LIO a #

newtype Ref LIO a Source # 
Instance details

Defined in Simulation.Aivika.Lattice.Ref.Base.Strict

newtype Ref LIO a = Ref {}
newtype Ref LIO a Source # 
Instance details

Defined in Simulation.Aivika.Lattice.Ref.Base.Lazy

newtype Ref LIO a = Ref {}
data EventQueue LIO Source # 
Instance details

Defined in Simulation.Aivika.Lattice.Internal.Event

data Generator LIO Source # 
Instance details

Defined in Simulation.Aivika.Lattice.Generator

newtype StrategyQueue LIO FCFS a Source # 
Instance details

Defined in Simulation.Aivika.Lattice.QueueStrategy

newtype StrategyQueue LIO LCFS a Source # 
Instance details

Defined in Simulation.Aivika.Lattice.QueueStrategy

data LIOLattice Source #

Specifies the lattice.

lattice Source #

Arguments

:: Int

the lattice size

-> (Int -> Int -> Int)

get the parent member index by the specified time and member indices

-> LIOLattice 

Return a lattice by the specifed size and the parent member function.

newRandomLattice :: Int -> IO LIOLattice Source #

Create a new random lattice by the specified size with equal probabilities, whether the interior child node derives from the left or right parents.

newRandomLatticeWithProb :: Double -> Int -> IO LIOLattice Source #

Create a new random lattice by the specified probability and size, where the probability defines whether the interior child node derives from the right parent.

runLIO :: LIOLattice -> LIO a -> IO a Source #

Run the LIO computation using the specified lattice.

latticeTimeIndex :: LIO Int Source #

Return the lattice time index starting from 0. The index should be less than or equaled to latticeSize.

latticeMemberIndex :: LIO Int Source #

Return the lattice member index starting from 0. It is always less than or equaled to latticeTimeIndex.

latticeParentMemberIndex :: LIO (Maybe Int) Source #

Return the parent member index starting from 0 for non-root lattice nodes.

latticeSize :: LIO Int Source #

Return the lattice size.

latticeTime :: Parameter LIO Double Source #

Return the time for the current lattice node.

latticeTimes :: Parameter LIO [Double] Source #

Return the time values in the lattice nodes.

latticeTimeStep :: Parameter LIO Double Source #

Return the lattice time step.

findLatticeTimeIndex :: Double -> Parameter LIO Int Source #

Find the lattice time index by the specified modeling time.

enqueueEventWithLatticeTimes :: Event LIO () -> Event LIO () Source #

Actuate the event handler in the lattice node time points.

Orphan instances

EventIOQueueing LIO Source #

An implementation of the EventIOQueueing type class.

Instance details

Methods

enqueueEventIO :: Double -> Event LIO () -> Event LIO () #

MonadDES LIO Source # 
Instance details

MonadComp LIO Source # 
Instance details