aboutsummaryrefslogtreecommitdiff
path: root/src/server/Job/Model.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/server/Job/Model.hs')
-rw-r--r--src/server/Job/Model.hs64
1 files changed, 39 insertions, 25 deletions
diff --git a/src/server/Job/Model.hs b/src/server/Job/Model.hs
index cd7297a..e1a3c77 100644
--- a/src/server/Job/Model.hs
+++ b/src/server/Job/Model.hs
@@ -1,33 +1,47 @@
+{-# LANGUAGE OverloadedStrings #-}
+
module Job.Model
- ( getLastExecution
+ ( Job(..)
+ , getLastExecution
, actualizeLastExecution
, actualizeLastCheck
) where
-import Control.Monad.IO.Class (liftIO)
-
-import Data.Time.Clock (UTCTime, getCurrentTime)
import Data.Maybe (isJust)
-
-import Database.Persist
-
-import Model.Database
+import Data.Time.Clock (UTCTime, getCurrentTime)
+import Database.SQLite.Simple (Only(Only))
+import qualified Database.SQLite.Simple as SQLite
+import Prelude hiding (id)
import Job.Kind
-
-getLastExecution :: Kind -> Persist (Maybe UTCTime)
-getLastExecution kind = do
- mbJob <- fmap entityVal <$> selectFirst [JobKind ==. kind] []
- return (mbJob >>= jobLastExecution)
-
-actualizeLastExecution :: Kind -> UTCTime -> Persist ()
-actualizeLastExecution kind time = do
- jobKindDefined <- isJust <$> selectFirst [JobKind ==. kind] []
- if jobKindDefined
- then updateWhere [JobKind ==. kind] [JobLastExecution =. Just time]
- else insert (Job kind (Just time) (Just time)) >> return ()
-
-actualizeLastCheck :: Kind -> Persist ()
-actualizeLastCheck kind = do
- now <- liftIO getCurrentTime
- updateWhere [JobKind ==. kind] [JobLastCheck =. Just now]
+import Model.Query (Query(Query))
+
+data Job = Job
+ { id :: String
+ , kind :: Kind
+ , lastExecution :: Maybe UTCTime
+ , lastCheck :: Maybe UTCTime
+ } deriving (Show)
+
+getLastExecution :: Kind -> Query (Maybe UTCTime)
+getLastExecution jobKind =
+ Query (\conn -> do
+ [Only time] <- SQLite.query conn "SELECT last_execution FROM job WHERE kind = ?" (Only jobKind) :: IO [Only (Maybe UTCTime)]
+ return time
+ )
+
+actualizeLastExecution :: Kind -> UTCTime -> Query ()
+actualizeLastExecution jobKind time =
+ Query (\conn -> do
+ [Only result] <- SQLite.query conn "SELECT 1 FROM job WHERE kind = ?" (Only jobKind) :: IO [Only (Maybe Int)]
+ if isJust result
+ then SQLite.execute conn "UPDATE job SET last_execution = ? WHERE kind = ?" (time, jobKind)
+ else SQLite.execute conn "INSERT INTO job (kind, last_execution, last_check) VALUES (?, ?, ?)" (jobKind, time, time)
+ )
+
+actualizeLastCheck :: Kind -> Query ()
+actualizeLastCheck jobKind =
+ Query (\conn -> do
+ now <- getCurrentTime
+ SQLite.execute conn "UPDATE job SET kind = ? WHERE last_check = ?" (jobKind, now)
+ )