{-# LANGUAGE FlexibleContexts #-}
module Villefort.Stats (genStats,
              makeTable
             )where

import Villefort.Database
import Control.Monad.IO.Class
import Control.Monad.Reader
import Villefort.Definitions
import Paths_Villefort
import System.Random


-- | Helper function to generate row of table
makeRow :: [String] -> String
makeRow x =  "<tr> <th>" ++ (x !! 0) ++ "</th> <th>  " ++ (x!! 1) ++ "</th> </tr>"

-- | Generate Table
makeTable ::[String] ->  [[String]] -> String
makeTable tableData stats = "<table class='table' style='width:100%'> "  ++ "<thead class='thead-inverse'>" ++ ( makeRow  tableData) ++ "</thead>" ++ (mconcat (map  makeRow stats)) ++  "</table>"


-- | Generate stats
genStats :: (MonadReader VConfig m, MonadIO m) => m String
genStats = do
  subjects <- getSubjects
  gits <- mapM makeGithub subjects 
  avg <- getAvg
  statsSum <- getSum
  x <- liftIO $ getDataFileName "templates/header"
  header <- liftIO (readFile x)
  return (header ++ table ++ (makeTable ["Subject","time"] avg) ++ "</br> <h1> Sum </h1>" ++ (makeTable ["Subject","time"] statsSum) ++ "</html>" ++ (mconcat gits))

  
-- | Library to include for github table
table :: String
table = " <script src='/js-chart-widgets.min.js'></script><h1> avg </h1>"

-- | creates the github like graph from database

makeGithub ::(MonadReader VConfig m, MonadIO m) =>  String ->  m Subject
makeGithub subject = do
  z <-   makeQuery ("select substr(Due,1,10) from todo where subject = '" ++ subject ++ "' and state = 0") 
  color <- liftIO $  getColor 
  let header = "<h2 id='"++ subject ++ "'> Calendar "++ subject ++ " </h2> <script> new Calendar({ append_to: '" ++ subject ++ "',num_weeks: 51,day_size: 11, data: ["
  let q = Prelude.map (\x -> "['" ++ (x !! 0) ++"',500],") z
  let bot = "  ], color: " ++ color ++ " }); </script>"
  return (header ++ (Prelude.concat q )++  bot)

statsColors :: [String]
statsColors = ["'#F44336'"
         ,"'#E91E63'"
         ,"'#9C27B0'"
         ,"'#673AB7'"
         ,"'#3F51B5'"
         ,"'#2196F3'"
         ,"'#03A9F4'"
         ,"'#00BCD4'"
         ,"'#009688'"
         ,"'#4CAF50'"
         ,"'#8BC34A'"
         ,"'#CDDC39'"
         ,"'#FFEB3B'"
         ,"'#FFC107'"
         ,"'#FF9800'"
         ,"'#FF5722'"
         ,"'#795548'"
         ,"'#9E9E9E'"
         ,"'#607D8B'"
         ]

getColor :: IO String
getColor = do
  number <- randomRIO (0, (length $ statsColors)-1) :: IO Int
  return (statsColors !! number)