{-# LANGUAGE TypeFamilies #-}

-- |
-- Module     : Simulation.Aivika.Trans.Internal.Types
-- Copyright  : Copyright (c) 2009-2017, David Sorokin <david.sorokin@gmail.com>
-- License    : BSD3
-- Maintainer : David Sorokin <david.sorokin@gmail.com>
-- Stability  : experimental
-- Tested with: GHC 8.0.1
--
-- It defines the implementation details of some types. You should never
-- use it in ordinary simulation models. The module is destined for those
-- who will extend the library.
--
module Simulation.Aivika.Trans.Internal.Types
       (Specs(..),
        Method(..),
        Run(..),
        Point(..),
        Parameter(..),
        Simulation(..),
        Dynamics(..),
        Event(..),
        EventProcessing(..),
        EventQueueing(..),
        invokeParameter,
        invokeSimulation,
        invokeDynamics,
        invokeEvent) where

import Simulation.Aivika.Trans.Generator

-- | It defines the simulation specs.
data Specs m = Specs { Specs m -> Double
spcStartTime :: Double,    -- ^ the start time
                       Specs m -> Double
spcStopTime :: Double,     -- ^ the stop time
                       Specs m -> Double
spcDT :: Double,           -- ^ the integration time step
                       Specs m -> Method
spcMethod :: Method,       -- ^ the integration method
                       Specs m -> GeneratorType m
spcGeneratorType :: GeneratorType m
                       -- ^ the type of random number generator
                     }

-- | It defines the integration method.
data Method = Euler          -- ^ Euler's method
            | RungeKutta2    -- ^ the 2nd order Runge-Kutta method
            | RungeKutta4    -- ^ the 4th order Runge-Kutta method
            | RungeKutta4b   -- ^ the 4th order Runge-Kutta 3/8-method
            deriving (Method -> Method -> Bool
(Method -> Method -> Bool)
-> (Method -> Method -> Bool) -> Eq Method
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Method -> Method -> Bool
$c/= :: Method -> Method -> Bool
== :: Method -> Method -> Bool
$c== :: Method -> Method -> Bool
Eq, Eq Method
Eq Method
-> (Method -> Method -> Ordering)
-> (Method -> Method -> Bool)
-> (Method -> Method -> Bool)
-> (Method -> Method -> Bool)
-> (Method -> Method -> Bool)
-> (Method -> Method -> Method)
-> (Method -> Method -> Method)
-> Ord Method
Method -> Method -> Bool
Method -> Method -> Ordering
Method -> Method -> Method
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Method -> Method -> Method
$cmin :: Method -> Method -> Method
max :: Method -> Method -> Method
$cmax :: Method -> Method -> Method
>= :: Method -> Method -> Bool
$c>= :: Method -> Method -> Bool
> :: Method -> Method -> Bool
$c> :: Method -> Method -> Bool
<= :: Method -> Method -> Bool
$c<= :: Method -> Method -> Bool
< :: Method -> Method -> Bool
$c< :: Method -> Method -> Bool
compare :: Method -> Method -> Ordering
$ccompare :: Method -> Method -> Ordering
$cp1Ord :: Eq Method
Ord, Int -> Method -> ShowS
[Method] -> ShowS
Method -> String
(Int -> Method -> ShowS)
-> (Method -> String) -> ([Method] -> ShowS) -> Show Method
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Method] -> ShowS
$cshowList :: [Method] -> ShowS
show :: Method -> String
$cshow :: Method -> String
showsPrec :: Int -> Method -> ShowS
$cshowsPrec :: Int -> Method -> ShowS
Show)

-- | It indentifies the simulation run.
data Run m = Run { Run m -> Specs m
runSpecs :: Specs m,            -- ^ the simulation specs
                   Run m -> Int
runIndex :: Int,       -- ^ the current simulation run index
                   Run m -> Int
runCount :: Int,       -- ^ the total number of runs within the experiment
                   Run m -> EventQueue m
runEventQueue :: EventQueue m,  -- ^ the event queue
                   Run m -> Generator m
runGenerator :: Generator m     -- ^ the random number generator
                 }

-- | It defines the simulation point appended with the additional information.
data Point m = Point { Point m -> Specs m
pointSpecs :: Specs m,      -- ^ the simulation specs
                       Point m -> Run m
pointRun :: Run m,          -- ^ the simulation run
                       Point m -> Double
pointTime :: Double,        -- ^ the current time
                       Point m -> Int
pointIteration :: Int,      -- ^ the current iteration
                       Point m -> Int
pointPhase :: Int           -- ^ the current phase
                     }

-- | The 'Parameter' monad that allows specifying the model parameters.
-- For example, they can be used when running the Monte-Carlo simulation.
-- 
-- In general, this monad is very useful for representing a computation which is external
-- relative to the model itself.
newtype Parameter m a = Parameter (Run m -> m a)

-- | A value in the 'Simulation' monad represents a computation
-- within the simulation run.
newtype Simulation m a = Simulation (Run m -> m a)

-- | A value in the 'Dynamics' monad represents a polymorphic time varying function
-- defined in the whole spectrum of time values as a single entity. It is ideal for
-- numerical approximating integrals.
newtype Dynamics m a = Dynamics (Point m -> m a)

-- | A value in the 'Event' monad transformer represents a polymorphic time varying
-- function which is strongly synchronized with the event queue.
newtype Event m a = Event (Point m -> m a)

