-- |
-- Module     : Simulation.Aivika.Results.IO
-- 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
--
-- The module allows printing and converting the 'Simulation' 'Results' to a 'String'.
--
module Simulation.Aivika.Results.IO
       (-- * Basic Types
        ResultSourcePrint,
        ResultSourceShowS,
        -- * Printing the Results
        printResultsWithTime,
        printResultsInStartTime,
        printResultsInStopTime,
        printResultsInIntegTimes,
        printResultsInTime,
        printResultsInTimes,
        -- * Simulating and Printing the Results
        printSimulationResultsInStartTime,
        printSimulationResultsInStopTime,
        printSimulationResultsInIntegTimes,
        printSimulationResultsInTime,
        printSimulationResultsInTimes,
        -- * Showing the Results
        showResultsWithTime,
        showResultsInStartTime,
        showResultsInStopTime,
        showResultsInIntegTimes,
        showResultsInTime,
        showResultsInTimes,
        -- * Simulating and Showing the Results
        showSimulationResultsInStartTime,
        showSimulationResultsInStopTime,
        showSimulationResultsInIntegTimes,
        showSimulationResultsInTime,
        showSimulationResultsInTimes,
        -- * Printing the Result Source
        hPrintResultSourceIndented,
        hPrintResultSource,
        hPrintResultSourceInRussian,
        hPrintResultSourceInEnglish,
        printResultSourceIndented,
        printResultSource,
        printResultSourceInRussian,
        printResultSourceInEnglish,
        -- * Showing the Result Source
        showResultSourceIndented,
        showResultSource,
        showResultSourceInRussian,
        showResultSourceInEnglish) where

import Control.Monad
import Control.Monad.Trans

import qualified Data.Map as M
import qualified Data.Array as A

import System.IO

import Simulation.Aivika.Specs
import Simulation.Aivika.Simulation
import Simulation.Aivika.Dynamics
import Simulation.Aivika.Event
import Simulation.Aivika.Results
import Simulation.Aivika.Results.Locale

-- | This is a function that shows the simulation results within
-- the 'Event' computation synchronized with the event queue.
type ResultSourceShowS = ResultSource -> Event ShowS

-- | This is a function that prints the simulation results within
-- the 'Event' computation synchronized with the event queue.
type ResultSourcePrint = ResultSource -> Event ()

-- | Print a localised text representation of the results by the specified source
-- and with the given indent.
hPrintResultSourceIndented :: Handle
                              -- ^ a handle
                              -> Int
                              -- ^ an indent
                              -> ResultLocalisation
                              -- ^ a localisation
                              -> ResultSourcePrint
hPrintResultSourceIndented :: Handle -> Int -> ResultLocalisation -> ResultSourcePrint
hPrintResultSourceIndented Handle
h Int
indent ResultLocalisation
loc source :: ResultSource
source@(ResultItemSource (ResultItem a
x)) =
  Handle
-> Int -> ResultName -> ResultLocalisation -> ResultSourcePrint
hPrintResultSourceIndentedLabelled Handle
h Int
indent (a -> ResultName
forall a. ResultItemable a => a -> ResultName
resultItemName a
x) ResultLocalisation
loc ResultSource
source
hPrintResultSourceIndented Handle
h Int
indent ResultLocalisation
loc source :: ResultSource
source@(ResultVectorSource ResultVector
x) =
  Handle
-> Int -> ResultName -> ResultLocalisation -> ResultSourcePrint
hPrintResultSourceIndentedLabelled Handle
h Int
indent (ResultVector -> ResultName
resultVectorName ResultVector
x) ResultLocalisation
loc ResultSource
source
hPrintResultSourceIndented Handle
h Int
indent ResultLocalisation
loc source :: ResultSource
source@(ResultObjectSource ResultObject
x) =
  Handle
-> Int -> ResultName -> ResultLocalisation -> ResultSourcePrint
hPrintResultSourceIndentedLabelled Handle
h Int
indent (ResultObject -> ResultName
resultObjectName ResultObject
x) ResultLocalisation
loc ResultSource
source
hPrintResultSourceIndented Handle
h Int
indent ResultLocalisation
loc source :: ResultSource
source@(ResultSeparatorSource ResultSeparator
x) =
  Handle
-> Int -> ResultName -> ResultLocalisation -> ResultSourcePrint
hPrintResultSourceIndentedLabelled Handle
h Int
indent (ResultSeparator -> ResultName
resultSeparatorText ResultSeparator
x) ResultLocalisation
loc ResultSource
source

-- | Print an indented and labelled text representation of the results by
-- the specified source.
hPrintResultSourceIndentedLabelled :: Handle
                                      -- ^ a handle
                                      -> Int
                                      -- ^ an indent
                                      -> ResultName
                                      -- ^ a label
                                      -> ResultLocalisation
                                      -- ^ a localisation
                                      -> ResultSourcePrint
hPrintResultSourceIndentedLabelled :: Handle
-> Int -> ResultName -> ResultLocalisation -> ResultSourcePrint
hPrintResultSourceIndentedLabelled Handle
h Int
indent ResultName
label ResultLocalisation
loc (ResultItemSource (ResultItem a
x)) =
  do ResultName
a <- ResultValue ResultName -> ResultData ResultName
forall e. ResultValue e -> ResultData e
resultValueData (ResultValue ResultName -> ResultData ResultName)
-> ResultValue ResultName -> ResultData ResultName
forall a b. (a -> b) -> a -> b
$ a -> ResultValue ResultName
forall a. ResultItemable a => a -> ResultValue ResultName
resultItemToStringValue a
x
     let tab :: ResultName
tab = Int -> Char -> ResultName
forall a. Int -> a -> [a]
replicate Int
indent Char
' '
     IO () -> Event ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Event ()) -> IO () -> Event ()
forall a b. (a -> b) -> a -> b
$
       do Handle -> ResultName -> IO ()
hPutStr Handle
h ResultName
tab
          Handle -> ResultName -> IO ()
hPutStr Handle
h ResultName
"-- "
          Handle -> ResultName -> IO ()
hPutStr Handle
h (ResultLocalisation -> ResultId -> ResultName
localiseResultDescription ResultLocalisation
loc (ResultId -> ResultName) -> ResultId -> ResultName
forall a b. (a -> b) -> a -> b
$ a -> ResultId
forall a. ResultItemable a => a -> ResultId
resultItemId a
x)
          Handle -> ResultName -> IO ()
