module Villefort.Time  where

import Data.List.Split as S
import Data.Time
import Data.Time.Calendar.OrdinalDate

data D = D { year :: Integer,
             month :: Int,
             day :: Int} deriving (Show)

fromZonedTimeToDay :: String -> Day
fromZonedTimeToDay x = fromGregorian (year up) (month up ) (day up)
  where up = unpackStringToDate x

unpackStringToDate :: [Char] -> D
unpackStringToDate x = D (read (nums !! 0) :: Integer) (read (nums !! 1) :: Int) (read (nums !! 2) :: Int)
  where nums = S.splitOn "-" $  take 10 x
  
  
daysUntil :: [Char] -> IO Integer
daysUntil date = do
  let splits = S.splitOn "-" date
  current <- fromZonedTimeToDay <$> show <$> getZonedTime
  let due     = fromGregorian (read (splits !! 0) :: Integer) (read (splits !! 1) :: Int) (read (splits !! 2) :: Int)
  return $ (diffDays  due current) 

getDate :: IO Day
getDate = fromZonedTimeToDay <$> show <$> getZonedTime

getDateD :: IO D
getDateD = unpackStringToDate <$> show <$> getZonedTime

getDay :: IO Int
getDay = do
  z <- getDate
  return $ snd $mondayStartWeek z


getStartOfWeek :: IO Day
getStartOfWeek = do
  currentDay <- toInteger <$> getDay
  today <- getDate
  return $ addDays (-currentDay) today
 
 
getDatesOfWeek :: IO [Day]
getDatesOfWeek = do
  start <- getStartOfWeek
  currentDay <- getDay
  return $ tail $ take (currentDay+1) $ scanl next start [1,1 .. ]
  where next s x = addDays (x) s


getDatesOfPrevWeek :: IO [Day]
getDatesOfPrevWeek = do
  start <- addDays (-6) <$> getStartOfWeek
  currentDay <- getDay
  return $ [start ,last $ take (currentDay+2) $ scanl next start [1,1 .. ]]
  where next s   x = addDays (x) s

getDatesOfThisWeek :: IO [Day]
getDatesOfThisWeek = do
  start <- addDays (1) <$> getStartOfWeek
  currentDay <- getDay
  return $ [start ,last $ take (currentDay+2) $ scanl next start [1,1 .. ]]
  where next s   x = addDays (x) s