| Copyright | Copyright (c) 2016-2017 David Sorokin <david.sorokin@gmail.com> |
|---|---|
| License | BSD3 |
| Maintainer | David Sorokin <david.sorokin@gmail.com> |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell98 |
Simulation.Aivika.Lattice.Estimate
Description
Tested with: GHC 8.0.1
The module defines the Estimate monad transformer which is destined for estimating
computations within lattice nodes. Such computations are separated from the Event
computations. An idea is that the forward-traversing Event computations provide with
something that can be observed, while the Estimate computations estimate the received
information and they can be backward-traversing.
- data Estimate m a
- class EstimateLift t m where
- runEstimateInStartTime :: MonadDES m => Estimate m a -> Simulation m a
- estimateTime :: MonadDES m => Estimate m Double
- foldEstimate :: (a -> a -> Estimate LIO a) -> Estimate LIO a -> Simulation LIO (Estimate LIO a)
- memoEstimate :: (Estimate LIO a -> Estimate LIO a) -> Estimate LIO a -> Simulation LIO (Estimate LIO a)
- estimateUpSide :: Estimate LIO a -> Estimate LIO a
- estimateDownSide :: Estimate LIO a -> Estimate LIO a
- estimateFuture :: Int -> Int -> Estimate LIO a -> Estimate LIO a
- shiftEstimate :: Int -> Int -> Estimate LIO a -> Estimate LIO a
- estimateAt :: Int -> Int -> Estimate LIO a -> Estimate LIO a
- catchEstimate :: (MonadException m, Exception e) => Estimate m a -> (e -> Estimate m a) -> Estimate m a
- finallyEstimate :: MonadException m => Estimate m a -> Estimate m b -> Estimate m a
- throwEstimate :: (MonadException m, Exception e) => e -> Estimate m a
- traceEstimate :: String -> Estimate LIO a -> Estimate LIO a
Estimate Monad
A value in the Estimate monad transformer represents something
that can be estimated within lattice nodes.
Instances
| MonadTrans Estimate Source # | |
| Monad m => ParameterLift Estimate m Source # | |
| Monad m => MonadCompTrans Estimate m Source # | |
| Monad m => EstimateLift Estimate m Source # | |
| Monad m => Monad (Estimate m) Source # | |
| Functor m => Functor (Estimate m) Source # | |
| MonadFix m => MonadFix (Estimate m) Source # | |
| Applicative m => Applicative (Estimate m) Source # | |
| MonadIO m => MonadIO (Estimate m) Source # | |
class EstimateLift t m where Source #
A type class to lift the Estimate computations into other computations.
Minimal complete definition
Methods
liftEstimate :: Estimate m a -> t m a Source #
Lift the specified Estimate computation into another computation.
Instances
| Monad m => EstimateLift Estimate m Source # | |
runEstimateInStartTime :: MonadDES m => Estimate m a -> Simulation m a Source #
Run the Estimate computation in the start time and return the estimate.
estimateTime :: MonadDES m => Estimate m Double Source #
Like time estimates the current modeling time.
It is more effcient than latticeTime.
Computations within Lattice
Arguments
| :: (a -> a -> Estimate LIO a) | reduce in the intermediate nodes of the lattice |
| -> Estimate LIO a | estimate the computation in the final time point and beyond it |
| -> Simulation LIO (Estimate LIO a) |
Fold the estimation of the specified computation.
Arguments
| :: (Estimate LIO a -> Estimate LIO a) | estimate in the intermediate time point of the lattice |
| -> Estimate LIO a | estimate in the final time point of the lattice or beyond it |
| -> Simulation LIO (Estimate LIO a) |
Estimate the computation in the lattice nodes.
estimateUpSide :: Estimate LIO a -> Estimate LIO a Source #
Estimate the computation in the up side node of the lattice,
where latticeTimeIndex is increased by 1 but latticeMemberIndex remains the same.
It is merely equivalent to the following definition:
estimateUpSide = shiftEstimate 1 0
estimateDownSide :: Estimate LIO a -> Estimate LIO a Source #
Estimate the computation in the down side node of the lattice,
where the both latticeTimeIndex and latticeMemberIndex are increased by 1.
It is merely equivalent to the following definition:
estimateDownSide = shiftEstimate 1 1
Arguments
| :: Int | a positive shift of the lattice time index |
| -> Int | a shift of the lattice member index |
| -> Estimate LIO a | the source computation |
| -> Estimate LIO a |
Like shiftEstimate but only the first argument must be possitive.
Arguments
| :: Int | a shift of the lattice time index |
| -> Int | a shift of the lattice member index |
| -> Estimate LIO a | the source computation |
| -> Estimate LIO a |
Estimate the computation in the shifted lattice node, where the first parameter
specifies the latticeTimeIndex shift of any sign, but the second parameter
specifies the latticeMemberIndex shift af any sign too.
It allows looking into the future or past computations. The lattice is constructed in such a way
that we can define the past Estimate computation in terms of the future Estimate
computation. That is the point.
Regarding the Event computation, it is quite different. The future Event computation
depends strongly on the past Event computations. But we can update Ref references within
the corresponding discrete event simulation and then read them within the Estimate
computation, because Ref is Observable.
Arguments
| :: Int | the lattice time index |
| -> Int | the lattice size index |
| -> Estimate LIO a | the computation |
| -> Estimate LIO a |
Estimate the computation at the specified latticeTimeIndex and latticeMemberIndex.
Error Handling
catchEstimate :: (MonadException m, Exception e) => Estimate m a -> (e -> Estimate m a) -> Estimate m a Source #
Exception handling within Estimate computations.
finallyEstimate :: MonadException m => Estimate m a -> Estimate m b -> Estimate m a Source #
A computation with finalization part like the finally function.
throwEstimate :: (MonadException m, Exception e) => e -> Estimate m a Source #
Like the standard throw function.