hPutStrLn Handle
h ResultName
""
          Handle -> ResultName -> IO ()
hPutStr Handle
h ResultName
tab
          Handle -> ResultName -> IO ()
hPutStr Handle
h ResultName
label
          Handle -> ResultName -> IO ()
hPutStr Handle
h ResultName
" = "
          Handle -> ResultName -> IO ()
hPutStrLn Handle
h ResultName
a
          Handle -> ResultName -> IO ()
hPutStrLn Handle
h ResultName
""
hPrintResultSourceIndentedLabelled Handle
h Int
indent ResultName
label ResultLocalisation
loc (ResultVectorSource ResultVector
x) =
  do let tab :: ResultName
tab = Int -> Char -> ResultName
forall a. Int -> a -> [a]
replicate Int
indent Char
' '
     IO () -> Event ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Event ()) -> IO () -> Event ()
forall a b. (a -> b) -> a -> b
$
       do Handle -> ResultName -> IO ()
hPutStr Handle
h ResultName
tab
          Handle -> ResultName -> IO ()
hPutStr Handle
h ResultName
"-- "
          Handle -> ResultName -> IO ()
hPutStr Handle
h (ResultLocalisation -> ResultId -> ResultName
localiseResultDescription ResultLocalisation
loc (ResultId -> ResultName) -> ResultId -> ResultName
forall a b. (a -> b) -> a -> b
$ ResultVector -> ResultId
resultVectorId ResultVector
x)
          Handle -> ResultName -> IO ()
hPutStrLn Handle
h ResultName
""
          Handle -> ResultName -> IO ()
hPutStr Handle
h ResultName
tab
          Handle -> ResultName -> IO ()
hPutStr Handle
h ResultName
label
          Handle -> ResultName -> IO ()
hPutStrLn Handle
h ResultName
":"
          Handle -> ResultName -> IO ()
hPutStrLn Handle
h ResultName
""
     let items :: [ResultSource]
items = Array Int ResultSource -> [ResultSource]
forall i e. Array i e -> [e]
A.elems (ResultVector -> Array Int ResultSource
resultVectorItems ResultVector
x)
         subscript :: [ResultName]
subscript = Array Int ResultName -> [ResultName]
forall i e. Array i e -> [e]
A.elems (ResultVector -> Array Int ResultName
resultVectorSubscript ResultVector
x)
     [(ResultSource, ResultName)]
-> ((ResultSource, ResultName) -> Event ()) -> Event ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ ([ResultSource] -> [ResultName] -> [(ResultSource, ResultName)]
forall a b. [a] -> [b] -> [(a, b)]
zip [ResultSource]
items [ResultName]
subscript) (((ResultSource, ResultName) -> Event ()) -> Event ())
-> ((ResultSource, ResultName) -> Event ()) -> Event ()
forall a b. (a -> b) -> a -> b
$ \(ResultSource
i, ResultName
s) ->
       Handle
-> Int -> ResultName -> ResultLocalisation -> ResultSourcePrint
hPrintResultSourceIndentedLabelled Handle
h (Int
indent Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) (ResultName
label ResultName -> ResultName -> ResultName
forall a. [a] -> [a] -> [a]
++ ResultName
s) ResultLocalisation
loc ResultSource
i
hPrintResultSourceIndentedLabelled Handle
h Int
indent ResultName
label ResultLocalisation
loc (ResultObjectSource ResultObject
x) =
  do let tab :: ResultName
tab = Int -> Char -> ResultName
forall a. Int -> a -> [a]
replicate Int
indent Char
' '
     IO () -> Event ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Event ()) -> IO () -> Event ()
forall a b. (a -> b) -> a -> b
$
       do Handle -> ResultName -> IO ()
hPutStr Handle
h ResultName
tab
          Handle -> ResultName -> IO ()
hPutStr Handle
h ResultName
"-- "
          Handle -> ResultName -> IO ()
hPutStr Handle
h (ResultLocalisation -> ResultId -> ResultName
localiseResultDescription ResultLocalisation
loc (ResultId -> ResultName) -> ResultId -> ResultName
forall a b. (a -> b) -> a -> b
$ ResultObject -> ResultId
resultObjectId ResultObject
x)
          Handle -> ResultName -> IO ()
hPutStrLn Handle
h ResultName
""
          Handle -> ResultName -> IO ()
hPutStr Handle
h ResultName
tab
          Handle -> ResultName -> IO ()
hPutStr Handle
h ResultName
label
          Handle -> ResultName -> IO ()
hPutStrLn Handle
h ResultName
":"
          Handle -> ResultName -> IO ()
hPutStrLn Handle
h ResultName
""
     [ResultProperty] -> (ResultProperty -> Event ()) -> Event ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (ResultObject -> [ResultProperty]
resultObjectProperties ResultObject
x) ((ResultProperty -> Event ()) -> Event ())
-> (ResultProperty -> Event ()) -> Event ()
forall a b. (a -> b) -> a -> b
$ \ResultProperty
p ->
       do let indent' :: Int
indent' = Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
indent
              tab' :: ResultName
tab'    = ResultName
"  " ResultName -> ResultName -> ResultName
forall a. [a] -> [a] -> [a]
++ ResultName
tab
              label' :: ResultName
label'  = ResultProperty -> ResultName
resultPropertyLabel ResultProperty
p
              source' :: ResultSource
source' = ResultProperty -> ResultSource
resultPropertySource ResultProperty
p
          Handle
-> Int -> ResultName -> ResultLocalisation -> ResultSourcePrint
hPrintResultSourceIndentedLabelled Handle
h Int
indent' ResultName
label' ResultLocalisation
loc ResultSource
source'
hPrintResultSourceIndentedLabelled Handle
h Int
indent ResultName
label ResultLocalisation
loc (ResultSeparatorSource ResultSeparator
x) =
  do let tab :: ResultName
tab = Int -> Char -> ResultName
forall a. Int -> a -> [a]
replicate Int
indent Char
' '
     IO () -> Event ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Event ()) -> IO () -> Event ()
forall a b. (a -> b) -> a -> b
$
       do Handle -> ResultName -> IO ()
hPutStr Handle
h ResultName
tab
          Handle -> ResultName -> IO ()
hPutStr Handle
h ResultName
label
          Handle -> ResultName -> IO ()
hPutStrLn Handle
h ResultName
""
          Handle -> ResultName -> IO ()
hPutStrLn Handle
h ResultName
""

