module Stats (genStats
             )where
import Database
import Control.Monad.IO.Class
import Paths_Villefort
import System.Random

data Query = Query String

-- | Query to get average of subjects
--getAvg :: IO (Maybe [String])
getAvg =  makeQuery "select avg(time), Subject from todo  group by Subject order by avg(time) desc"

-- | Query to get sum of subjects
--getSum :: IO (Maybe [String])
getSum =  makeQuery "select sum(time), Subject from todo group by Subject order by sum(time) desc"

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

-- | Generate Table
makeTable stats = "<table style='width:100%'>" ++ (mconcat (map  makeRow stats)) ++ "</table>"

-- | Generate stats


genStats = getSubjects >>= \x ->  mapM makeGithub x >>= \gits -> getAvg >>=
  \avg -> getSum >>= \sum -> getDataFileName "templates/header" >>= \x -> liftIO (readFile x) >>= \head -> return (head ++ table ++ (makeTable avg) ++ "</br> <h1> Sum </h1>" ++ (makeTable sum) ++ "</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 :: Maybe String -> IO String
makeGithub subject = do
  z <-   makeQuery ("select Due from todo where subject = '" ++ subject ++ "' and state = 0")
  color <- getColor
  let head = "<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 (head ++ (Prelude.concat q )++  bot)

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

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