{-# LANGUAGE FlexibleContexts, MonoLocalBinds #-}
module Simulation.Aivika.Trans.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,
hEnqueuePrintingResultSourceIndented,
hEnqueuePrintingResultSource,
hEnqueuePrintingResultSourceInRussian,
hEnqueuePrintingResultSourceInEnglish,
enqueuePrintingResultSourceIndented,
enqueuePrintingResultSource,
enqueuePrintingResultSourceInRussian,
enqueuePrintingResultSourceInEnglish,
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.Trans.Comp
import Simulation.Aivika.Trans.DES
import Simulation.Aivika.Trans.Specs
import Simulation.Aivika.Trans.Simulation
import Simulation.Aivika.Trans.Dynamics
import Simulation.Aivika.Trans.Event
import Simulation.Aivika.Trans.Ref
import Simulation.Aivika.Trans.Results
import Simulation.Aivika.Trans.Results.Locale
type ResultSourceShowS m = ResultSource m -> Event m ShowS
type ResultSourcePrint m = ResultSource m -> Event m ()
hPrintResultSourceIndented :: (MonadDES m, MonadIO (Event m))
=> Handle
-> Int
-> ResultLocalisation
-> ResultSourcePrint m
{-# INLINABLE hPrintResultSourceIndented #-}
hPrintResultSourceIndented :: forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle -> Int -> ResultLocalisation -> ResultSourcePrint m
hPrintResultSourceIndented Handle
h Int
indent ResultLocalisation
loc source :: ResultSource m
source@(ResultItemSource (ResultItem a m
x)) =
forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle
-> Int -> ResultName -> ResultLocalisation -> ResultSourcePrint m
hPrintResultSourceIndentedLabelled Handle
h Int
indent (forall (a :: (* -> *) -> *) (m :: * -> *).
ResultItemable a =>
a m -> ResultName
resultItemName a m
x) ResultLocalisation
loc ResultSource m
source
hPrintResultSourceIndented Handle
h Int
indent ResultLocalisation
loc source :: ResultSource m
source@(ResultVectorSource ResultVector m
x) =
forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle
-> Int -> ResultName -> ResultLocalisation -> ResultSourcePrint m
hPrintResultSourceIndentedLabelled Handle
h Int
indent (forall (m :: * -> *). ResultVector m -> ResultName
resultVectorName ResultVector m
x) ResultLocalisation
loc ResultSource m
source
hPrintResultSourceIndented Handle
h Int
indent ResultLocalisation
loc source :: ResultSource m
source@(ResultObjectSource ResultObject m
x) =
forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle
-> Int -> ResultName -> ResultLocalisation -> ResultSourcePrint m
hPrintResultSourceIndentedLabelled Handle
h Int
indent (forall (m :: * -> *). ResultObject m -> ResultName
resultObjectName ResultObject m
x) ResultLocalisation
loc ResultSource m
source
hPrintResultSourceIndented Handle
h Int
indent ResultLocalisation
loc source :: ResultSource m
source@(ResultSeparatorSource ResultSeparator
x) =
forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle
-> Int -> ResultName -> ResultLocalisation -> ResultSourcePrint m
hPrintResultSourceIndentedLabelled Handle
h Int
indent (ResultSeparator -> ResultName
resultSeparatorText ResultSeparator
x) ResultLocalisation
loc ResultSource m
source
hPrintResultSourceIndentedLabelled :: (MonadDES m, MonadIO (Event m))
=> Handle
-> Int
-> ResultName
-> ResultLocalisation
-> ResultSourcePrint m
{-# INLINABLE hPrintResultSourceIndentedLabelled #-}
hPrintResultSourceIndentedLabelled :: forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle
-> Int -> ResultName -> ResultLocalisation -> ResultSourcePrint m
hPrintResultSourceIndentedLabelled Handle
h Int
indent ResultName
label ResultLocalisation
loc (ResultItemSource (ResultItem a m
x)) =
do ResultName
a <- forall e (m :: * -> *). ResultValue e m -> ResultData e m
resultValueData forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) (a :: (* -> *) -> *).
(MonadDES m, ResultItemable a) =>
a m -> ResultValue ResultName m
resultItemToStringValue a m
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 :: (* -> *) -> *) (m :: * -> *).
ResultItemable a =>
a m -> ResultId
resultItemId a m
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 m
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
$ forall (m :: * -> *). ResultVector m -> ResultId
resultVectorId ResultVector m
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 m]
items = forall i e. Array i e -> [e]
A.elems (forall (m :: * -> *). ResultVector m -> Array Int (ResultSource m)
resultVectorItems ResultVector m
x)
subscript :: [ResultName]
subscript = forall i e. Array i e -> [e]
A.elems (forall (m :: * -> *). ResultVector m -> Array Int ResultName
resultVectorSubscript ResultVector m
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 m]
items [ResultName]
subscript) forall a b. (a -> b) -> a -> b
$ \(ResultSource m
i, ResultName
s) ->
forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle
-> Int -> ResultName -> ResultLocalisation -> ResultSourcePrint m
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 m
i
hPrintResultSourceIndentedLabelled Handle
h Int
indent ResultName
label ResultLocalisation
loc (ResultObjectSource ResultObject m
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
$ forall (m :: * -> *). ResultObject m -> ResultId
resultObjectId ResultObject m
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_ (forall (m :: * -> *). ResultObject m -> [ResultProperty m]
resultObjectProperties ResultObject m
x) forall a b. (a -> b) -> a -> b
$ \ResultProperty m
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' = forall (m :: * -> *). ResultProperty m -> ResultName
resultPropertyLabel ResultProperty m
p
source' :: ResultSource m
source' = forall (m :: * -> *). ResultProperty m -> ResultSource m
resultPropertySource ResultProperty m
p
forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle
-> Int -> ResultName -> ResultLocalisation -> ResultSourcePrint m
hPrintResultSourceIndentedLabelled Handle
h Int
indent' ResultName
label' ResultLocalisation
loc ResultSource m
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 :: (MonadDES m, MonadIO (Event m))
=> Int
-> ResultLocalisation
-> ResultSourcePrint m
{-# INLINABLE printResultSourceIndented #-}
printResultSourceIndented :: forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Int -> ResultLocalisation -> ResultSourcePrint m
printResultSourceIndented = forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle -> Int -> ResultLocalisation -> ResultSourcePrint m
hPrintResultSourceIndented Handle
stdout
hPrintResultSource :: (MonadDES m, MonadIO (Event m))
=> Handle
-> ResultLocalisation
-> ResultSourcePrint m
{-# INLINABLE hPrintResultSource #-}
hPrintResultSource :: forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle -> ResultLocalisation -> ResultSourcePrint m
hPrintResultSource Handle
h = forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle -> Int -> ResultLocalisation -> ResultSourcePrint m
hPrintResultSourceIndented Handle
h Int
0
printResultSource :: (MonadDES m, MonadIO (Event m))
=> ResultLocalisation
-> ResultSourcePrint m
{-# INLINABLE printResultSource #-}
printResultSource :: forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
ResultLocalisation -> ResultSourcePrint m
printResultSource = forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle -> ResultLocalisation -> ResultSourcePrint m
hPrintResultSource Handle
stdout
hPrintResultSourceInRussian :: (MonadDES m, MonadIO (Event m)) => Handle -> ResultSourcePrint m
{-# INLINABLE hPrintResultSourceInRussian #-}
hPrintResultSourceInRussian :: forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle -> ResultSourcePrint m
hPrintResultSourceInRussian Handle
h = forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle -> ResultLocalisation -> ResultSourcePrint m
hPrintResultSource Handle
h ResultLocalisation
russianResultLocalisation
hPrintResultSourceInEnglish :: (MonadDES m, MonadIO (Event m)) => Handle -> ResultSourcePrint m
{-# INLINABLE hPrintResultSourceInEnglish #-}
hPrintResultSourceInEnglish :: forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle -> ResultSourcePrint m
hPrintResultSourceInEnglish Handle
h = forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle -> ResultLocalisation -> ResultSourcePrint m
hPrintResultSource Handle
h ResultLocalisation
englishResultLocalisation
printResultSourceInRussian :: (MonadDES m, MonadIO (Event m)) => ResultSourcePrint m
{-# INLINABLE printResultSourceInRussian #-}
printResultSourceInRussian :: forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
ResultSourcePrint m
printResultSourceInRussian = forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle -> ResultSourcePrint m
hPrintResultSourceInRussian Handle
stdout
printResultSourceInEnglish :: (MonadDES m, MonadIO (Event m)) => ResultSourcePrint m
{-# INLINABLE printResultSourceInEnglish #-}
printResultSourceInEnglish :: forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
ResultSourcePrint m
printResultSourceInEnglish = forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle -> ResultSourcePrint m
hPrintResultSourceInEnglish Handle
stdout
hEnqueuePrintingResultSourceIndented :: (MonadDES m, EventIOQueueing m)
=> Handle
-> Int
-> ResultLocalisation
-> ResultSourcePrint m
{-# INLINABLE hEnqueuePrintingResultSourceIndented #-}
hEnqueuePrintingResultSourceIndented :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Handle -> Int -> ResultLocalisation -> ResultSourcePrint m
hEnqueuePrintingResultSourceIndented Handle
h Int
indent ResultLocalisation
loc ResultSource m
source =
do Double
t <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
DynamicsLift t m =>
Dynamics m a -> t m a
liftDynamics forall (m :: * -> *). Monad m => Dynamics m Double
time
forall (m :: * -> *).
EventIOQueueing m =>
Double -> Event m () -> Event m ()
enqueueEventIO Double
t forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
Handle -> Int -> ResultLocalisation -> ResultSourcePrint m
hPrintResultSourceIndented Handle
h Int
indent ResultLocalisation
loc ResultSource m
source
enqueuePrintingResultSourceIndented :: (MonadDES m, EventIOQueueing m)
=> Int
-> ResultLocalisation
-> ResultSourcePrint m
{-# INLINABLE enqueuePrintingResultSourceIndented #-}
enqueuePrintingResultSourceIndented :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Int -> ResultLocalisation -> ResultSourcePrint m
enqueuePrintingResultSourceIndented = forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Handle -> Int -> ResultLocalisation -> ResultSourcePrint m
hEnqueuePrintingResultSourceIndented Handle
stdout
hEnqueuePrintingResultSource :: (MonadDES m, EventIOQueueing m)
=> Handle
-> ResultLocalisation
-> ResultSourcePrint m
{-# INLINABLE hEnqueuePrintingResultSource #-}
hEnqueuePrintingResultSource :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Handle -> ResultLocalisation -> ResultSourcePrint m
hEnqueuePrintingResultSource Handle
h = forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Handle -> Int -> ResultLocalisation -> ResultSourcePrint m
hEnqueuePrintingResultSourceIndented Handle
h Int
0
enqueuePrintingResultSource :: (MonadDES m, EventIOQueueing m)
=> ResultLocalisation
-> ResultSourcePrint m
{-# INLINABLE enqueuePrintingResultSource #-}
enqueuePrintingResultSource :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
ResultLocalisation -> ResultSourcePrint m
enqueuePrintingResultSource = forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Handle -> ResultLocalisation -> ResultSourcePrint m
hEnqueuePrintingResultSource Handle
stdout
hEnqueuePrintingResultSourceInRussian :: (MonadDES m, EventIOQueueing m) => Handle -> ResultSourcePrint m
{-# INLINABLE hEnqueuePrintingResultSourceInRussian #-}
hEnqueuePrintingResultSourceInRussian :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Handle -> ResultSourcePrint m
hEnqueuePrintingResultSourceInRussian Handle
h = forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Handle -> ResultLocalisation -> ResultSourcePrint m
hEnqueuePrintingResultSource Handle
h ResultLocalisation
russianResultLocalisation
hEnqueuePrintingResultSourceInEnglish :: (MonadDES m, EventIOQueueing m) => Handle -> ResultSourcePrint m
{-# INLINABLE hEnqueuePrintingResultSourceInEnglish #-}
hEnqueuePrintingResultSourceInEnglish :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Handle -> ResultSourcePrint m
hEnqueuePrintingResultSourceInEnglish Handle
h = forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Handle -> ResultLocalisation -> ResultSourcePrint m
hEnqueuePrintingResultSource Handle
h ResultLocalisation
englishResultLocalisation
enqueuePrintingResultSourceInRussian :: (MonadDES m, EventIOQueueing m) => ResultSourcePrint m
{-# INLINABLE enqueuePrintingResultSourceInRussian #-}
enqueuePrintingResultSourceInRussian :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
ResultSourcePrint m
enqueuePrintingResultSourceInRussian = forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Handle -> ResultSourcePrint m
hEnqueuePrintingResultSourceInRussian Handle
stdout
enqueuePrintingResultSourceInEnglish :: (MonadDES m, EventIOQueueing m) => ResultSourcePrint m
{-# INLINABLE enqueuePrintingResultSourceInEnglish #-}
enqueuePrintingResultSourceInEnglish :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
ResultSourcePrint m
enqueuePrintingResultSourceInEnglish = forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Handle -> ResultSourcePrint m
hEnqueuePrintingResultSourceInEnglish Handle
stdout
showResultSourceIndented :: MonadDES m
=> Int
-> ResultLocalisation
-> ResultSourceShowS m
{-# INLINABLE showResultSourceIndented #-}
showResultSourceIndented :: forall (m :: * -> *).
MonadDES m =>
Int -> ResultLocalisation -> ResultSourceShowS m
showResultSourceIndented Int
indent ResultLocalisation
loc source :: ResultSource m
source@(ResultItemSource (ResultItem a m
x)) =
forall (m :: * -> *).
MonadDES m =>
Int -> ResultName -> ResultLocalisation -> ResultSourceShowS m
showResultSourceIndentedLabelled Int
indent (forall (a :: (* -> *) -> *) (m :: * -> *).
ResultItemable a =>
a m -> ResultName
resultItemName a m
x) ResultLocalisation
loc ResultSource m
source
showResultSourceIndented Int
indent ResultLocalisation
loc source :: ResultSource m
source@(ResultVectorSource ResultVector m
x) =
forall (m :: * -> *).
MonadDES m =>
Int -> ResultName -> ResultLocalisation -> ResultSourceShowS m
showResultSourceIndentedLabelled Int
indent (forall (m :: * -> *). ResultVector m -> ResultName
resultVectorName ResultVector m
x) ResultLocalisation
loc ResultSource m
source
showResultSourceIndented Int
indent ResultLocalisation
loc source :: ResultSource m
source@(ResultObjectSource ResultObject m
x) =
forall (m :: * -> *).
MonadDES m =>
Int -> ResultName -> ResultLocalisation -> ResultSourceShowS m
showResultSourceIndentedLabelled Int
indent (forall (m :: * -> *). ResultObject m -> ResultName
resultObjectName ResultObject m
x) ResultLocalisation
loc ResultSource m
source
showResultSourceIndented Int
indent ResultLocalisation
loc source :: ResultSource m
source@(ResultSeparatorSource ResultSeparator
x) =
forall (m :: * -> *).
MonadDES m =>
Int -> ResultName -> ResultLocalisation -> ResultSourceShowS m
showResultSourceIndentedLabelled Int
indent (ResultSeparator -> ResultName
resultSeparatorText ResultSeparator
x) ResultLocalisation
loc ResultSource m
source
showResultSourceIndentedLabelled :: MonadDES m
=> Int
-> String
-> ResultLocalisation
-> ResultSourceShowS m
{-# INLINABLE showResultSourceIndentedLabelled #-}
showResultSourceIndentedLabelled :: forall (m :: * -> *).
MonadDES m =>
Int -> ResultName -> ResultLocalisation -> ResultSourceShowS m
showResultSourceIndentedLabelled Int
indent ResultName
label ResultLocalisation
loc (ResultItemSource (ResultItem a m
x)) =
do ResultName
a <- forall e (m :: * -> *). ResultValue e m -> ResultData e m
resultValueData forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) (a :: (* -> *) -> *).
(MonadDES m, ResultItemable a) =>
a m -> ResultValue ResultName m
resultItemToStringValue a m
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 :: (* -> *) -> *) (m :: * -> *).
ResultItemable a =>
a m -> ResultId
resultItemId a m
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 m
x) =
do let tab :: ResultName
tab = forall a. Int -> a -> [a]
replicate Int
indent Char
' '
items :: [ResultSource m]
items = forall i e. Array i e -> [e]
A.elems (forall (m :: * -> *). ResultVector m -> Array Int (ResultSource m)
resultVectorItems ResultVector m
x)
subscript :: [ResultName]
subscript = forall i e. Array i e -> [e]
A.elems (forall (m :: * -> *). ResultVector m -> Array Int ResultName
resultVectorSubscript ResultVector m
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 m]
items [ResultName]
subscript) forall a b. (a -> b) -> a -> b
$ \(ResultSource m
i, ResultName
s) ->
forall (m :: * -> *).
MonadDES m =>
Int -> ResultName -> ResultLocalisation -> ResultSourceShowS m
showResultSourceIndentedLabelled (Int
indent forall a. Num a => a -> a -> a
+ Int
2) (ResultName
label forall a. [a] -> [a] -> [a]
++ ResultName
s) ResultLocalisation
loc ResultSource m
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
$ forall (m :: * -> *). ResultVector m -> ResultId
resultVectorId ResultVector m
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 m
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 (forall (m :: * -> *). ResultObject m -> [ResultProperty m]
resultObjectProperties ResultObject m
x) forall a b. (a -> b) -> a -> b
$ \ResultProperty m
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' = forall (m :: * -> *). ResultProperty m -> ResultName
resultPropertyLabel ResultProperty m
p
output' :: ResultSource m
output' = forall (m :: * -> *). ResultProperty m -> ResultSource m
resultPropertySource ResultProperty m
p
forall (m :: * -> *).
MonadDES m =>
Int -> ResultName -> ResultLocalisation -> ResultSourceShowS m
showResultSourceIndentedLabelled Int
indent' ResultName
label' ResultLocalisation
loc ResultSource m
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
$ forall (m :: * -> *). ResultObject m -> ResultId
resultObjectId ResultObject m
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 :: MonadDES m
=> ResultLocalisation
-> ResultSourceShowS m
{-# INLINABLE showResultSource #-}
showResultSource :: forall (m :: * -> *).
MonadDES m =>
ResultLocalisation -> ResultSourceShowS m
showResultSource = forall (m :: * -> *).
MonadDES m =>
Int -> ResultLocalisation -> ResultSourceShowS m
showResultSourceIndented Int
0
showResultSourceInRussian :: MonadDES m => ResultSourceShowS m
{-# INLINABLE showResultSourceInRussian #-}
showResultSourceInRussian :: forall (m :: * -> *). MonadDES m => ResultSourceShowS m
showResultSourceInRussian = forall (m :: * -> *).
MonadDES m =>
ResultLocalisation -> ResultSourceShowS m
showResultSource ResultLocalisation
russianResultLocalisation
showResultSourceInEnglish :: MonadDES m => ResultSourceShowS m
{-# INLINABLE showResultSourceInEnglish #-}
showResultSourceInEnglish :: forall (m :: * -> *). MonadDES m => ResultSourceShowS m
showResultSourceInEnglish = forall (m :: * -> *).
MonadDES m =>
ResultLocalisation -> ResultSourceShowS m
showResultSource ResultLocalisation
englishResultLocalisation
printResultsWithTime :: (MonadDES m, MonadIO (Event m)) => ResultSourcePrint m -> Results m -> Event m ()
{-# INLINABLE printResultsWithTime #-}
printResultsWithTime :: forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
ResultSourcePrint m -> Results m -> Event m ()
printResultsWithTime ResultSourcePrint m
print Results m
results =
do let x1 :: ResultSource m
x1 = forall (m :: * -> *). ResultName -> ResultSource m
textResultSource ResultName
"----------"
x2 :: ResultSource m
x2 = forall (m :: * -> *). MonadDES m => ResultSource m
timeResultSource
x3 :: ResultSource m
x3 = forall (m :: * -> *). ResultName -> ResultSource m
textResultSource ResultName
""
xs :: [ResultSource m]
xs = forall (m :: * -> *). Results m -> [ResultSource m]
resultSourceList Results m
results
ResultSourcePrint m
print forall {m :: * -> *}. ResultSource m
x1
ResultSourcePrint m
print ResultSource m
x2
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ResultSourcePrint m
print [ResultSource m]
xs
printResultsInStartTime :: (MonadDES m, EventIOQueueing m) => ResultSourcePrint m -> Results m -> Simulation m ()
{-# INLINABLE printResultsInStartTime #-}
printResultsInStartTime :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
ResultSourcePrint m -> Results m -> Simulation m ()
printResultsInStartTime ResultSourcePrint m
print Results m
results =
do forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStartTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Event m () -> Event m ()
enqueueEventIOWithStartTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
ResultSourcePrint m -> Results m -> Event m ()
printResultsWithTime ResultSourcePrint m
print Results m
results
forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStopTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. Monad m => a -> m a
return ()
printResultsInStopTime :: (MonadDES m, EventIOQueueing m) => ResultSourcePrint m -> Results m -> Simulation m ()
{-# INLINABLE printResultsInStopTime #-}
printResultsInStopTime :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
ResultSourcePrint m -> Results m -> Simulation m ()
printResultsInStopTime ResultSourcePrint m
print Results m
results =
do forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStartTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Event m () -> Event m ()
enqueueEventIOWithStopTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
ResultSourcePrint m -> Results m -> Event m ()
printResultsWithTime ResultSourcePrint m
print Results m
results
forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStopTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. Monad m => a -> m a
return ()
printResultsInIntegTimes :: (MonadDES m, EventIOQueueing m) => ResultSourcePrint m -> Results m -> Simulation m ()
{-# INLINABLE printResultsInIntegTimes #-}
printResultsInIntegTimes :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
ResultSourcePrint m -> Results m -> Simulation m ()
printResultsInIntegTimes ResultSourcePrint m
print Results m
results =
do forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStartTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Event m () -> Event m ()
enqueueEventIOWithIntegTimes forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
ResultSourcePrint m -> Results m -> Event m ()
printResultsWithTime ResultSourcePrint m
print Results m
results
forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStopTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. Monad m => a -> m a
return ()
printResultsInTime :: (MonadDES m, EventIOQueueing m) => Double -> ResultSourcePrint m -> Results m -> Simulation m ()
{-# INLINABLE printResultsInTime #-}
printResultsInTime :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Double -> ResultSourcePrint m -> Results m -> Simulation m ()
printResultsInTime Double
t ResultSourcePrint m
print Results m
results =
do forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStartTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *).
EventIOQueueing m =>
Double -> Event m () -> Event m ()
enqueueEventIO Double
t forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
ResultSourcePrint m -> Results m -> Event m ()
printResultsWithTime ResultSourcePrint m
print Results m
results
forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStopTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. Monad m => a -> m a
return ()
printResultsInTimes :: (MonadDES m, EventIOQueueing m) => [Double] -> ResultSourcePrint m -> Results m -> Simulation m ()
{-# INLINABLE printResultsInTimes #-}
printResultsInTimes :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
[Double] -> ResultSourcePrint m -> Results m -> Simulation m ()
printResultsInTimes [Double]
ts ResultSourcePrint m
print Results m
results =
do forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStartTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
[Double] -> Event m () -> Event m ()
enqueueEventIOWithTimes [Double]
ts forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *).
(MonadDES m, MonadIO (Event m)) =>
ResultSourcePrint m -> Results m -> Event m ()
printResultsWithTime ResultSourcePrint m
print Results m
results
forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStopTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. Monad m => a -> m a
return ()
showResultsWithTime :: MonadDES m => ResultSourceShowS m -> Results m -> Event m ShowS
{-# INLINABLE showResultsWithTime #-}
showResultsWithTime :: forall (m :: * -> *).
MonadDES m =>
ResultSourceShowS m -> Results m -> Event m ShowS
showResultsWithTime ResultSourceShowS m
f Results m
results =
do let x1 :: ResultSource m
x1 = forall (m :: * -> *). ResultName -> ResultSource m
textResultSource ResultName
"----------"
x2 :: ResultSource m
x2 = forall (m :: * -> *). MonadDES m => ResultSource m
timeResultSource
x3 :: ResultSource m
x3 = forall (m :: * -> *). ResultName -> ResultSource m
textResultSource ResultName
""
xs :: [ResultSource m]
xs = forall (m :: * -> *). Results m -> [ResultSource m]
resultSourceList Results m
results
ShowS
y1 <- ResultSourceShowS m
f forall {m :: * -> *}. ResultSource m
x1
ShowS
y2 <- ResultSourceShowS m
f ResultSource m
x2
ShowS
y3 <- ResultSourceShowS m
f forall {m :: * -> *}. ResultSource m
x3
[ShowS]
ys <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [ResultSource m]
xs ResultSourceShowS m
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 :: MonadDES m => ResultSourceShowS m -> Results m -> Simulation m ShowS
{-# INLINABLE showResultsInStartTime #-}
showResultsInStartTime :: forall (m :: * -> *).
MonadDES m =>
ResultSourceShowS m -> Results m -> Simulation m ShowS
showResultsInStartTime ResultSourceShowS m
f Results m
results =
do ShowS
g <- forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStartTime forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *).
MonadDES m =>
ResultSourceShowS m -> Results m -> Event m ShowS
showResultsWithTime ResultSourceShowS m
f Results m
results
forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStopTime forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return ShowS
g
showResultsInStopTime :: MonadDES m => ResultSourceShowS m -> Results m -> Simulation m ShowS
{-# INLINABLE showResultsInStopTime #-}
showResultsInStopTime :: forall (m :: * -> *).
MonadDES m =>
ResultSourceShowS m -> Results m -> Simulation m ShowS
showResultsInStopTime ResultSourceShowS m
f Results m
results =
forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStopTime forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *).
MonadDES m =>
ResultSourceShowS m -> Results m -> Event m ShowS
showResultsWithTime ResultSourceShowS m
f Results m
results
showResultsInIntegTimes :: MonadDES m => ResultSourceShowS m -> Results m -> Simulation m ShowS
{-# INLINABLE showResultsInIntegTimes #-}
showResultsInIntegTimes :: forall (m :: * -> *).
MonadDES m =>
ResultSourceShowS m -> Results m -> Simulation m ShowS
showResultsInIntegTimes ResultSourceShowS m
f Results m
results =
do Ref m ShowS
r <- forall (m :: * -> *) a. MonadDES m => a -> Simulation m (Ref m a)
newRef forall a. a -> a
id
forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStartTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *). MonadDES m => Event m () -> Event m ()
enqueueEventWithIntegTimes forall a b. (a -> b) -> a -> b
$
do ShowS
g <- forall (m :: * -> *).
MonadDES m =>
ResultSourceShowS m -> Results m -> Event m ShowS
showResultsWithTime ResultSourceShowS m
f Results m
results
forall (m :: * -> *) a.
MonadDES m =>
Ref m a -> (a -> a) -> Event m ()
modifyRef Ref m ShowS
r (forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
g)
forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStopTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. MonadDES m => Ref m a -> Event m a
readRef Ref m ShowS
r
showResultsInTime :: MonadDES m => Double -> ResultSourceShowS m -> Results m -> Simulation m ShowS
{-# INLINABLE showResultsInTime #-}
showResultsInTime :: forall (m :: * -> *).
MonadDES m =>
Double -> ResultSourceShowS m -> Results m -> Simulation m ShowS
showResultsInTime Double
t ResultSourceShowS m
f Results m
results =
do Ref m ShowS
r <- forall (m :: * -> *) a. MonadDES m => a -> Simulation m (Ref m a)
newRef forall a. a -> a
id
forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStartTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *).
EventQueueing m =>
Double -> Event m () -> Event m ()
enqueueEvent Double
t forall a b. (a -> b) -> a -> b
$
do ShowS
g <- forall (m :: * -> *).
MonadDES m =>
ResultSourceShowS m -> Results m -> Event m ShowS
showResultsWithTime ResultSourceShowS m
f Results m
results
forall (m :: * -> *) a. MonadDES m => Ref m a -> a -> Event m ()
writeRef Ref m ShowS
r ShowS
g
forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStopTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. MonadDES m => Ref m a -> Event m a
readRef Ref m ShowS
r
showResultsInTimes :: MonadDES m => [Double] -> ResultSourceShowS m -> Results m -> Simulation m ShowS
{-# INLINABLE showResultsInTimes #-}
showResultsInTimes :: forall (m :: * -> *).
MonadDES m =>
[Double] -> ResultSourceShowS m -> Results m -> Simulation m ShowS
showResultsInTimes [Double]
ts ResultSourceShowS m
f Results m
results =
do Ref m ShowS
r <- forall (m :: * -> *) a. MonadDES m => a -> Simulation m (Ref m a)
newRef forall a. a -> a
id
forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStartTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *).
MonadDES m =>
[Double] -> Event m () -> Event m ()
enqueueEventWithTimes [Double]
ts forall a b. (a -> b) -> a -> b
$
do ShowS
g <- forall (m :: * -> *).
MonadDES m =>
ResultSourceShowS m -> Results m -> Event m ShowS
showResultsWithTime ResultSourceShowS m
f Results m
results
forall (m :: * -> *) a.
MonadDES m =>
Ref m a -> (a -> a) -> Event m ()
modifyRef Ref m ShowS
r (forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
g)
forall (m :: * -> *) a. MonadDES m => Event m a -> Simulation m a
runEventInStopTime forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. MonadDES m => Ref m a -> Event m a
readRef Ref m ShowS
r
printSimulationResultsInStartTime :: (MonadDES m, EventIOQueueing m) => ResultSourcePrint m -> Simulation m (Results m) -> Specs m -> m ()
{-# INLINABLE printSimulationResultsInStartTime #-}
printSimulationResultsInStartTime :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
ResultSourcePrint m -> Simulation m (Results m) -> Specs m -> m ()
printSimulationResultsInStartTime ResultSourcePrint m
print Simulation m (Results m)
model Specs m
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (m :: * -> *) a.
MonadDES m =>
Simulation m a -> Specs m -> m a
runSimulation Specs m
specs forall a b. (a -> b) -> a -> b
$
Simulation m (Results m)
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
ResultSourcePrint m -> Results m -> Simulation m ()
printResultsInStartTime ResultSourcePrint m
print
printSimulationResultsInStopTime :: (MonadDES m, EventIOQueueing m) => ResultSourcePrint m -> Simulation m (Results m) -> Specs m -> m ()
{-# INLINABLE printSimulationResultsInStopTime #-}
printSimulationResultsInStopTime :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
ResultSourcePrint m -> Simulation m (Results m) -> Specs m -> m ()
printSimulationResultsInStopTime ResultSourcePrint m
print Simulation m (Results m)
model Specs m
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (m :: * -> *) a.
MonadDES m =>
Simulation m a -> Specs m -> m a
runSimulation Specs m
specs forall a b. (a -> b) -> a -> b
$
Simulation m (Results m)
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
ResultSourcePrint m -> Results m -> Simulation m ()
printResultsInStopTime ResultSourcePrint m
print
printSimulationResultsInIntegTimes :: (MonadDES m, EventIOQueueing m) => ResultSourcePrint m -> Simulation m (Results m) -> Specs m -> m ()
{-# INLINABLE printSimulationResultsInIntegTimes #-}
printSimulationResultsInIntegTimes :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
ResultSourcePrint m -> Simulation m (Results m) -> Specs m -> m ()
printSimulationResultsInIntegTimes ResultSourcePrint m
print Simulation m (Results m)
model Specs m
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (m :: * -> *) a.
MonadDES m =>
Simulation m a -> Specs m -> m a
runSimulation Specs m
specs forall a b. (a -> b) -> a -> b
$
Simulation m (Results m)
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
ResultSourcePrint m -> Results m -> Simulation m ()
printResultsInIntegTimes ResultSourcePrint m
print
printSimulationResultsInTime :: (MonadDES m, EventIOQueueing m) => Double -> ResultSourcePrint m -> Simulation m (Results m) -> Specs m -> m ()
{-# INLINABLE printSimulationResultsInTime #-}
printSimulationResultsInTime :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Double
-> ResultSourcePrint m
-> Simulation m (Results m)
-> Specs m
-> m ()
printSimulationResultsInTime Double
t ResultSourcePrint m
print Simulation m (Results m)
model Specs m
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (m :: * -> *) a.
MonadDES m =>
Simulation m a -> Specs m -> m a
runSimulation Specs m
specs forall a b. (a -> b) -> a -> b
$
Simulation m (Results m)
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
Double -> ResultSourcePrint m -> Results m -> Simulation m ()
printResultsInTime Double
t ResultSourcePrint m
print
printSimulationResultsInTimes :: (MonadDES m, EventIOQueueing m) => [Double] -> ResultSourcePrint m -> Simulation m (Results m) -> Specs m -> m ()
{-# INLINABLE printSimulationResultsInTimes #-}
printSimulationResultsInTimes :: forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
[Double]
-> ResultSourcePrint m
-> Simulation m (Results m)
-> Specs m
-> m ()
printSimulationResultsInTimes [Double]
ts ResultSourcePrint m
print Simulation m (Results m)
model Specs m
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (m :: * -> *) a.
MonadDES m =>
Simulation m a -> Specs m -> m a
runSimulation Specs m
specs forall a b. (a -> b) -> a -> b
$
Simulation m (Results m)
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *).
(MonadDES m, EventIOQueueing m) =>
[Double] -> ResultSourcePrint m -> Results m -> Simulation m ()
printResultsInTimes [Double]
ts ResultSourcePrint m
print
showSimulationResultsInStartTime :: MonadDES m => ResultSourceShowS m -> Simulation m (Results m) -> Specs m -> m ShowS
{-# INLINABLE showSimulationResultsInStartTime #-}
showSimulationResultsInStartTime :: forall (m :: * -> *).
MonadDES m =>
ResultSourceShowS m
-> Simulation m (Results m) -> Specs m -> m ShowS
showSimulationResultsInStartTime ResultSourceShowS m
f Simulation m (Results m)
model Specs m
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (m :: * -> *) a.
MonadDES m =>
Simulation m a -> Specs m -> m a
runSimulation Specs m
specs forall a b. (a -> b) -> a -> b
$
Simulation m (Results m)
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *).
MonadDES m =>
ResultSourceShowS m -> Results m -> Simulation m ShowS
showResultsInStartTime ResultSourceShowS m
f
showSimulationResultsInStopTime :: MonadDES m => ResultSourceShowS m -> Simulation m (Results m) -> Specs m -> m ShowS
{-# INLINABLE showSimulationResultsInStopTime #-}
showSimulationResultsInStopTime :: forall (m :: * -> *).
MonadDES m =>
ResultSourceShowS m
-> Simulation m (Results m) -> Specs m -> m ShowS
showSimulationResultsInStopTime ResultSourceShowS m
f Simulation m (Results m)
model Specs m
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (m :: * -> *) a.
MonadDES m =>
Simulation m a -> Specs m -> m a
runSimulation Specs m
specs forall a b. (a -> b) -> a -> b
$
Simulation m (Results m)
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *).
MonadDES m =>
ResultSourceShowS m -> Results m -> Simulation m ShowS
showResultsInStopTime ResultSourceShowS m
f
showSimulationResultsInIntegTimes :: MonadDES m => ResultSourceShowS m -> Simulation m (Results m) -> Specs m -> m ShowS
{-# INLINABLE showSimulationResultsInIntegTimes #-}
showSimulationResultsInIntegTimes :: forall (m :: * -> *).
MonadDES m =>
ResultSourceShowS m
-> Simulation m (Results m) -> Specs m -> m ShowS
showSimulationResultsInIntegTimes ResultSourceShowS m
f Simulation m (Results m)
model Specs m
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (m :: * -> *) a.
MonadDES m =>
Simulation m a -> Specs m -> m a
runSimulation Specs m
specs forall a b. (a -> b) -> a -> b
$
Simulation m (Results m)
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *).
MonadDES m =>
ResultSourceShowS m -> Results m -> Simulation m ShowS
showResultsInIntegTimes ResultSourceShowS m
f
showSimulationResultsInTime :: MonadDES m => Double -> ResultSourceShowS m -> Simulation m (Results m) -> Specs m -> m ShowS
{-# INLINABLE showSimulationResultsInTime #-}
showSimulationResultsInTime :: forall (m :: * -> *).
MonadDES m =>
Double
-> ResultSourceShowS m
-> Simulation m (Results m)
-> Specs m
-> m ShowS
showSimulationResultsInTime Double
t ResultSourceShowS m
f Simulation m (Results m)
model Specs m
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (m :: * -> *) a.
MonadDES m =>
Simulation m a -> Specs m -> m a
runSimulation Specs m
specs forall a b. (a -> b) -> a -> b
$
Simulation m (Results m)
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *).
MonadDES m =>
Double -> ResultSourceShowS m -> Results m -> Simulation m ShowS
showResultsInTime Double
t ResultSourceShowS m
f
showSimulationResultsInTimes :: MonadDES m => [Double] -> ResultSourceShowS m -> Simulation m (Results m) -> Specs m -> m ShowS
{-# INLINABLE showSimulationResultsInTimes #-}
showSimulationResultsInTimes :: forall (m :: * -> *).
MonadDES m =>
[Double]
-> ResultSourceShowS m
-> Simulation m (Results m)
-> Specs m
-> m ShowS
showSimulationResultsInTimes [Double]
ts ResultSourceShowS m
f Simulation m (Results m)
model Specs m
specs =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (m :: * -> *) a.
MonadDES m =>
Simulation m a -> Specs m -> m a
runSimulation Specs m
specs forall a b. (a -> b) -> a -> b
$
Simulation m (Results m)
model forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *).
MonadDES m =>
[Double] -> ResultSourceShowS m -> Results m -> Simulation m ShowS
showResultsInTimes [Double]
ts ResultSourceShowS m
f