-- | Print a localised text representation of the results by the specified source
-- and with the given indent.
printResultSourceIndented :: Int
                             -- ^ an indent
                             -> ResultLocalisation
                             -- ^ a localisation
                             -> ResultSourcePrint
printResultSourceIndented :: Int -> ResultLocalisation -> ResultSourcePrint
printResultSourceIndented = Handle -> Int -> ResultLocalisation -> ResultSourcePrint
hPrintResultSourceIndented Handle
stdout

-- | Print a localised text representation of the results by the specified source.
hPrintResultSource :: Handle
                      -- ^ a handle
                      -> ResultLocalisation
                      -- ^ a localisation
                      -> ResultSourcePrint
hPrintResultSource :: Handle -> ResultLocalisation -> ResultSourcePrint
hPrintResultSource Handle
h = Handle -> Int -> ResultLocalisation -> ResultSourcePrint
hPrintResultSourceIndented Handle
h Int
0

-- | Print a localised text representation of the results by the specified source.
printResultSource :: ResultLocalisation
                     -- ^ a localisation
                     -> ResultSourcePrint
printResultSource :: ResultLocalisation -> ResultSourcePrint
printResultSource = Handle -> ResultLocalisation -> ResultSourcePrint
hPrintResultSource Handle
stdout

-- | Print in Russian a text representation of the results by the specified source.
hPrintResultSourceInRussian :: Handle -> ResultSourcePrint
hPrintResultSourceInRussian :: Handle -> ResultSourcePrint
hPrintResultSourceInRussian Handle
h = Handle -> ResultLocalisation -> ResultSourcePrint
hPrintResultSource Handle
h ResultLocalisation
russianResultLocalisation

-- | Print in English a text representation of the results by the specified source.
hPrintResultSourceInEnglish :: Handle -> ResultSourcePrint
hPrintResultSourceInEnglish :: Handle -> ResultSourcePrint
hPrintResultSourceInEnglish Handle
h = Handle -> ResultLocalisation -> ResultSourcePrint
hPrintResultSource Handle
h ResultLocalisation
englishResultLocalisation

-- | Print in Russian a text representation of the results by the specified source.
printResultSourceInRussian :: ResultSourcePrint
printResultSourceInRussian :: ResultSourcePrint
printResultSourceInRussian = Handle -> ResultSourcePrint
hPrintResultSourceInRussian Handle
stdout

-- | Print in English a text representation of the results by the specified source.
printResultSourceInEnglish :: ResultSourcePrint
printResultSourceInEnglish :: ResultSourcePrint
printResultSourceInEnglish = Handle -> ResultSourcePrint
hPrintResultSourceInEnglish Handle
stdout

-- | Show a localised text representation of the results by the specified source
-- and with the given indent.
showResultSourceIndented :: Int
                            -- ^ an indent
                            -> ResultLocalisation
                            -- ^ a localisation
                            -> ResultSourceShowS
showResultSourceIndented :: Int -> ResultLocalisation -> ResultSourceShowS
showResultSourceIndented Int
indent ResultLocalisation
loc source :: ResultSource
source@(ResultItemSource (ResultItem a
x)) =
  Int -> ResultName -> ResultLocalisation -> ResultSourceShowS
showResultSourceIndentedLabelled Int
indent (a -> ResultName
forall a. ResultItemable a => a -> ResultName
resultItemName a
x) ResultLocalisation
loc ResultSource
source
showResultSourceIndented Int
indent ResultLocalisation
loc source :: ResultSource
source@(ResultVectorSource ResultVector
x) =
  Int -> ResultName -> ResultLocalisation -> ResultSourceShowS
showResultSourceIndentedLabelled Int
indent (ResultVector -> ResultName
resultVectorName ResultVector
x) ResultLocalisation
loc ResultSource
source
showResultSourceIndented Int
indent ResultLocalisation
loc source :: ResultSource
source@(ResultObjectSource ResultObject
x) =
  Int -> ResultName -> ResultLocalisation -> ResultSourceShowS
showResultSourceIndentedLabelled Int
indent (ResultObject -> ResultName
resultObjectName ResultObject
x) ResultLocalisation
loc ResultSource
source
showResultSourceIndented Int
indent ResultLocalisation
loc source :: ResultSource
source@(ResultSeparatorSource ResultSeparator
x) =
  Int -> ResultName -> ResultLocalisation -> ResultSourceShowS
showResultSourceIndentedLabelled Int
indent (ResultSeparator -> ResultName
resultSeparatorText ResultSeparator
x) ResultLocalisation
loc ResultSource
source

-- | Show an indented and labelled text representation of the results by the specified source.
showResultSourceIndentedLabelled :: Int
                                   -- ^ an indent
                                   -> String
                                   -- ^ a label
                                   -> ResultLocalisation
                                   -- ^ a localisation
                                   -> ResultSourceShowS
showResultSourceIndentedLabelled :: Int -> ResultName -> ResultLocalisation -> ResultSourceShowS
showResultSourceIndentedLabelled Int
indent ResultName
label ResultLocalisation
loc (ResultItemSource (ResultItem a
x)) =
  do ResultName
a <- ResultValue ResultName -> ResultData ResultName
forall e. ResultValue e -> ResultData e
resultValueData (ResultValue ResultName -> ResultData ResultName)
-> ResultValue ResultName -> ResultData ResultName
forall a b. (a -> b) -> a -> b
$ a -> ResultValue ResultName
forall a. ResultItemable a => a -> ResultValue ResultName
resultItemToStringValue a
x
     let tab :: ResultName
tab = Int -> Char -> ResultName
forall a. Int -> a -> [a]
replicate Int
indent Char
' '
     (ResultName -> ResultName) -> Event (ResultName -> ResultName)
