-- | -- Module : Simulation.Aivika.Dynamics.Interpolate -- Copyright : Copyright (c) 2009-2013, David Sorokin -- License : BSD3 -- Maintainer : David Sorokin -- Stability : experimental -- Tested with: GHC 7.6.3 -- -- This module defines interpolation functions. -- These functions complement the memoization. -- module Simulation.Aivika.Dynamics.Interpolate (discreteDynamics, interpolateDynamics) where import Simulation.Aivika.Internal.Specs import Simulation.Aivika.Internal.Dynamics -- | Discretize the computation in the integration time points. discreteDynamics :: Dynamics a -> Dynamics a {-# INLINE discreteDynamics #-} discreteDynamics (Dynamics m) = Dynamics $ \p -> if pointPhase p == 0 then m p else let sc = pointSpecs p n = pointIteration p in m $ p { pointTime = basicTime sc n 0, pointPhase = 0 } -- | Interpolate the computation based on the integration time points only. -- Unlike the 'discreteDynamics' function it knows about the intermediate -- time points that are used in the Runge-Kutta method. interpolateDynamics :: Dynamics a -> Dynamics a {-# INLINE interpolateDynamics #-} interpolateDynamics (Dynamics m) = Dynamics $ \p -> if pointPhase p >= 0 then m p else let sc = pointSpecs p n = pointIteration p in m $ p { pointTime = basicTime sc n 0, pointPhase = 0 }