module Main where

import System ( getArgs )

import NFib ( nFib1, nFib2 )

import Test.SBench.STerm ( makeIntSeeds, toDataGen, toData, toNamedData )
import Test.SBench.Time.Series.Test ( nfRuntimeSeries )
import Test.SBench.Space.Single.Test ( getMemLine )
import Test.SBench.Space.Series.Test ( maxMemSeries )
import Test.SBench.Plot.Gnuplot ( series2scaledPlot, series2plot, sbench2scaledPlot, toDiagram, toDiagramWith )

import qualified Graphics.Gnuplot.Frame.OptionSet as Opt
import qualified Graphics.Gnuplot.Terminal.PostScript as PS
import qualified Graphics.Gnuplot.Terminal.PNG as PNG

doRuntimeTests bOpts rOpts = 
    let seeds = makeIntSeeds 1 10000 10 in
    do dat_fib1 <- nfRuntimeSeries 
                     (Just (bOpts, rOpts, "runtime_fib1", "fib1"))
                     nFib1 
                     (toDataGen id "" "id") 
                     seeds
       dat_fib2 <- nfRuntimeSeries 
                     (Just (bOpts, rOpts, "runtime_fib2", "fib2"))
                     nFib2
                     (toDataGen id "" "id")
                     seeds
       let plt_fib1  = series2scaledPlot ((/(1000 :: Double)) . fromIntegral) (*1000000) "fib1" dat_fib1
           plt_fib2  = series2scaledPlot ((/(1000 :: Double)) . fromIntegral) (*1000000) "fib2" dat_fib2
           frameOpts = [ Opt.title  "runtime comparism for Fibunacci number generators"
                       , Opt.xLabel "number of the Fibunacci number requested (*1000)"
                       , Opt.yLabel "runtime (microseconds)"
                       ]
       toDiagram "comp_runtime_fib" [PS.color] frameOpts [plt_fib1, plt_fib2]


-- | Create a heap profile for a function.
--   fib2 runs to fast to generate a profile, i.e., there is no sample measured,
--   so here only fib1 is measured.
doMemProfile = 
    let inp = toNamedData 3000000 "(3000000::Int)" in
    do  dat_fib1 <- getMemLine True ("memline_fib1", "fib1") nFib1 inp
        let plt_fib1  = series2scaledPlot id ((/(1024*1024::Double)) . fromIntegral) "fib1" dat_fib1
            frameOpts = [ Opt.title  $ "heap consumption when calculating the " 
                                       ++ show inp ++ "th Fibonacci number"
                        , Opt.xLabel "runtime (seconds)"
                        , Opt.yLabel "heap consumption (MBytes)"
                        ]
        toDiagram "comp_memline_fib" [PS.color] frameOpts [plt_fib1]

doMaxMemSeries =
    let seeds = makeIntSeeds 1 10000 10 in
    do  dat_fib1 <- maxMemSeries True ("memline_fib1", "fib1") nFib1 (toDataGen id "" "id") seeds
        dat_fib2 <- maxMemSeries True ("memline_fib2", "fib2") nFib2 (toDataGen id "" "id") seeds
        let plt_fib1  = series2scaledPlot ((/(1000 :: Double)) . fromIntegral) ((/(1024::Double)) . fromIntegral) "fib1" dat_fib1
            plt_fib2  = series2scaledPlot ((/(1000 :: Double)) . fromIntegral) ((/(1024::Double)) . fromIntegral) "fib2" dat_fib2
            frameOpts = [ Opt.title  $ "comparism of maximal heap consumption for Fibonacci number generators"
                        , Opt.xLabel "number of the Fibunacci number requested (*1000)"
                        , Opt.yLabel "heap consumption (kBytes)"
                        ]
        toDiagram "comp_maxmem_fib" [PS.color] frameOpts [plt_fib1, plt_fib2]

redoRuntimePlotAsPNG = do
    plt_fib1 <- sbench2scaledPlot (/1000) (*1000000) "runtime_fib1"
    plt_fib2 <- sbench2scaledPlot (/1000) (*1000000) "runtime_fib2"
    let frameOpts = [ Opt.title  "runtime comparism for Fibunacci number generators"
                    , Opt.xLabel "number of the Fibunacci number requested (*1000)"
                    , Opt.yLabel "runtime (microseconds)"
                    ]
    toDiagramWith (PNG.cons "comp_runtime_fib.png") frameOpts [plt_fib1, plt_fib2]

main = do
    let bOpts = "unknown"
        rOpts = "unknown"
    print bOpts
    print rOpts
    doRuntimeTests bOpts rOpts
    doMemProfile
    doMaxMemSeries
    redoRuntimePlotAsPNG