forall (m :: * -> *) a. Monad m => a -> m a
return ((ResultName -> ResultName) -> Event (ResultName -> ResultName))
-> (ResultName -> ResultName) -> Event (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$
       ResultName -> ResultName -> ResultName
showString ResultName
tab (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
"-- " (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString (ResultLocalisation -> ResultId -> ResultName
localiseResultDescription ResultLocalisation
loc (ResultId -> ResultName) -> ResultId -> ResultName
forall a b. (a -> b) -> a -> b
$ a -> ResultId
forall a. ResultItemable a => a -> ResultId
resultItemId a
x) (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
"\n" (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
tab (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
label (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
" = " (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
a (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
"\n\n"
showResultSourceIndentedLabelled Int
indent ResultName
label ResultLocalisation
loc (ResultVectorSource ResultVector
x) =
  do let tab :: ResultName
tab = Int -> Char -> ResultName
forall a. Int -> a -> [a]
replicate Int
indent Char
' '
         items :: [ResultSource]
items = Array Int ResultSource -> [ResultSource]
forall i e. Array i e -> [e]
A.elems (ResultVector -> Array Int ResultSource
resultVectorItems ResultVector
x)
         subscript :: [ResultName]
subscript = Array Int ResultName -> [ResultName]
forall i e. Array i e -> [e]
A.elems (ResultVector -> Array Int ResultName
resultVectorSubscript ResultVector
x)
     [ResultName -> ResultName]
contents <-
       [(ResultSource, ResultName)]
-> ((ResultSource, ResultName) -> Event (ResultName -> ResultName))
-> Event [ResultName -> ResultName]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM ([ResultSource] -> [ResultName] -> [(ResultSource, ResultName)]
forall a b. [a] -> [b] -> [(a, b)]
zip [ResultSource]
items [ResultName]
subscript) (((ResultSource, ResultName) -> Event (ResultName -> ResultName))
 -> Event [ResultName -> ResultName])
-> ((ResultSource, ResultName) -> Event (ResultName -> ResultName))
-> Event [ResultName -> ResultName]
forall a b. (a -> b) -> a -> b
$ \(ResultSource
i, ResultName
s) ->
       Int -> ResultName -> ResultLocalisation -> ResultSourceShowS
showResultSourceIndentedLabelled (Int
indent Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) (ResultName
label ResultName -> ResultName -> ResultName
forall a. [a] -> [a] -> [a]
++ ResultName
s) ResultLocalisation
loc ResultSource
i
     let showContents :: ResultName -> ResultName
showContents = ((ResultName -> ResultName)
 -> (ResultName -> ResultName) -> ResultName -> ResultName)
-> (ResultName -> ResultName)
-> [ResultName -> ResultName]
-> ResultName
-> ResultName
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) ResultName -> ResultName
forall a. a -> a
id [ResultName -> ResultName]
contents
     (ResultName -> ResultName) -> Event (ResultName -> ResultName)
forall (m :: * -> *) a. Monad m => a -> m a
return ((ResultName -> ResultName) -> Event (ResultName -> ResultName))
-> (ResultName -> ResultName) -> Event (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$
       ResultName -> ResultName -> ResultName
showString ResultName
tab (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
"-- " (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString (ResultLocalisation -> ResultId -> ResultName
localiseResultDescription ResultLocalisation
loc (ResultId -> ResultName) -> ResultId -> ResultName
forall a b. (a -> b) -> a -> b
$ ResultVector -> ResultId
resultVectorId ResultVector
x) (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
"\n" (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
tab (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
label (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
":\n\n" (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName
showContents
showResultSourceIndentedLabelled Int
indent ResultName
label ResultLocalisation
loc (ResultObjectSource ResultObject
x) =
  do let tab :: ResultName
tab = Int -> Char -> ResultName
forall a. Int -> a -> [a]
replicate Int
indent Char
' '
     [ResultName -> ResultName]
contents <-
       [ResultProperty]
-> (ResultProperty -> Event (ResultName -> ResultName))
-> Event [ResultName -> ResultName]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (ResultObject -> [ResultProperty]
resultObjectProperties ResultObject
x) ((ResultProperty -> Event (ResultName -> ResultName))
 -> Event [ResultName -> ResultName])
-> (ResultProperty -> Event (ResultName -> ResultName))
-> Event [ResultName -> ResultName]
forall a b. (a -> b) -> a -> b
$ \ResultProperty
p ->
       do let indent' :: Int
indent' = Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
indent
              tab' :: ResultName
tab'    = ResultName
"  " ResultName -> ResultName -> ResultName
forall a. [a] -> [a] -> [a]
++ ResultName
tab
              label' :: ResultName
label'  = ResultProperty -> ResultName
resultPropertyLabel ResultProperty
p
              output' :: ResultSource
output' = ResultProperty -> ResultSource
resultPropertySource ResultProperty
p
          Int -> ResultName -> ResultLocalisation -> ResultSourceShowS
showResultSourceIndentedLabelled Int
indent' ResultName
label' ResultLocalisation
loc ResultSource
output'
     let showContents :: ResultName -> ResultName
showContents = ((ResultName -> ResultName)
 -> (ResultName -> ResultName) -> ResultName -> ResultName)
-> (ResultName -> ResultName)
-> [ResultName -> ResultName]
-> ResultName
-> ResultName
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) ResultName -> ResultName
forall a. a -> a
id [ResultName -> ResultName]
contents
     (ResultName -> ResultName) -> Event (ResultName -> ResultName)
forall (m :: * -> *) a. Monad m => a -> m a
return ((ResultName -> ResultName) -> Event (ResultName -> ResultName))
-> (ResultName -> ResultName) -> Event (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$
       ResultName -> ResultName -> ResultName
showString ResultName
tab (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
"-- " (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString (ResultLocalisation -> ResultId -> ResultName
localiseResultDescription ResultLocalisation
loc (ResultId -> ResultName) -> ResultId -> ResultName
forall a b. (a -> b) -> a -> b
$ ResultObject -> ResultId
resultObjectId ResultObject
x) (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
"\n" (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
tab (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
label (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
":\n\n" (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName
showContents
showResultSourceIndentedLabelled Int
indent ResultName
label ResultLocalisation
loc (ResultSeparatorSource ResultSeparator
x) =
  do let tab :: ResultName
tab = Int -> Char -> ResultName
forall a. Int -> a -> [a]
replicate Int
indent Char
' '
     (ResultName -> ResultName) -> Event (ResultName -> ResultName)
forall (m :: * -> *) a. Monad m => a -> m a
return ((ResultName -> ResultName) -> Event (ResultName -> ResultName))
-> (ResultName -> ResultName) -> Event (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$
       ResultName -> ResultName -> ResultName
showString ResultName
tab (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
label (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName -> ResultName
showString ResultName
"\n\n"

-- | Show a localised text representation of the results by the specified source.
showResultSource :: ResultLocalisation
                    -- ^ a localisation
                    -> ResultSourceShowS
showResultSource :: ResultLocalisation -> ResultSourceShowS
showResultSource = Int -> ResultLocalisation -> ResultSourceShowS
showResultSourceIndented Int
0

-- | Show in Russian a text representation of the results by the specified source.
showResultSourceInRussian :: ResultSourceShowS
showResultSourceInRussian :: ResultSourceShowS
showResultSourceInRussian = ResultLocalisation -> ResultSourceShowS
showResultSource ResultLocalisation
russianResultLocalisation

-- | Show in English a text representation of the results by the specified source.
showResultSourceInEnglish :: ResultSourceShowS
showResultSourceInEnglish :: ResultSourceShowS
showResultSourceInEnglish = ResultLocalisation -> ResultSourceShowS
showResultSource ResultLocalisation
englishResultLocalisation

-- | Print the results with the information about the modeling time.
printResultsWithTime :: ResultSourcePrint -> Results -> Event ()
printResultsWithTime :: ResultSourcePrint -> Results -> Event ()
printResultsWithTime ResultSourcePrint
print Results
results =
  do let x1 :: ResultSource
x1 = ResultName -> ResultSource
textResultSource ResultName
"----------"
         x2 :: ResultSource
x2 = ResultSource
timeResultSource
         x3 :: ResultSource
x3 = ResultName -> ResultSource
textResultSource ResultName
""
         xs :: [ResultSource]
xs = Results -> [ResultSource]
resultSourceList Results
results
     ResultSourcePrint
print ResultSource
x1
     ResultSourcePrint
print ResultSource
x2
     -- print x3
     ResultSourcePrint -> [ResultSource] -> Event ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ResultSourcePrint
print [ResultSource]
xs
     -- print x3

-- | Print the simulation results in start time.
printResultsInStartTime :: ResultSourcePrint -> Results -> Simulation ()
printResultsInStartTime :: ResultSourcePrint -> Results -> Simulation ()
printResultsInStartTime ResultSourcePrint
print Results
results =
  Event () -> Simulation ()
forall a. Event a -> Simulation a
runEventInStartTime (Event () -> Simulation ()) -> Event () -> Simulation ()
forall a b. (a -> b) -> a -> b
$ ResultSourcePrint -> Results -> Event ()
printResultsWithTime ResultSourcePrint
print Results
results

-- | Print the simulation results in stop time.
printResultsInStopTime :: ResultSourcePrint -> Results -> Simulation ()
printResultsInStopTime :: ResultSourcePrint -> Results -> Simulation ()
printResultsInStopTime ResultSourcePrint
print Results
results =
  Event () -> Simulation ()
forall a. Event a -> Simulation a
runEventInStopTime (Event () -> Simulation ()) -> Event () -> Simulation ()
forall a b. (a -> b) -> a -> b
$ ResultSourcePrint -> Results -> Event ()
printResultsWithTime ResultSourcePrint
print Results
results

-- | Print the simulation results in the integration time points.
printResultsInIntegTimes :: ResultSourcePrint -> Results -> Simulation ()
printResultsInIntegTimes :: ResultSourcePrint -> Results -> Simulation ()
printResultsInIntegTimes ResultSourcePrint
print Results
results =
  do let loop :: [m a] -> m ()
loop (m a
m : [m a]
ms) = m a
m m a -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [m a] -> m ()
loop [m a]
ms
         loop [] = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     [IO ()]
ms <- Dynamics () -> Simulation [IO ()]
forall a. Dynamics a -> Simulation [IO a]
runDynamicsInIntegTimes (Dynamics () -> Simulation [IO ()])
-> Dynamics () -> Simulation [IO ()]
forall a b. (a -> b) -> a -> b
$ Event () -> Dynamics ()
forall a. Event a -> Dynamics a
runEvent (Event () -> Dynamics ()) -> Event () -> Dynamics ()
forall a b. (a -> b) -> a -> b
$
           ResultSourcePrint -> Results -> Event ()
printResultsWithTime ResultSourcePrint
print Results
results
     IO () -> Simulation ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Simulation ()) -> IO () -> Simulation ()
forall a b. (a -> b) -> a -> b
$ [IO ()] -> IO ()
forall (m :: * -> *) a. Monad m => [m a] -> m ()
loop [IO ()]
ms

-- | Print the simulation results in the specified time.
printResultsInTime :: Double -> ResultSourcePrint -> Results -> Simulation ()
printResultsInTime :: Double -> ResultSourcePrint -> Results -> Simulation ()
printResultsInTime Double
t ResultSourcePrint
print Results
results =
  Double -> Dynamics () -> Simulation ()
forall a. Double -> Dynamics a -> Simulation a
runDynamicsInTime Double
t (Dynamics () -> Simulation ()) -> Dynamics () -> Simulation ()
forall a b. (a -> b) -> a -> b
$ Event () -> Dynamics ()
forall a. Event a -> Dynamics a
runEvent (Event () -> Dynamics ()) -> Event () -> Dynamics ()
forall a b. (a -> b) -> a -> b
$
  ResultSourcePrint -> Results -> Event ()
printResultsWithTime ResultSourcePrint
print Results
results

-- | Print the simulation results in the specified time points.
printResultsInTimes :: [Double] -> ResultSourcePrint -> Results -> Simulation ()
printResultsInTimes :: [Double] -> ResultSourcePrint -> Results -> Simulation ()
printResultsInTimes [Double]
ts ResultSourcePrint
print Results
results =
  do let loop :: [m a] -> m ()
loop (m a
m : [m a]
ms) = m a
m m a -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [m a] -> m ()
loop [m a]
ms
         loop [] = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     [IO ()]
ms <- [Double] -> Dynamics () -> Simulation [IO ()]
forall a. [Double] -> Dynamics a -> Simulation [IO a]
runDynamicsInTimes [Double]
ts (Dynamics () -> Simulation [IO ()])
-> Dynamics () -> Simulation [IO ()]
forall a b. (a -> b) -> a -> b
$ Event () -> Dynamics ()
forall a. Event a -> Dynamics a
runEvent (Event () -> Dynamics ()) -> Event () -> Dynamics ()
forall a b. (a -> b) -> a -> b
$
           ResultSourcePrint -> Results -> Event ()
printResultsWithTime ResultSourcePrint
print Results
results
     IO () -> Simulation ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Simulation ()) -> IO () -> Simulation ()
forall a b. (a -> b) -> a -> b
$ [IO ()] -> IO ()
forall (m :: * -> *) a. Monad m => [m a] -> m ()
loop [IO ()]
ms

-- | Show the results with the information about the modeling time.
showResultsWithTime :: ResultSourceShowS -> Results -> Event ShowS
showResultsWithTime :: ResultSourceShowS -> Results -> Event (ResultName -> ResultName)
showResultsWithTime ResultSourceShowS
f Results
results =
  do let x1 :: ResultSource
x1 = ResultName -> ResultSource
textResultSource ResultName
"----------"
         x2 :: ResultSource
x2 = ResultSource
timeResultSource
         x3 :: ResultSource
x3 = ResultName -> ResultSource
textResultSource ResultName
""
         xs :: [ResultSource]
xs = Results -> [ResultSource]
resultSourceList Results
results
     ResultName -> ResultName
y1 <- ResultSourceShowS
f ResultSource
x1
     ResultName -> ResultName
y2 <- ResultSourceShowS
f ResultSource
x2
     ResultName -> ResultName
y3 <- ResultSourceShowS
f ResultSource
x3
     [ResultName -> ResultName]
ys <- [ResultSource]
-> ResultSourceShowS -> Event [ResultName -> ResultName]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [ResultSource]
xs ResultSourceShowS
f
     (ResultName -> ResultName) -> Event (ResultName -> ResultName)
forall (m :: * -> *) a. Monad m => a -> m a
return ((ResultName -> ResultName) -> Event (ResultName -> ResultName))
-> (ResultName -> ResultName) -> Event (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$
       ResultName -> ResultName
y1 (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       ResultName -> ResultName
y2 (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       -- y3 .
       ((ResultName -> ResultName)
 -> (ResultName -> ResultName) -> ResultName -> ResultName)
-> (ResultName -> ResultName)
-> [ResultName -> ResultName]
-> ResultName
-> ResultName
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (ResultName -> ResultName)
-> (ResultName -> ResultName) -> ResultName -> ResultName
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) ResultName -> ResultName
forall a. a -> a
id [ResultName -> ResultName]
ys
       -- y3

-- | Show the simulation results in start time.
showResultsInStartTime :: ResultSourceShowS -> Results -> Simulation ShowS
showResultsInStartTime :: ResultSourceShowS
-> Results -> Simulation (ResultName -> ResultName)
showResultsInStartTime ResultSourceShowS
f Results
results =
  Event (ResultName -> ResultName)
-> Simulation (ResultName -> ResultName)
forall a. Event a -> Simulation a
runEventInStartTime (Event (ResultName -> ResultName)
 -> Simulation (ResultName -> ResultName))
-> Event (ResultName -> ResultName)
-> Simulation (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$ ResultSourceShowS -> Results -> Event (ResultName -> ResultName)
showResultsWithTime ResultSourceShowS
f Results
results

-- | Show the simulation results in stop time.
showResultsInStopTime :: ResultSourceShowS -> Results -> Simulation ShowS
showResultsInStopTime :: ResultSourceShowS
-> Results -> Simulation (ResultName -> ResultName)
showResultsInStopTime ResultSourceShowS
f Results
results =
  Event (ResultName -> ResultName)
-> Simulation (ResultName -> ResultName)
forall a. Event a -> Simulation a
runEventInStopTime (Event (ResultName -> ResultName)
 -> Simulation (ResultName -> ResultName))
-> Event (ResultName -> ResultName)
-> Simulation (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$ ResultSourceShowS -> Results -> Event (ResultName -> ResultName)
showResultsWithTime ResultSourceShowS
f Results
results

-- | Show the simulation results in the integration time points.
--
-- It may consume much memory, for we have to traverse all the integration
-- points to create the resulting function within the 'Simulation' computation.
showResultsInIntegTimes :: ResultSourceShowS -> Results -> Simulation ShowS
showResultsInIntegTimes :: ResultSourceShowS
-> Results -> Simulation (ResultName -> ResultName)
showResultsInIntegTimes ResultSourceShowS
f Results
results =
  do let loop :: [m (b -> b)] -> m (b -> b)
loop (m (b -> b)
m : [m (b -> b)]
ms) = ((b -> b) -> (b -> b) -> b -> b)
-> m ((b -> b) -> (b -> b) -> b -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> b) -> (b -> b) -> b -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) m ((b -> b) -> (b -> b) -> b -> b)
-> m (b -> b) -> m ((b -> b) -> b -> b)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` m (b -> b)
m m ((b -> b) -> b -> b) -> m (b -> b) -> m (b -> b)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` [m (b -> b)] -> m (b -> b)
loop [m (b -> b)]
ms
         loop [] = (b -> b) -> m (b -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return b -> b
forall a. a -> a
id
     [IO (ResultName -> ResultName)]
ms <- Dynamics (ResultName -> ResultName)
-> Simulation [IO (ResultName -> ResultName)]
forall a. Dynamics a -> Simulation [IO a]
runDynamicsInIntegTimes (Dynamics (ResultName -> ResultName)
 -> Simulation [IO (ResultName -> ResultName)])
-> Dynamics (ResultName -> ResultName)
-> Simulation [IO (ResultName -> ResultName)]
forall a b. (a -> b) -> a -> b
$ Event (ResultName -> ResultName)
-> Dynamics (ResultName -> ResultName)
forall a. Event a -> Dynamics a
runEvent (Event (ResultName -> ResultName)
 -> Dynamics (ResultName -> ResultName))
-> Event (ResultName -> ResultName)
-> Dynamics (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$
           ResultSourceShowS -> Results -> Event (ResultName -> ResultName)
showResultsWithTime ResultSourceShowS
f Results
results
     IO (ResultName -> ResultName)
-> Simulation (ResultName -> ResultName)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (ResultName -> ResultName)
 -> Simulation (ResultName -> ResultName))
-> IO (ResultName -> ResultName)
-> Simulation (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$ [IO (ResultName -> ResultName)] -> IO (ResultName -> ResultName)
forall (m :: * -> *) b. Monad m => [m (b -> b)] -> m (b -> b)
loop [IO (ResultName -> ResultName)]
ms

-- | Show the simulation results in the specified time point.
showResultsInTime :: Double -> ResultSourceShowS -> Results -> Simulation ShowS
showResultsInTime :: Double
-> ResultSourceShowS
-> Results
-> Simulation (ResultName -> ResultName)
showResultsInTime Double
t ResultSourceShowS
f Results
results =
  Double
-> Dynamics (ResultName -> ResultName)
-> Simulation (ResultName -> ResultName)
forall a. Double -> Dynamics a -> Simulation a
runDynamicsInTime Double
t (Dynamics (ResultName -> ResultName)
 -> Simulation (ResultName -> ResultName))
-> Dynamics (ResultName -> ResultName)
-> Simulation (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$ Event (ResultName -> ResultName)
-> Dynamics (ResultName -> ResultName)
forall a. Event a -> Dynamics a
runEvent (Event (ResultName -> ResultName)
 -> Dynamics (ResultName -> ResultName))
-> Event (ResultName -> ResultName)
-> Dynamics (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$
  ResultSourceShowS -> Results -> Event (ResultName -> ResultName)
showResultsWithTime ResultSourceShowS
f Results
results

-- | Show the simulation results in the specified time points.
--
-- It may consume much memory, for we have to traverse all the specified
-- points to create the resulting function within the 'Simulation' computation.
showResultsInTimes :: [Double] -> ResultSourceShowS -> Results -> Simulation ShowS
showResultsInTimes :: [Double]
-> ResultSourceShowS
-> Results
-> Simulation (ResultName -> ResultName)
showResultsInTimes [Double]
ts ResultSourceShowS
f Results
results =
  do let loop :: [m (b -> b)] -> m (b -> b)
loop (m (b -> b)
m : [m (b -> b)]
ms) = ((b -> b) -> (b -> b) -> b -> b)
-> m ((b -> b) -> (b -> b) -> b -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> b) -> (b -> b) -> b -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) m ((b -> b) -> (b -> b) -> b -> b)
-> m (b -> b) -> m ((b -> b) -> b -> b)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` m (b -> b)
m m ((b -> b) -> b -> b) -> m (b -> b) -> m (b -> b)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` [m (b -> b)] -> m (b -> b)
loop [m (b -> b)]
ms
         loop [] = (b -> b) -> m (b -> b)
forall (m :: * -> *) a. Monad m => a -> m a
return b -> b
forall a. a -> a
id
     [IO (ResultName -> ResultName)]
ms <- [Double]
-> Dynamics (ResultName -> ResultName)
-> Simulation [IO (ResultName -> ResultName)]
forall a. [Double] -> Dynamics a -> Simulation [IO a]
runDynamicsInTimes [Double]
ts (Dynamics (ResultName -> ResultName)
 -> Simulation [IO (ResultName -> ResultName)])
-> Dynamics (ResultName -> ResultName)
-> Simulation [IO (ResultName -> ResultName)]
forall a b. (a -> b) -> a -> b
$ Event (ResultName -> ResultName)
-> Dynamics (ResultName -> ResultName)
forall a. Event a -> Dynamics a
runEvent (Event (ResultName -> ResultName)
 -> Dynamics (ResultName -> ResultName))
-> Event (ResultName -> ResultName)
-> Dynamics (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$
           ResultSourceShowS -> Results -> Event (ResultName -> ResultName)
showResultsWithTime ResultSourceShowS
f Results
results
     IO (ResultName -> ResultName)
-> Simulation (ResultName -> ResultName)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (ResultName -> ResultName)
 -> Simulation (ResultName -> ResultName))
-> IO (ResultName -> ResultName)
-> Simulation (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$ [IO (ResultName -> ResultName)] -> IO (ResultName -> ResultName)
forall (m :: * -> *) b. Monad m => [m (b -> b)] -> m (b -> b)
loop [IO (ResultName -> ResultName)]
ms

-- | Run the simulation and then print the results in the start time.
printSimulationResultsInStartTime :: ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInStartTime :: ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInStartTime ResultSourcePrint
print Simulation Results
model Specs
specs =
  (Simulation () -> Specs -> IO ())
-> Specs -> Simulation () -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip Simulation () -> Specs -> IO ()
forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs (Simulation () -> IO ()) -> Simulation () -> IO ()
forall a b. (a -> b) -> a -> b
$
  Simulation Results
model Simulation Results -> (Results -> Simulation ()) -> Simulation ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ResultSourcePrint -> Results -> Simulation ()
printResultsInStartTime ResultSourcePrint
print

-- | Run the simulation and then print the results in the final time.
printSimulationResultsInStopTime :: ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInStopTime :: ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInStopTime ResultSourcePrint
print Simulation Results
model Specs
specs =
  (Simulation () -> Specs -> IO ())
-> Specs -> Simulation () -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip Simulation () -> Specs -> IO ()
forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs (Simulation () -> IO ()) -> Simulation () -> IO ()
forall a b. (a -> b) -> a -> b
$
  Simulation Results
model Simulation Results -> (Results -> Simulation ()) -> Simulation ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ResultSourcePrint -> Results -> Simulation ()
printResultsInStopTime ResultSourcePrint
print

-- | Run the simulation and then print the results in the integration time points.
printSimulationResultsInIntegTimes :: ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInIntegTimes :: ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInIntegTimes ResultSourcePrint
print Simulation Results
model Specs
specs =
  (Simulation () -> Specs -> IO ())
-> Specs -> Simulation () -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip Simulation () -> Specs -> IO ()
forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs (Simulation () -> IO ()) -> Simulation () -> IO ()
forall a b. (a -> b) -> a -> b
$
  Simulation Results
model Simulation Results -> (Results -> Simulation ()) -> Simulation ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ResultSourcePrint -> Results -> Simulation ()
printResultsInIntegTimes ResultSourcePrint
print

-- | Run the simulation and then print the results in the specified time point.
printSimulationResultsInTime :: Double -> ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInTime :: Double -> ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInTime Double
t ResultSourcePrint
print Simulation Results
model Specs
specs =
  (Simulation () -> Specs -> IO ())
-> Specs -> Simulation () -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip Simulation () -> Specs -> IO ()
forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs (Simulation () -> IO ()) -> Simulation () -> IO ()
forall a b. (a -> b) -> a -> b
$
  Simulation Results
model Simulation Results -> (Results -> Simulation ()) -> Simulation ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Double -> ResultSourcePrint -> Results -> Simulation ()
printResultsInTime Double
t ResultSourcePrint
print

-- | Run the simulation and then print the results in the specified time points.
printSimulationResultsInTimes :: [Double] -> ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInTimes :: [Double]
-> ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInTimes [Double]
ts ResultSourcePrint
print Simulation Results
model Specs
specs =
  (Simulation () -> Specs -> IO ())
-> Specs -> Simulation () -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip Simulation () -> Specs -> IO ()
forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs (Simulation () -> IO ()) -> Simulation () -> IO ()
forall a b. (a -> b) -> a -> b
$
  Simulation Results
model Simulation Results -> (Results -> Simulation ()) -> Simulation ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Double] -> ResultSourcePrint -> Results -> Simulation ()
printResultsInTimes [Double]
ts ResultSourcePrint
print

-- | Run the simulation and then show the results in the start time.
showSimulationResultsInStartTime :: ResultSourceShowS -> Simulation Results -> Specs -> IO ShowS
showSimulationResultsInStartTime :: ResultSourceShowS
-> Simulation Results -> Specs -> IO (ResultName -> ResultName)
showSimulationResultsInStartTime ResultSourceShowS
f Simulation Results
model Specs
specs =
  (Simulation (ResultName -> ResultName)
 -> Specs -> IO (ResultName -> ResultName))
-> Specs
-> Simulation (ResultName -> ResultName)
-> IO (ResultName -> ResultName)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Simulation (ResultName -> ResultName)
-> Specs -> IO (ResultName -> ResultName)
forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs (Simulation (ResultName -> ResultName)
 -> IO (ResultName -> ResultName))
-> Simulation (ResultName -> ResultName)
-> IO (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$
  Simulation Results
model Simulation Results
-> (Results -> Simulation (ResultName -> ResultName))
-> Simulation (ResultName -> ResultName)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ResultSourceShowS
-> Results -> Simulation (ResultName -> ResultName)
showResultsInStartTime ResultSourceShowS
f

-- | Run the simulation and then show the results in the final time.
showSimulationResultsInStopTime :: ResultSourceShowS -> Simulation Results -> Specs -> IO ShowS
showSimulationResultsInStopTime :: ResultSourceShowS
-> Simulation Results -> Specs -> IO (ResultName -> ResultName)
showSimulationResultsInStopTime ResultSourceShowS
f Simulation Results
model Specs
specs =
  (Simulation (ResultName -> ResultName)
 -> Specs -> IO (ResultName -> ResultName))
-> Specs
-> Simulation (ResultName -> ResultName)
-> IO (ResultName -> ResultName)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Simulation (ResultName -> ResultName)
-> Specs -> IO (ResultName -> ResultName)
forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs (Simulation (ResultName -> ResultName)
 -> IO (ResultName -> ResultName))
-> Simulation (ResultName -> ResultName)
-> IO (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$
  Simulation Results
model Simulation Results
-> (Results -> Simulation (ResultName -> ResultName))
-> Simulation (ResultName -> ResultName)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ResultSourceShowS
-> Results -> Simulation (ResultName -> ResultName)
showResultsInStopTime ResultSourceShowS
f

-- | Run the simulation and then show the results in the integration time points.
--
-- It may consume much memory, for we have to traverse all the integration
-- points to create the resulting function within the 'IO' computation.
showSimulationResultsInIntegTimes :: ResultSourceShowS -> Simulation Results -> Specs -> IO ShowS
showSimulationResultsInIntegTimes :: ResultSourceShowS
-> Simulation Results -> Specs -> IO (ResultName -> ResultName)
showSimulationResultsInIntegTimes ResultSourceShowS
f Simulation Results
model Specs
specs =
  (Simulation (ResultName -> ResultName)
 -> Specs -> IO (ResultName -> ResultName))
-> Specs
-> Simulation (ResultName -> ResultName)
-> IO (ResultName -> ResultName)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Simulation (ResultName -> ResultName)
-> Specs -> IO (ResultName -> ResultName)
forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs (Simulation (ResultName -> ResultName)
 -> IO (ResultName -> ResultName))
-> Simulation (ResultName -> ResultName)
-> IO (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$
  Simulation Results
model Simulation Results
-> (Results -> Simulation (ResultName -> ResultName))
-> Simulation (ResultName -> ResultName)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ResultSourceShowS
-> Results -> Simulation (ResultName -> ResultName)
showResultsInIntegTimes ResultSourceShowS
f

-- | Run the simulation and then show the results in the integration time point.
showSimulationResultsInTime :: Double -> ResultSourceShowS -> Simulation Results -> Specs -> IO ShowS
showSimulationResultsInTime :: Double
-> ResultSourceShowS
-> Simulation Results
-> Specs
-> IO (ResultName -> ResultName)
showSimulationResultsInTime Double
t ResultSourceShowS
f Simulation Results
model Specs
specs =
  (Simulation (ResultName -> ResultName)
 -> Specs -> IO (ResultName -> ResultName))
-> Specs
-> Simulation (ResultName -> ResultName)
-> IO (ResultName -> ResultName)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Simulation (ResultName -> ResultName)
-> Specs -> IO (ResultName -> ResultName)
forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs (Simulation (ResultName -> ResultName)
 -> IO (ResultName -> ResultName))
-> Simulation (ResultName -> ResultName)
-> IO (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$
  Simulation Results
model Simulation Results
-> (Results -> Simulation (ResultName -> ResultName))
-> Simulation (ResultName -> ResultName)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Double
-> ResultSourceShowS
-> Results
-> Simulation (ResultName -> ResultName)
showResultsInTime Double
t ResultSourceShowS
f

-- | Run the simulation and then show the results in the specified time points.
--
-- It may consume much memory, for we have to traverse all the specified
-- points to create the resulting function within the 'IO' computation.
showSimulationResultsInTimes :: [Double] -> ResultSourceShowS -> Simulation Results -> Specs -> IO ShowS
showSimulationResultsInTimes :: [Double]
-> ResultSourceShowS
-> Simulation Results
-> Specs
-> IO (ResultName -> ResultName)
showSimulationResultsInTimes [Double]
ts ResultSourceShowS
f Simulation Results
model Specs
specs =
  (Simulation (ResultName -> ResultName)
 -> Specs -> IO (ResultName -> ResultName))
-> Specs
-> Simulation (ResultName -> ResultName)
-> IO (ResultName -> ResultName)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Simulation (ResultName -> ResultName)
-> Specs -> IO (ResultName -> ResultName)
forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs (Simulation (ResultName -> ResultName)
 -> IO (ResultName -> ResultName))
-> Simulation (ResultName -> ResultName)
-> IO (ResultName -> ResultName)
forall a b. (a -> b) -> a -> b
$
  Simulation Results
model Simulation Results
-> (Results -> Simulation (ResultName -> ResultName))
-> Simulation (ResultName -> ResultName)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Double]
-> ResultSourceShowS
-> Results
-> Simulation (ResultName -> ResultName)
showResultsInTimes [Double]
ts ResultSourceShowS
f