-- | Invoke the 'Parameter' computation.
invokeParameter :: Run m -> Parameter m a -> m a
{-# INLINE invokeParameter #-}
invokeParameter :: Run m -> Parameter m a -> m a
invokeParameter Run m
r (Parameter Run m -> m a
m) = Run m -> m a
m Run m
r

-- | Invoke the 'Simulation' computation.
invokeSimulation :: Run m -> Simulation m a -> m a
{-# INLINE invokeSimulation #-}
invokeSimulation :: Run m -> Simulation m a -> m a
invokeSimulation Run m
r (Simulation Run m -> m a
m) = Run m -> m a
m Run m
r

-- | Invoke the 'Dynamics' computation.
invokeDynamics :: Point m -> Dynamics m a -> m a
{-# INLINE invokeDynamics #-}
invokeDynamics :: Point m -> Dynamics m a -> m a
invokeDynamics Point m
p (Dynamics Point m -> m a
m) = Point m -> m a
m Point m
p

-- | Invoke the 'Event' computation.
invokeEvent :: Point m -> Event m a -> m a
{-# INLINE invokeEvent #-}
invokeEvent :: Point m -> Event m a -> m a
invokeEvent Point m
p (Event Point m -> m a
m) = Point m -> m a
m Point m
p

-- | Defines how the events are processed.
data EventProcessing = CurrentEvents
                       -- ^ either process all earlier and then current events,
                       -- or raise an error if the current simulation time is less
                       -- than the actual time of the event queue (safe within
                       -- the 'Event' computation as this is protected by the type system)
                     | EarlierEvents
                       -- ^ either process all earlier events not affecting
                       -- the events at the current simulation time,
                       -- or raise an error if the current simulation time is less
                       -- than the actual time of the event queue (safe within
                       -- the 'Event' computation as this is protected by the type system)
                     | CurrentEventsOrFromPast
                       -- ^ either process all earlier and then current events,
                       -- or do nothing if the current simulation time is less
                       -- than the actual time of the event queue
                       -- (do not use unless the documentation states the opposite)
                     | EarlierEventsOrFromPast
                       -- ^ either process all earlier events,
                       -- or do nothing if the current simulation time is less
                       -- than the actual time of the event queue
                       -- (do not use unless the documentation states the opposite)
                     deriving (EventProcessing -> EventProcessing -> Bool
(EventProcessing -> EventProcessing -> Bool)
-> (EventProcessing -> EventProcessing -> Bool)
-> Eq EventProcessing
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventProcessing -> EventProcessing -> Bool
$c/= :: EventProcessing -> EventProcessing -> Bool
== :: EventProcessing -> EventProcessing -> Bool
$c== :: EventProcessing -> EventProcessing -> Bool
Eq, Eq EventProcessing
Eq EventProcessing
-> (EventProcessing -> EventProcessing -> Ordering)
-> (EventProcessing -> EventProcessing -> Bool)
-> (EventProcessing -> EventProcessing -> Bool)
-> (EventProcessing -> EventProcessing -> Bool)
-> (EventProcessing -> EventProcessing -> Bool)
-> (EventProcessing -> EventProcessing -> EventProcessing)
-> (EventProcessing -> EventProcessing -> EventProcessing)
-> Ord EventProcessing
EventProcessing -> EventProcessing -> Bool
EventProcessing -> EventProcessing -> Ordering
EventProcessing -> EventProcessing -> EventProcessing
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EventProcessing -> EventProcessing -> EventProcessing
$cmin :: EventProcessing -> EventProcessing -> EventProcessing
max :: EventProcessing -> EventProcessing -> EventProcessing
$cmax :: EventProcessing -> EventProcessing -> EventProcessing
>= :: EventProcessing -> EventProcessing -> Bool
$c>= :: EventProcessing -> EventProcessing -> Bool
> :: EventProcessing -> EventProcessing -> Bool
$c> :: EventProcessing -> EventProcessing -> Bool
<= :: EventProcessing -> EventProcessing -> Bool
$c<= :: EventProcessing -> EventProcessing -> Bool
< :: EventProcessing -> EventProcessing -> Bool
$c< :: EventProcessing -> EventProcessing -> Bool
compare :: EventProcessing -> EventProcessing -> Ordering
$ccompare :: EventProcessing -> EventProcessing -> Ordering
$cp1Ord :: Eq EventProcessing
Ord, Int -> EventProcessing -> ShowS
[EventProcessing] -> ShowS
EventProcessing -> String
(Int -> EventProcessing -> ShowS)
-> (EventProcessing -> String)
-> ([EventProcessing] -> ShowS)
-> Show EventProcessing
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EventProcessing] -> ShowS
$cshowList :: [EventProcessing] -> ShowS
show :: EventProcessing -> String
$cshow :: EventProcessing -> String
showsPrec :: Int -> EventProcessing -> ShowS
$cshowsPrec :: Int -> EventProcessing -> ShowS
Show)

-- | A type class of monads that allow enqueueing the events.
class EventQueueing m where

  -- | It represents the event queue.
  data EventQueue m :: *

  -- | Create a new event queue by the specified specs with simulation session.
  newEventQueue :: Specs m -> m (EventQueue m)

  -- | Enqueue the event which must be actuated at the specified time.
  enqueueEvent :: Double -> Event m () -> Event m ()

  -- | Run the 'EventT' computation in the current simulation time
  -- within the 'DynamicsT' computation involving all pending
  -- 'CurrentEvents' in the processing too.
  runEvent :: Event m a -> Dynamics m a
  {-# INLINE runEvent #-}
  runEvent = EventProcessing -> Event m a -> Dynamics m a
forall (m :: * -> *) a.
EventQueueing m =>
EventProcessing -> Event m a -> Dynamics m a
runEventWith EventProcessing
CurrentEvents

  -- | Run the 'EventT' computation in the current simulation time
  -- within the 'DynamicsT' computation specifying what pending events 
  -- should be involved in the processing.
  runEventWith :: EventProcessing -> Event m a -> Dynamics m a

  -- | Return the number of pending events that should
  -- be yet actuated.
  eventQueueCount :: Event m Int