{-# LANGUAGE FlexibleContexts #-} module Villefort.Database where import Control.Monad.IO.Class import Database.HDBC.Sqlite3 import Database.HDBC import Data.List.Split import System.Environment.FindBin import System.Environment import Paths_Villefort type Query = String type Path = String type Subject = String getSubjects :: IO [Subject] getSubjects = (\x-> (!! 0) <$> x) <$> makeQuery "select Subject from todo where state = 0 group by Subject" --path =fmap (\x -> (x !! 0) ++ "Villefort.app/Contents/Resources/") $ (Data.List.Split.splitOn "Villefort.app") <$> getProgPath --path :: IO Path path' :: IO FilePath path' = do args <- getArgs if args !! 0 == "--custom" then return $ args !! 1 else getDataDir getDb :: IO Connection getDb = (++ "/data/todo.db") <$> path' >>= \path -> connectSqlite3 path --convRow :: [[SqlValue]] -> [[String]] convRow dat = Prelude.map (\x -> Prelude.map (\y -> fromSql y :: String ) x) dat --makeQuery :: Query -> IO [[String]] makeQuery query = do conn <- getDb taskRaw <- quickQuery' conn query [] disconnect conn return (convRow taskRaw) {- makeQuery query = getDb >>= \conn -> quickQuery' conn query [] >>= \taskRaw -> disconnect conn >> return ( convRow taskRaw) -} --execQuery :: Query -> [Int] -> IO () execQuery query params = getDb >>= \conn -> prepare conn query >>= \stmt -> execute stmt ( map toSql params) >> commit conn >> disconnect conn getNextId ::IO Integer getNextId = do f <-liftIO $ makeQuery "select id from todo order by id desc" let rawid = head $ f let id = (read (rawid !! 0) :: Integer) +1 return id