module Simulation.Aivika.Trans.Internal.Specs
(Specs(..),
Method(..),
Run(..),
Point(..),
Parameter(..),
Simulation(..),
Dynamics(..),
Event(..),
EventProcessing(..),
EventQueueing(..),
invokeParameter,
invokeSimulation,
invokeDynamics,
invokeEvent,
basicTime,
integIterationBnds,
integIterationHiBnd,
integIterationLoBnd,
integPhaseBnds,
integPhaseHiBnd,
integPhaseLoBnd,
integTimes,
integPoints,
integStartPoint,
integStopPoint,
pointAt) where
import Simulation.Aivika.Trans.Session
import Simulation.Aivika.Trans.Generator
data Specs m = Specs { spcStartTime :: Double,
spcStopTime :: Double,
spcDT :: Double,
spcMethod :: Method,
spcGeneratorType :: GeneratorType m
}
data Method = Euler
| RungeKutta2
| RungeKutta4
deriving (Eq, Ord, Show)
data Run m = Run { runSpecs :: Specs m,
runSession :: Session m,
runIndex :: Int,
runCount :: Int,
runEventQueue :: EventQueue m,
runGenerator :: Generator m
}
data Point m = Point { pointSpecs :: Specs m,
pointRun :: Run m,
pointTime :: Double,
pointIteration :: Int,
pointPhase :: Int
}
newtype Parameter m a = Parameter (Run m -> m a)
newtype Simulation m a = Simulation (Run m -> m a)
newtype Dynamics m a = Dynamics (Point m -> m a)
newtype Event m a = Event (Point m -> m a)
invokeParameter :: Run m -> Parameter m a -> m a
invokeParameter r (Parameter m) = m r
invokeSimulation :: Run m -> Simulation m a -> m a
invokeSimulation r (Simulation m) = m r
invokeDynamics :: Point m -> Dynamics m a -> m a
invokeDynamics p (Dynamics m) = m p
invokeEvent :: Point m -> Event m a -> m a
invokeEvent p (Event m) = m p
data EventProcessing = CurrentEvents
| EarlierEvents
| CurrentEventsOrFromPast
| EarlierEventsOrFromPast
deriving (Eq, Ord, Show)
class EventQueueing m where
data EventQueue m :: *
newEventQueue :: Session m -> Specs m -> m (EventQueue m)
enqueueEvent :: Double -> Event m () -> Event m ()
runEvent :: Event m a -> Dynamics m a
runEvent = runEventWith CurrentEvents
runEventWith :: EventProcessing -> Event m a -> Dynamics m a
eventQueueCount :: Event m Int
integIterations :: Specs m -> [Int]
integIterations sc = [i1 .. i2] where
i1 = integIterationLoBnd sc
i2 = integIterationHiBnd sc
integIterationBnds :: Specs m -> (Int, Int)
integIterationBnds sc = (i1, i2) where
i1 = integIterationLoBnd sc
i2 = integIterationHiBnd sc
integIterationLoBnd :: Specs m -> Int
integIterationLoBnd sc = 0
integIterationHiBnd :: Specs m -> Int
integIterationHiBnd sc =
let n = round ((spcStopTime sc
spcStartTime sc) / spcDT sc)
in if n < 0
then
error $
"Either the simulation specs are incorrect, " ++
"or a step time is too small, because of which " ++
"a floating point overflow occurred on 32-bit Haskell implementation."
else n
integPhases :: Specs m -> [Int]
integPhases sc =
case spcMethod sc of
Euler -> [0]
RungeKutta2 -> [0, 1]
RungeKutta4 -> [0, 1, 2, 3]
integPhaseBnds :: Specs m -> (Int, Int)
integPhaseBnds sc =
case spcMethod sc of
Euler -> (0, 0)
RungeKutta2 -> (0, 1)
RungeKutta4 -> (0, 3)
integPhaseLoBnd :: Specs m -> Int
integPhaseLoBnd sc = 0
integPhaseHiBnd :: Specs m -> Int
integPhaseHiBnd sc =
case spcMethod sc of
Euler -> 0
RungeKutta2 -> 1
RungeKutta4 -> 3
basicTime :: Specs m -> Int -> Int -> Double
basicTime sc n ph =
if ph < 0 then
error "Incorrect phase: basicTime"
else
spcStartTime sc + n' * spcDT sc + delta (spcMethod sc) ph
where n' = fromIntegral n
delta Euler 0 = 0
delta RungeKutta2 0 = 0
delta RungeKutta2 1 = spcDT sc
delta RungeKutta4 0 = 0
delta RungeKutta4 1 = spcDT sc / 2
delta RungeKutta4 2 = spcDT sc / 2
delta RungeKutta4 3 = spcDT sc
integTimes :: Specs m -> [Double]
integTimes sc = map t [nl .. nu]
where (nl, nu) = integIterationBnds sc
t n = basicTime sc n 0
integPoints :: Run m -> [Point m]
integPoints r = points
where sc = runSpecs r
(nl, nu) = integIterationBnds sc
points = map point [nl .. nu]
point n = Point { pointSpecs = sc,
pointRun = r,
pointTime = basicTime sc n 0,
pointIteration = n,
pointPhase = 0 }
integStartPoint :: Run m -> Point m
integStartPoint r = point nl
where sc = runSpecs r
(nl, nu) = integIterationBnds sc
point n = Point { pointSpecs = sc,
pointRun = r,
pointTime = basicTime sc n 0,
pointIteration = n,
pointPhase = 0 }
integStopPoint :: Run m -> Point m
integStopPoint r = point nu
where sc = runSpecs r
(nl, nu) = integIterationBnds sc
point n = Point { pointSpecs = sc,
pointRun = r,
pointTime = basicTime sc n 0,
pointIteration = n,
pointPhase = 0 }
pointAt :: Run m -> Double -> Point m
pointAt r t = p
where sc = runSpecs r
t0 = spcStartTime sc
dt = spcDT sc
n = fromIntegral $ floor ((t t0) / dt)
p = Point { pointSpecs = sc,
pointRun = r,
pointTime = t,
pointIteration = n,
pointPhase = 1 }