module Todo where

import Database
import Data.List.Split
import Control.Monad.IO.Class
import Data.Time
import Data.List.Split as S
import Paths_Villefort


data Row = Row { rid :: Int,
                 title :: String,
                 description :: String,
                 due :: String,
                 time :: Int
               } deriving (Show)

toRow :: [String] -> Row
toRow x = Row (read (x !! 0) :: Int) (x !! 1) (x !! 2) (x !! 3) (read( x !! 4) :: Int)

qetTasks' =  makeQuery " select id, Title, Description, Due, sum(time) from todo where state = 1 group by Title, Description order by Due " >>=
  \x -> return (map toRow x)





merge [] ys = ys
merge (x:xs) ys = x:merge ys xs


  
genModal' row = do
  let f = due row
  modal <- getModal
  days  <- daysTilDue f
  let da = [daysToColor' days ,
            show $ rid row,
            (convTitle $ title row) ++ "Due in " ++  show days,
            show $ rid row,
            title row,
            description row,
            "/delete",
            show $ time row,
            show $ rid row
           ]
           
  return $ mconcat $  merge modal da
 

--genModal row =

daysToColor' x = if x < 1 then "btn-due0"
            else if x == 1 then "btn-due1"
            else if x == 2 then "btn-due2"
            else if x == 3 then "btn-due3"
            else if x == 4 then "btn-due4"
            else if x == 5 then "btn-due5"
            else if x == 6 then "btn-due6"
            else "btn-due7"




convTitle title
  | length s1 > 30 = s1
  | length s2 > 30 = s2
  | length s3 > 30 = s3
  | length s4 > 30 = s4
  | otherwise = title
  where split = (Data.List.Split.splitOn "." title)
        s1 = (split !! 0)
        s2 = mconcat (take 2 split)
        s3 = mconcat (take 3 split)
        s4 = mconcat (take 4 split)
          

getModal :: IO [[Char]]
--getModal =  path >>= \path -> readFile (path ++ "templates/modal.ts") >>= \rawModal -> return  (Data.List.Split.splitOn "}" rawModal)
getModal =  getDataFileName "templates/modal.ts" >>= \path -> readFile path>>= \rawModal -> return  (Data.List.Split.splitOn "}" rawModal)

daysTilDue date = do
  c <- getCurrentTime
  let (y,m,d) = toGregorian $ utctDay c
  let split = Data.List.Split.splitOn "-" date
  current <- fromZonedTimeToDay <$> show <$> getZonedTime
  let due     = fromGregorian (read (split !! 0) :: Integer) (read (split !! 1) :: Int) (read (split !! 2) :: Int)
  return $ (diffDays  due current) 

fromZonedTimeToDay x = fromGregorian (read (nums !! 0) :: Integer) (read (nums !! 1) :: Int) (read (nums !! 2) :: Int) 
  where nums = S.splitOn "-" $  take 10 x
  

getTodos = do
  tasks <-  qetTasks'
  path  <- path 
  modals <- sequence $ Prelude.map genModal'  tasks
  path   <- getDataFileName "templates/index.html"
  header <- readFile path
  let body = Prelude.concat modals
  return (header ++  body)

deleteTodo raw = do
    let da   = Data.List.Split.splitOn "&" (show raw)
    let rawid = Data.List.Split.splitOn "=" $  (Prelude.init (da !! 1))
    let id   = read (rawid!! 1) :: Int
    let rawtime = Data.List.Split.splitOn "=" $ (da !! 0)
    let time = read (rawtime !! 1) :: Int
    do liftIO $ delTask id 
    do liftIO $ addTime id time
    return ()


addTime :: Int -> Int -> IO ()
addTime id time = execQuery "update todo set time = ? where id = ?" [time,id]
  
delTask :: Int ->  IO ()
delTask id = execQuery "update todo  set state = 0 where id = ?" [id]

updateTask :: Int -> Int ->  IO ()
updateTask id time = execQuery "insert into todo (Description,Title,Entered,Due,state,time,Subject) select Description,Title,Entered,Due,0,time+?,Subject from todo where id = ?" [ time, id]