--------------------------------------------------------------------
-- |
-- Module    : Generate sparkline graphs of hackage uploads
-- Copyright : (c) Don Stewart 2008
-- License   : BSD3
--
-- Maintainer: Don Stewart <dons@galois.com>
-- Stability : provisional
-- Portability:
--
--------------------------------------------------------------------

import Data.List
import Data.Maybe
import Graphics.Rendering.HSparklines
import System.Locale
import System.Time
import System.Time.Parse
import System.Directory
import System.FilePath
import Text.HTML.Download

url = "http://hackage.haskell.org/packages/archive/log"

png1 = "hackage-monthly.png"
png2 = "hackage-daily.png"

main :: IO ()
main = do
    pwd <- getCurrentDirectory
    src <- openURL url
    let dates    = catMaybes . sort . map parse . lines $ src

    -- uploads per year
    let  permonth = groupBy month dates
    graph <- make ((barSpark {bgColor = rgb 0xee 0xee 0xee}) ) (map genericLength permonth)
    savePngFile png1 graph
    putStrLn $ "Wrote: " ++ pwd </> png1

    -- print uploads this month
    let today = last dates
        thismonth = groupBy day . filter (month today) $ dates
    graph <- make ((barSpark {bgColor = rgb 0xee 0xee 0xee
                             , limits = (0,20)} )) (map genericLength thismonth)
    savePngFile png2 graph
    putStrLn $ "Wrote: " ++ pwd </> png2

  where
    parse = parseCalendarTime defaultTimeLocale "%c"
    month a b = ctYear a == ctYear b && ctMonth a == ctMonth b
    day   a b = month a b && ctDay a == ctDay b