gdritter repos bb8 / master src / BB8 / DB.hs
master

Tree @master (Download .tar.gz)

DB.hs @masterraw · history · blame

module BB8.DB where

import qualified Database.SQLite.Simple as SQL

import BB8.Types


type Query t = SQL.Connection -> IO t


-- * Queries that return jobs

getNextJob :: Query (Maybe Job)
getNextJob conn = do
  rs <- SQL.query_ conn " SELECT j.id, j.name, j.owner, j.team, j.state, j.jira \
                        \ FROM jobs j WHERE j.state = \"fetching\" \
                        \ ORDER BY j.id"
  return $ case rs of
    [] -> Nothing
    (jID, name, owner, team, state, jira):_ ->
      Just (Job name (User owner team) jID state jira Nothing)

getJobs :: Query [Job]
getJobs conn = do
  rs <- SQL.query_ conn " SELECT j.id, j.name, j.owner, j.team, j.state, j.jira \
                        \ FROM jobs j WHERE j.state != \"deleted\" ORDER BY j.id DESC "
  return [ Job name (User owner team) jID state jira Nothing
         | (jID, name, owner, team, state, jira) <- rs
         ]

getJobById :: Integer -> Query [Job]
getJobById ident conn = do
  rs <- SQL.query conn " SELECT j.id, j.name, j.owner, j.team, j.state, j.jira, t.name \
                       \ FROM jobs j, tags t WHERE t.id = j.tag AND j.id = ? " (SQL.Only ident)
  return [ Job name (User owner team) jID state jira tag
         | (jID, name, owner, team, state, jira, tag) <- rs
         ]

deleteJob :: Integer -> Query ()
deleteJob ident conn = do
  SQL.execute conn " UPDATE jobs SET state = \"deleted\" WHERE id = ?" (SQL.Only ident)

getJobState :: Integer -> Query (Maybe JobState)
getJobState ident conn = do
  return Nothing

-- -- * Queries that return timing info for a job

-- getJobTimes :: Integer -> Query [TimingInfo]
-- getJobTimes ident conn =
--   SQL.query conn " SELECT (name, start, end, duration) FROM timings WHERE id = ?"
--     (SQL.Only ident)


-- -- * Queries that return current tags

-- getTags :: Query [Text]
-- getTags conn = do
--   rs <- SQL.query_ conn "SELECT name FROM tags"
--   return (map SQL.fromOnly rs)


-- * Saving jobs

createJob :: Job -> Query Job
createJob job@(Job name (User owner team) _ _ jira _) conn = do
  SQL.execute conn
    " INSERT INTO jobs (name, owner, team, state, for_the_record, jira, tag) \
    \ VALUES (?, ?, ?, \"fetching\", ?, ?, NULL) "
    (name, owner, team, False, jira)
  return job

recordJob :: Job -> Query ()
recordJob job conn = do
  SQL.execute conn "UPDATE jobs SET state = ? WHERE id = ?" (jobState job, jobID job)
  return ()