module Simulation.Aivika.Results.IO
(
ResultSourcePrint,
ResultSourceShowS,
printResultsWithTime,
printResultsInStartTime,
printResultsInStopTime,
printResultsInIntegTimes,
printResultsInTime,
printResultsInTimes,
printSimulationResultsInStartTime,
printSimulationResultsInStopTime,
printSimulationResultsInIntegTimes,
printSimulationResultsInTime,
printSimulationResultsInTimes,
showResultsWithTime,
showResultsInStartTime,
showResultsInStopTime,
showResultsInIntegTimes,
showResultsInTime,
showResultsInTimes,
showSimulationResultsInStartTime,
showSimulationResultsInStopTime,
showSimulationResultsInIntegTimes,
showSimulationResultsInTime,
showSimulationResultsInTimes,
hPrintResultSourceIndented,
hPrintResultSource,
hPrintResultSourceInRussian,
hPrintResultSourceInEnglish,
printResultSourceIndented,
printResultSource,
printResultSourceInRussian,
printResultSourceInEnglish,
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
type ResultSourceShowS = ResultSource -> Event ShowS
type ResultSourcePrint = ResultSource -> Event ()
hPrintResultSourceIndented :: Handle
-> Int
-> ResultLocalisation
-> 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 (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
hPrintResultSourceIndentedLabelled :: Handle
-> Int
-> ResultName
-> ResultLocalisation
-> ResultSourcePrint
hPrintResultSourceIndentedLabelled :: Handle
-> Int -> ResultName -> ResultLocalisation -> ResultSourcePrint
hPrintResultSourceIndentedLabelled Handle
h Int
indent ResultName
label ResultLocalisation
loc (ResultItemSource (ResultItem a
x)) =
do ResultName
a <- forall e. ResultValue e -> ResultData e
resultValueData forall a b. (a -> b) -> a -> b
$ forall a. ResultItemable a => a -> ResultValue ResultName
resultItemToStringValue a
x
let tab :: ResultName
tab = forall a. Int -> a -> [a]
replicate Int
indent Char
' '
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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 forall a b. (a -> b) -> a -> b
$ 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 = forall a. Int -> a -> [a]
replicate Int
indent Char
' '
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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 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 = forall i e. Array i e -> [e]
A.elems (ResultVector -> Array Int ResultSource
resultVectorItems ResultVector
x)
subscript :: [ResultName]
subscript = forall i e. Array i e -> [e]
A.elems (ResultVector -> Array Int ResultName
resultVectorSubscript ResultVector
x)
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (forall a b. [a] -> [b] -> [(a, b)]
zip [ResultSource]
items [ResultName]
subscript) forall a b. (a -> b) -> a -> b
$ \(ResultSource
i, ResultName
s) ->
Handle
-> Int -> ResultName -> ResultLocalisation -> ResultSourcePrint
hPrintResultSourceIndentedLabelled Handle
h (Int
indent forall a. Num a => a -> a -> a
+ Int
2) (ResultName
label 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 = forall a. Int -> a -> [a]
replicate Int
indent Char
' '
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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 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
""
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (ResultObject -> [ResultProperty]
resultObjectProperties ResultObject
x) forall a b. (a -> b) -> a -> b
$ \ResultProperty
p ->
do let indent' :: Int
indent' = Int
2 forall a. Num a => a -> a -> a
+ Int
indent
tab' :: ResultName
tab' = 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 = forall a. Int -> a -> [a]
replicate Int
indent Char
' '
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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
""
printResultSourceIndented :: Int
-> ResultLocalisation
-> ResultSourcePrint
printResultSourceIndented :: Int -> ResultLocalisation -> ResultSourcePrint
printResultSourceIndented = Handle -> Int -> ResultLocalisation -> ResultSourcePrint
hPrintResultSourceIndented Handle
stdout
hPrintResultSource :: Handle
-> ResultLocalisation
-> ResultSourcePrint
hPrintResultSource :: Handle -> ResultLocalisation -> ResultSourcePrint
hPrintResultSource Handle
h = Handle -> Int -> ResultLocalisation -> ResultSourcePrint
hPrintResultSourceIndented Handle
h Int
0
printResultSource :: ResultLocalisation
-> ResultSourcePrint
printResultSource :: ResultLocalisation -> ResultSourcePrint
printResultSource = Handle -> ResultLocalisation -> ResultSourcePrint
hPrintResultSource Handle
stdout
hPrintResultSourceInRussian :: Handle -> ResultSourcePrint
hPrintResultSourceInRussian :: Handle -> ResultSourcePrint
hPrintResultSourceInRussian Handle
h = Handle -> ResultLocalisation -> ResultSourcePrint
hPrintResultSource Handle
h ResultLocalisation
russianResultLocalisation
hPrintResultSourceInEnglish :: Handle -> ResultSourcePrint
hPrintResultSourceInEnglish :: Handle -> ResultSourcePrint
hPrintResultSourceInEnglish Handle
h = Handle -> ResultLocalisation -> ResultSourcePrint
hPrintResultSource Handle
h ResultLocalisation
englishResultLocalisation
printResultSourceInRussian :: ResultSourcePrint
printResultSourceInRussian :: ResultSourcePrint
printResultSourceInRussian = Handle -> ResultSourcePrint
hPrintResultSourceInRussian Handle
stdout
printResultSourceInEnglish :: ResultSourcePrint
printResultSourceInEnglish :: ResultSourcePrint
printResultSourceInEnglish = Handle -> ResultSourcePrint
hPrintResultSourceInEnglish Handle
stdout
showResultSourceIndented :: Int
-> ResultLocalisation
-> ResultSourceShowS
showResultSourceIndented :: Int -> ResultLocalisation -> ResultSourceShowS
showResultSourceIndented Int
indent ResultLocalisation
loc source :: ResultSource
source@(ResultItemSource (ResultItem a
x)) =
Int -> ResultName -> ResultLocalisation -> ResultSourceShowS
showResultSourceIndentedLabelled Int
indent (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
showResultSourceIndentedLabelled :: Int
-> String
-> ResultLocalisation
-> ResultSourceShowS
showResultSourceIndentedLabelled :: Int -> ResultName -> ResultLocalisation -> ResultSourceShowS
showResultSourceIndentedLabelled Int
indent ResultName
label ResultLocalisation
loc (ResultItemSource (ResultItem a
x)) =
do ResultName
a <- forall e. ResultValue e -> ResultData e
resultValueData forall a b. (a -> b) -> a -> b
$ forall a. ResultItemable a => a -> ResultValue ResultName
resultItemToStringValue a
x
let tab :: ResultName
tab = forall a. Int -> a -> [a]
replicate Int
indent Char
' '
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
ResultName -> ShowS
showString ResultName
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
"-- " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString (ResultLocalisation -> ResultId -> ResultName
localiseResultDescription ResultLocalisation
loc forall a b. (a -> b) -> a -> b
$ forall a. ResultItemable a => a -> ResultId
resultItemId a
x) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
"\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
label forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
" = " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
a forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
"\n\n"
showResultSourceIndentedLabelled Int
indent ResultName
label ResultLocalisation
loc (ResultVectorSource ResultVector
x) =
do let tab :: ResultName
tab = forall a. Int -> a -> [a]
replicate Int
indent Char
' '
items :: [ResultSource]
items = forall i e. Array i e -> [e]
A.elems (ResultVector -> Array Int ResultSource
resultVectorItems ResultVector
x)
subscript :: [ResultName]
subscript = forall i e. Array i e -> [e]
A.elems (ResultVector -> Array Int ResultName
resultVectorSubscript ResultVector
x)
[ShowS]
contents <-
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (forall a b. [a] -> [b] -> [(a, b)]
zip [ResultSource]
items [ResultName]
subscript) forall a b. (a -> b) -> a -> b
$ \(ResultSource
i, ResultName
s) ->
Int -> ResultName -> ResultLocalisation -> ResultSourceShowS
showResultSourceIndentedLabelled (Int
indent forall a. Num a => a -> a -> a
+ Int
2) (ResultName
label forall a. [a] -> [a] -> [a]
++ ResultName
s) ResultLocalisation
loc ResultSource
i
let showContents :: ShowS
showContents = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall a. a -> a
id [ShowS]
contents
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
ResultName -> ShowS
showString ResultName
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
"-- " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString (ResultLocalisation -> ResultId -> ResultName
localiseResultDescription ResultLocalisation
loc forall a b. (a -> b) -> a -> b
$ ResultVector -> ResultId
resultVectorId ResultVector
x) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
"\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
label forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
":\n\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ShowS
showContents
showResultSourceIndentedLabelled Int
indent ResultName
label ResultLocalisation
loc (ResultObjectSource ResultObject
x) =
do let tab :: ResultName
tab = forall a. Int -> a -> [a]
replicate Int
indent Char
' '
[ShowS]
contents <-
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (ResultObject -> [ResultProperty]
resultObjectProperties ResultObject
x) forall a b. (a -> b) -> a -> b
$ \ResultProperty
p ->
do let indent' :: Int
indent' = Int
2 forall a. Num a => a -> a -> a
+ Int
indent
tab' :: ResultName
tab' = 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 :: ShowS
showContents = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall a. a -> a
id [ShowS]
contents
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
ResultName -> ShowS
showString ResultName
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
"-- " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString (ResultLocalisation -> ResultId -> ResultName
localiseResultDescription ResultLocalisation
loc forall a b. (a -> b) -> a -> b
$ ResultObject -> ResultId
resultObjectId ResultObject
x) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
"\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
label forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
":\n\n" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ShowS
showContents
showResultSourceIndentedLabelled Int
indent ResultName
label ResultLocalisation
loc (ResultSeparatorSource ResultSeparator
x) =
do let tab :: ResultName
tab = forall a. Int -> a -> [a]
replicate Int
indent Char
' '
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
ResultName -> ShowS
showString ResultName
tab forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
label forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ResultName -> ShowS
showString ResultName
"\n\n"
showResultSource :: ResultLocalisation
-> ResultSourceShowS
showResultSource :: ResultLocalisation -> ResultSourceShowS
showResultSource = Int -> ResultLocalisation -> ResultSourceShowS
showResultSourceIndented Int
0
showResultSourceInRussian :: ResultSourceShowS
showResultSourceInRussian :: ResultSourceShowS
showResultSourceInRussian = ResultLocalisation -> ResultSourceShowS
showResultSource ResultLocalisation
russianResultLocalisation
showResultSourceInEnglish :: ResultSourceShowS
showResultSourceInEnglish :: ResultSourceShowS
showResultSourceInEnglish = ResultLocalisation -> ResultSourceShowS
showResultSource ResultLocalisation
englishResultLocalisation
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
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ResultSourcePrint
print [ResultSource]
xs
printResultsInStartTime :: ResultSourcePrint -> Results -> Simulation ()
printResultsInStartTime :: ResultSourcePrint -> Results -> Simulation ()
printResultsInStartTime ResultSourcePrint
print Results
results =
forall a. Event a -> Simulation a
runEventInStartTime forall a b. (a -> b) -> a -> b
$ ResultSourcePrint -> Results -> Event ()
printResultsWithTime ResultSourcePrint
print Results
results
printResultsInStopTime :: ResultSourcePrint -> Results -> Simulation ()
printResultsInStopTime :: ResultSourcePrint -> Results -> Simulation ()
printResultsInStopTime ResultSourcePrint
print Results
results =
forall a. Event a -> Simulation a
runEventInStopTime forall a b. (a -> b) -> a -> b
$ ResultSourcePrint -> Results -> Event ()
printResultsWithTime ResultSourcePrint
print Results
results
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 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [m a] -> m ()
loop [m a]
ms
loop [] = forall (m :: * -> *) a. Monad m => a -> m a
return ()
[IO ()]
ms <- forall a. Dynamics a -> Simulation [IO a]
runDynamicsInIntegTimes forall a b. (a -> b) -> a -> b
$ forall a. Event a -> Dynamics a
runEvent forall a b. (a -> b) -> a -> b
$
ResultSourcePrint -> Results -> Event ()
printResultsWithTime ResultSourcePrint
print Results
results
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall {m :: * -> *} {a}. Monad m => [m a] -> m ()
loop [IO ()]
ms
printResultsInTime :: Double -> ResultSourcePrint -> Results -> Simulation ()
printResultsInTime :: Double -> ResultSourcePrint -> Results -> Simulation ()
printResultsInTime Double
t ResultSourcePrint
print Results
results =
forall a. Double -> Dynamics a -> Simulation a
runDynamicsInTime Double
t forall a b. (a -> b) -> a -> b
$ forall a. Event a -> Dynamics a
runEvent forall a b. (a -> b) -> a -> b
$
ResultSourcePrint -> Results -> Event ()
printResultsWithTime ResultSourcePrint
print Results
results
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 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [m a] -> m ()
loop [m a]
ms
loop [] = forall (m :: * -> *) a. Monad m => a -> m a
return ()
[IO ()]
ms <- forall a. [Double] -> Dynamics a -> Simulation [IO a]
runDynamicsInTimes [Double]
ts forall a b. (a -> b) -> a -> b
$ forall a. Event a -> Dynamics a
runEvent forall a b. (a -> b) -> a -> b
$
ResultSourcePrint -> Results -> Event ()
printResultsWithTime ResultSourcePrint
print Results
results
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall {m :: * -> *} {a}. Monad m => [m a] -> m ()
loop [IO ()]
ms
showResultsWithTime :: ResultSourceShowS -> Results -> Event ShowS
showResultsWithTime :: ResultSourceShowS -> Results -> Event ShowS
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
ShowS
y1 <- ResultSourceShowS
f ResultSource
x1
ShowS
y2 <- ResultSourceShowS
f ResultSource
x2
ShowS
y3 <- ResultSourceShowS
f ResultSource
x3
[ShowS]
ys <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [ResultSource]
xs ResultSourceShowS
f
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
ShowS
y1 forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ShowS
y2 forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall a. a -> a
id [ShowS]
ys
showResultsInStartTime :: ResultSourceShowS -> Results -> Simulation ShowS
showResultsInStartTime :: ResultSourceShowS -> Results -> Simulation ShowS
showResultsInStartTime ResultSourceShowS
f Results
results =
forall a. Event a -> Simulation a
runEventInStartTime forall a b. (a -> b) -> a -> b
$ ResultSourceShowS -> Results -> Event ShowS
showResultsWithTime ResultSourceShowS
f Results
results
showResultsInStopTime :: ResultSourceShowS -> Results -> Simulation ShowS
showResultsInStopTime :: ResultSourceShowS -> Results -> Simulation ShowS
showResultsInStopTime ResultSourceShowS
f Results
results =
forall a. Event a -> Simulation a
runEventInStopTime forall a b. (a -> b) -> a -> b
$ ResultSourceShowS -> Results -> Event ShowS
showResultsWithTime ResultSourceShowS
f Results
results
showResultsInIntegTimes :: ResultSourceShowS -> Results -> Simulation ShowS
showResultsInIntegTimes :: ResultSourceShowS -> Results -> Simulation ShowS
showResultsInIntegTimes ResultSourceShowS
f Results
results =
do let loop :: [m (b -> b)] -> m (b -> b)
loop (m (b -> b)
m : [m (b -> b)]
ms) = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` m (b -> b)
m 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 [] = forall (m :: * -> *) a. Monad m => a -> m a
return forall a. a -> a
id
[IO ShowS]
ms <- forall a. Dynamics a -> Simulation [IO a]
runDynamicsInIntegTimes forall a b. (a -> b) -> a -> b
$ forall a. Event a -> Dynamics a
runEvent forall a b. (a -> b) -> a -> b
$
ResultSourceShowS -> Results -> Event ShowS
showResultsWithTime ResultSourceShowS
f Results
results
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall {m :: * -> *} {b}. Monad m => [m (b -> b)] -> m (b -> b)
loop [IO ShowS]
ms
showResultsInTime :: Double -> ResultSourceShowS -> Results -> Simulation ShowS
showResultsInTime :: Double -> ResultSourceShowS -> Results -> Simulation ShowS
showResultsInTime Double
t ResultSourceShowS
f Results
results =
forall a. Double -> Dynamics a -> Simulation a
runDynamicsInTime Double
t forall a b. (a -> b) -> a -> b
$ forall a. Event a -> Dynamics a
runEvent forall a b. (a -> b) -> a -> b
$
ResultSourceShowS -> Results -> Event ShowS
showResultsWithTime ResultSourceShowS
f Results
results
showResultsInTimes :: [Double] -> ResultSourceShowS -> Results -> Simulation ShowS
showResultsInTimes :: [Double] -> ResultSourceShowS -> Results -> Simulation ShowS
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) = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` m (b -> b)
m 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 [] = forall (m :: * -> *) a. Monad m => a -> m a
return forall a. a -> a
id
[IO ShowS]
ms <- forall a. [Double] -> Dynamics a -> Simulation [IO a]
runDynamicsInTimes [Double]
ts forall a b. (a -> b) -> a -> b
$ forall a. Event a -> Dynamics a
runEvent forall a b. (a -> b) -> a -> b
$
ResultSourceShowS -> Results -> Event ShowS
showResultsWithTime ResultSourceShowS
f Results
results
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall {m :: * -> *} {b}. Monad m => [m (b -> b)] -> m (b -> b)
loop [IO ShowS]
ms
printSimulationResultsInStartTime :: ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInStartTime :: ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInStartTime ResultSourcePrint
print Simulation Results
model Specs
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs forall a b. (a -> b) -> a -> b
$
Simulation Results
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ResultSourcePrint -> Results -> Simulation ()
printResultsInStartTime ResultSourcePrint
print
printSimulationResultsInStopTime :: ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInStopTime :: ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInStopTime ResultSourcePrint
print Simulation Results
model Specs
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs forall a b. (a -> b) -> a -> b
$
Simulation Results
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ResultSourcePrint -> Results -> Simulation ()
printResultsInStopTime ResultSourcePrint
print
printSimulationResultsInIntegTimes :: ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInIntegTimes :: ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInIntegTimes ResultSourcePrint
print Simulation Results
model Specs
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs forall a b. (a -> b) -> a -> b
$
Simulation Results
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ResultSourcePrint -> Results -> Simulation ()
printResultsInIntegTimes ResultSourcePrint
print
printSimulationResultsInTime :: Double -> ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInTime :: Double -> ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInTime Double
t ResultSourcePrint
print Simulation Results
model Specs
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs forall a b. (a -> b) -> a -> b
$
Simulation Results
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Double -> ResultSourcePrint -> Results -> Simulation ()
printResultsInTime Double
t ResultSourcePrint
print
printSimulationResultsInTimes :: [Double] -> ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInTimes :: [Double]
-> ResultSourcePrint -> Simulation Results -> Specs -> IO ()
printSimulationResultsInTimes [Double]
ts ResultSourcePrint
print Simulation Results
model Specs
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs forall a b. (a -> b) -> a -> b
$
Simulation Results
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Double] -> ResultSourcePrint -> Results -> Simulation ()
printResultsInTimes [Double]
ts ResultSourcePrint
print
showSimulationResultsInStartTime :: ResultSourceShowS -> Simulation Results -> Specs -> IO ShowS
showSimulationResultsInStartTime :: ResultSourceShowS -> Simulation Results -> Specs -> IO ShowS
showSimulationResultsInStartTime ResultSourceShowS
f Simulation Results
model Specs
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs forall a b. (a -> b) -> a -> b
$
Simulation Results
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ResultSourceShowS -> Results -> Simulation ShowS
showResultsInStartTime ResultSourceShowS
f
showSimulationResultsInStopTime :: ResultSourceShowS -> Simulation Results -> Specs -> IO ShowS
showSimulationResultsInStopTime :: ResultSourceShowS -> Simulation Results -> Specs -> IO ShowS
showSimulationResultsInStopTime ResultSourceShowS
f Simulation Results
model Specs
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs forall a b. (a -> b) -> a -> b
$
Simulation Results
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ResultSourceShowS -> Results -> Simulation ShowS
showResultsInStopTime ResultSourceShowS
f
showSimulationResultsInIntegTimes :: ResultSourceShowS -> Simulation Results -> Specs -> IO ShowS
showSimulationResultsInIntegTimes :: ResultSourceShowS -> Simulation Results -> Specs -> IO ShowS
showSimulationResultsInIntegTimes ResultSourceShowS
f Simulation Results
model Specs
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs forall a b. (a -> b) -> a -> b
$
Simulation Results
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ResultSourceShowS -> Results -> Simulation ShowS
showResultsInIntegTimes ResultSourceShowS
f
showSimulationResultsInTime :: Double -> ResultSourceShowS -> Simulation Results -> Specs -> IO ShowS
showSimulationResultsInTime :: Double
-> ResultSourceShowS -> Simulation Results -> Specs -> IO ShowS
showSimulationResultsInTime Double
t ResultSourceShowS
f Simulation Results
model Specs
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs forall a b. (a -> b) -> a -> b
$
Simulation Results
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Double -> ResultSourceShowS -> Results -> Simulation ShowS
showResultsInTime Double
t ResultSourceShowS
f
showSimulationResultsInTimes :: [Double] -> ResultSourceShowS -> Simulation Results -> Specs -> IO ShowS
showSimulationResultsInTimes :: [Double]
-> ResultSourceShowS -> Simulation Results -> Specs -> IO ShowS
showSimulationResultsInTimes [Double]
ts ResultSourceShowS
f Simulation Results
model Specs
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Simulation a -> Specs -> IO a
runSimulation Specs
specs forall a b. (a -> b) -> a -> b
$
Simulation Results
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Double] -> ResultSourceShowS -> Results -> Simulation ShowS
showResultsInTimes [Double]
ts ResultSourceShowS
f