Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / JQueue.hs @ 01eea342

History | View | Annotate | Download (9.9 kB)

1 aa79e62e Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 aa79e62e Iustin Pop
3 aa79e62e Iustin Pop
{-| Implementation of the job queue.
4 aa79e62e Iustin Pop
5 aa79e62e Iustin Pop
-}
6 aa79e62e Iustin Pop
7 aa79e62e Iustin Pop
{-
8 aa79e62e Iustin Pop
9 aa79e62e Iustin Pop
Copyright (C) 2010, 2012 Google Inc.
10 aa79e62e Iustin Pop
11 aa79e62e Iustin Pop
This program is free software; you can redistribute it and/or modify
12 aa79e62e Iustin Pop
it under the terms of the GNU General Public License as published by
13 aa79e62e Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 aa79e62e Iustin Pop
(at your option) any later version.
15 aa79e62e Iustin Pop
16 aa79e62e Iustin Pop
This program is distributed in the hope that it will be useful, but
17 aa79e62e Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 aa79e62e Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 aa79e62e Iustin Pop
General Public License for more details.
20 aa79e62e Iustin Pop
21 aa79e62e Iustin Pop
You should have received a copy of the GNU General Public License
22 aa79e62e Iustin Pop
along with this program; if not, write to the Free Software
23 aa79e62e Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 aa79e62e Iustin Pop
02110-1301, USA.
25 aa79e62e Iustin Pop
26 aa79e62e Iustin Pop
-}
27 aa79e62e Iustin Pop
28 aa79e62e Iustin Pop
module Ganeti.JQueue
29 aa79e62e Iustin Pop
    ( QueuedOpCode(..)
30 aa79e62e Iustin Pop
    , QueuedJob(..)
31 aa79e62e Iustin Pop
    , InputOpCode(..)
32 aa79e62e Iustin Pop
    , Timestamp
33 aa79e62e Iustin Pop
    , noTimestamp
34 aa79e62e Iustin Pop
    , opStatusFinalized
35 aa79e62e Iustin Pop
    , extractOpSummary
36 aa79e62e Iustin Pop
    , calcJobStatus
37 aa79e62e Iustin Pop
    , calcJobPriority
38 aa79e62e Iustin Pop
    , jobFileName
39 aa79e62e Iustin Pop
    , liveJobFile
40 aa79e62e Iustin Pop
    , archivedJobFile
41 aa79e62e Iustin Pop
    , determineJobDirectories
42 aa79e62e Iustin Pop
    , getJobIDs
43 aa79e62e Iustin Pop
    , sortJobIDs
44 aa79e62e Iustin Pop
    , loadJobFromDisk
45 aa79e62e Iustin Pop
    , noSuchJob
46 aa79e62e Iustin Pop
    ) where
47 aa79e62e Iustin Pop
48 aa79e62e Iustin Pop
import Control.Exception
49 aa79e62e Iustin Pop
import Control.Monad
50 aa79e62e Iustin Pop
import Data.List
51 aa79e62e Iustin Pop
import Data.Ord (comparing)
52 aa79e62e Iustin Pop
-- workaround what seems to be a bug in ghc 7.4's TH shadowing code
53 aa79e62e Iustin Pop
import Prelude hiding (log, id)
54 aa79e62e Iustin Pop
import System.Directory
55 aa79e62e Iustin Pop
import System.FilePath
56 aa79e62e Iustin Pop
import System.IO.Error (isDoesNotExistError)
57 aa79e62e Iustin Pop
import System.Posix.Files
58 aa79e62e Iustin Pop
import qualified Text.JSON
59 aa79e62e Iustin Pop
import Text.JSON.Types
60 aa79e62e Iustin Pop
61 aa79e62e Iustin Pop
import Ganeti.BasicTypes
62 aa79e62e Iustin Pop
import qualified Ganeti.Constants as C
63 aa79e62e Iustin Pop
import Ganeti.JSON
64 aa79e62e Iustin Pop
import Ganeti.Logging
65 aa79e62e Iustin Pop
import Ganeti.OpCodes
66 aa79e62e Iustin Pop
import Ganeti.Path
67 aa79e62e Iustin Pop
import Ganeti.THH
68 aa79e62e Iustin Pop
import Ganeti.Types
69 aa79e62e Iustin Pop
70 aa79e62e Iustin Pop
-- * Data types
71 aa79e62e Iustin Pop
72 aa79e62e Iustin Pop
-- | The ganeti queue timestamp type
73 aa79e62e Iustin Pop
type Timestamp = (Int, Int)
74 aa79e62e Iustin Pop
75 aa79e62e Iustin Pop
-- | Missing timestamp type.
76 aa79e62e Iustin Pop
noTimestamp :: Timestamp
77 aa79e62e Iustin Pop
noTimestamp = (-1, -1)
78 aa79e62e Iustin Pop
79 aa79e62e Iustin Pop
-- | An input opcode.
80 aa79e62e Iustin Pop
data InputOpCode = ValidOpCode MetaOpCode -- ^ OpCode was parsed successfully
81 aa79e62e Iustin Pop
                 | InvalidOpCode JSValue  -- ^ Invalid opcode
82 aa79e62e Iustin Pop
                   deriving (Show, Eq)
83 aa79e62e Iustin Pop
84 aa79e62e Iustin Pop
-- | JSON instance for 'InputOpCode', trying to parse it and if
85 aa79e62e Iustin Pop
-- failing, keeping the original JSValue.
86 aa79e62e Iustin Pop
instance Text.JSON.JSON InputOpCode where
87 aa79e62e Iustin Pop
  showJSON (ValidOpCode mo) = Text.JSON.showJSON mo
88 aa79e62e Iustin Pop
  showJSON (InvalidOpCode inv) = inv
89 aa79e62e Iustin Pop
  readJSON v = case Text.JSON.readJSON v of
90 aa79e62e Iustin Pop
                 Text.JSON.Error _ -> return $ InvalidOpCode v
91 aa79e62e Iustin Pop
                 Text.JSON.Ok mo -> return $ ValidOpCode mo
92 aa79e62e Iustin Pop
93 aa79e62e Iustin Pop
-- | Invalid opcode summary.
94 aa79e62e Iustin Pop
invalidOp :: String
95 aa79e62e Iustin Pop
invalidOp = "INVALID_OP"
96 aa79e62e Iustin Pop
97 aa79e62e Iustin Pop
-- | Tries to extract the opcode summary from an 'InputOpCode'. This
98 aa79e62e Iustin Pop
-- duplicates some functionality from the 'opSummary' function in
99 aa79e62e Iustin Pop
-- "Ganeti.OpCodes".
100 aa79e62e Iustin Pop
extractOpSummary :: InputOpCode -> String
101 aa79e62e Iustin Pop
extractOpSummary (ValidOpCode metaop) = opSummary $ metaOpCode metaop
102 aa79e62e Iustin Pop
extractOpSummary (InvalidOpCode (JSObject o)) =
103 aa79e62e Iustin Pop
  case fromObjWithDefault (fromJSObject o) "OP_ID" ("OP_" ++ invalidOp) of
104 aa79e62e Iustin Pop
    Just s -> drop 3 s -- drop the OP_ prefix
105 aa79e62e Iustin Pop
    Nothing -> invalidOp
106 aa79e62e Iustin Pop
extractOpSummary _ = invalidOp
107 aa79e62e Iustin Pop
108 aa79e62e Iustin Pop
$(buildObject "QueuedOpCode" "qo"
109 aa79e62e Iustin Pop
  [ simpleField "input"           [t| InputOpCode |]
110 aa79e62e Iustin Pop
  , simpleField "status"          [t| OpStatus    |]
111 aa79e62e Iustin Pop
  , simpleField "result"          [t| JSValue     |]
112 aa79e62e Iustin Pop
  , defaultField [| [] |] $
113 aa79e62e Iustin Pop
    simpleField "log"             [t| [(Int, Timestamp, ELogType, JSValue)] |]
114 aa79e62e Iustin Pop
  , simpleField "priority"        [t| Int         |]
115 aa79e62e Iustin Pop
  , optionalNullSerField $
116 aa79e62e Iustin Pop
    simpleField "start_timestamp" [t| Timestamp   |]
117 aa79e62e Iustin Pop
  , optionalNullSerField $
118 aa79e62e Iustin Pop
    simpleField "exec_timestamp"  [t| Timestamp   |]
119 aa79e62e Iustin Pop
  , optionalNullSerField $
120 aa79e62e Iustin Pop
    simpleField "end_timestamp"   [t| Timestamp   |]
121 aa79e62e Iustin Pop
  ])
122 aa79e62e Iustin Pop
123 aa79e62e Iustin Pop
$(buildObject "QueuedJob" "qj"
124 aa79e62e Iustin Pop
  [ simpleField "id"                 [t| JobId          |]
125 aa79e62e Iustin Pop
  , simpleField "ops"                [t| [QueuedOpCode] |]
126 aa79e62e Iustin Pop
  , optionalNullSerField $
127 aa79e62e Iustin Pop
    simpleField "received_timestamp" [t| Timestamp      |]
128 aa79e62e Iustin Pop
  , optionalNullSerField $
129 aa79e62e Iustin Pop
    simpleField "start_timestamp"    [t| Timestamp      |]
130 aa79e62e Iustin Pop
  , optionalNullSerField $
131 aa79e62e Iustin Pop
    simpleField "end_timestamp"      [t| Timestamp      |]
132 aa79e62e Iustin Pop
  ])
133 aa79e62e Iustin Pop
134 aa79e62e Iustin Pop
-- | Job file prefix.
135 aa79e62e Iustin Pop
jobFilePrefix :: String
136 aa79e62e Iustin Pop
jobFilePrefix = "job-"
137 aa79e62e Iustin Pop
138 aa79e62e Iustin Pop
-- | Computes the filename for a given job ID.
139 aa79e62e Iustin Pop
jobFileName :: JobId -> FilePath
140 aa79e62e Iustin Pop
jobFileName jid = jobFilePrefix ++ show (fromJobId jid)
141 aa79e62e Iustin Pop
142 aa79e62e Iustin Pop
-- | Parses a job ID from a file name.
143 aa79e62e Iustin Pop
parseJobFileId :: (Monad m) => FilePath -> m JobId
144 aa79e62e Iustin Pop
parseJobFileId path =
145 aa79e62e Iustin Pop
  case stripPrefix jobFilePrefix path of
146 aa79e62e Iustin Pop
    Nothing -> fail $ "Job file '" ++ path ++
147 aa79e62e Iustin Pop
                      "' doesn't have the correct prefix"
148 aa79e62e Iustin Pop
    Just suffix -> makeJobIdS suffix
149 aa79e62e Iustin Pop
150 aa79e62e Iustin Pop
-- | Computes the full path to a live job.
151 aa79e62e Iustin Pop
liveJobFile :: FilePath -> JobId -> FilePath
152 aa79e62e Iustin Pop
liveJobFile rootdir jid = rootdir </> jobFileName jid
153 aa79e62e Iustin Pop
154 aa79e62e Iustin Pop
-- | Computes the full path to an archives job. BROKEN.
155 aa79e62e Iustin Pop
archivedJobFile :: FilePath -> JobId -> FilePath
156 aa79e62e Iustin Pop
archivedJobFile rootdir jid =
157 aa79e62e Iustin Pop
  let subdir = show (fromJobId jid `div` C.jstoreJobsPerArchiveDirectory)
158 aa79e62e Iustin Pop
  in rootdir </> jobQueueArchiveSubDir </> subdir </> jobFileName jid
159 aa79e62e Iustin Pop
160 aa79e62e Iustin Pop
-- | Map from opcode status to job status.
161 aa79e62e Iustin Pop
opStatusToJob :: OpStatus -> JobStatus
162 aa79e62e Iustin Pop
opStatusToJob OP_STATUS_QUEUED    = JOB_STATUS_QUEUED
163 aa79e62e Iustin Pop
opStatusToJob OP_STATUS_WAITING   = JOB_STATUS_WAITING
164 aa79e62e Iustin Pop
opStatusToJob OP_STATUS_SUCCESS   = JOB_STATUS_SUCCESS
165 aa79e62e Iustin Pop
opStatusToJob OP_STATUS_RUNNING   = JOB_STATUS_RUNNING
166 aa79e62e Iustin Pop
opStatusToJob OP_STATUS_CANCELING = JOB_STATUS_CANCELING
167 aa79e62e Iustin Pop
opStatusToJob OP_STATUS_CANCELED  = JOB_STATUS_CANCELED
168 aa79e62e Iustin Pop
opStatusToJob OP_STATUS_ERROR     = JOB_STATUS_ERROR
169 aa79e62e Iustin Pop
170 aa79e62e Iustin Pop
-- | Computes a queued job's status.
171 aa79e62e Iustin Pop
calcJobStatus :: QueuedJob -> JobStatus
172 aa79e62e Iustin Pop
calcJobStatus QueuedJob { qjOps = ops } =
173 aa79e62e Iustin Pop
  extractOpSt (map qoStatus ops) JOB_STATUS_QUEUED True
174 aa79e62e Iustin Pop
    where
175 aa79e62e Iustin Pop
      terminalStatus OP_STATUS_ERROR     = True
176 aa79e62e Iustin Pop
      terminalStatus OP_STATUS_CANCELING = True
177 aa79e62e Iustin Pop
      terminalStatus OP_STATUS_CANCELED  = True
178 aa79e62e Iustin Pop
      terminalStatus _                   = False
179 aa79e62e Iustin Pop
      softStatus     OP_STATUS_SUCCESS   = True
180 aa79e62e Iustin Pop
      softStatus     OP_STATUS_QUEUED    = True
181 aa79e62e Iustin Pop
      softStatus     _                   = False
182 aa79e62e Iustin Pop
      extractOpSt [] _ True = JOB_STATUS_SUCCESS
183 aa79e62e Iustin Pop
      extractOpSt [] d False = d
184 aa79e62e Iustin Pop
      extractOpSt (x:xs) d old_all
185 aa79e62e Iustin Pop
           | terminalStatus x = opStatusToJob x -- abort recursion
186 aa79e62e Iustin Pop
           | softStatus x     = extractOpSt xs d new_all -- continue unchanged
187 aa79e62e Iustin Pop
           | otherwise        = extractOpSt xs (opStatusToJob x) new_all
188 aa79e62e Iustin Pop
           where new_all = x == OP_STATUS_SUCCESS && old_all
189 aa79e62e Iustin Pop
190 aa79e62e Iustin Pop
-- | Determine whether an opcode status is finalized.
191 aa79e62e Iustin Pop
opStatusFinalized :: OpStatus -> Bool
192 aa79e62e Iustin Pop
opStatusFinalized = (> OP_STATUS_RUNNING)
193 aa79e62e Iustin Pop
194 aa79e62e Iustin Pop
-- | Compute a job's priority.
195 aa79e62e Iustin Pop
calcJobPriority :: QueuedJob -> Int
196 aa79e62e Iustin Pop
calcJobPriority QueuedJob { qjOps = ops } =
197 aa79e62e Iustin Pop
  helper . map qoPriority $ filter (not . opStatusFinalized . qoStatus) ops
198 aa79e62e Iustin Pop
    where helper [] = C.opPrioDefault
199 aa79e62e Iustin Pop
          helper ps = minimum ps
200 aa79e62e Iustin Pop
201 aa79e62e Iustin Pop
-- | Log but ignore an 'IOError'.
202 aa79e62e Iustin Pop
ignoreIOError :: a -> Bool -> String -> IOError -> IO a
203 aa79e62e Iustin Pop
ignoreIOError a ignore_noent msg e = do
204 aa79e62e Iustin Pop
  unless (isDoesNotExistError e && ignore_noent) .
205 aa79e62e Iustin Pop
    logWarning $ msg ++ ": " ++ show e
206 aa79e62e Iustin Pop
  return a
207 aa79e62e Iustin Pop
208 aa79e62e Iustin Pop
-- | Compute the list of existing archive directories. Note that I/O
209 aa79e62e Iustin Pop
-- exceptions are swallowed and ignored.
210 aa79e62e Iustin Pop
allArchiveDirs :: FilePath -> IO [FilePath]
211 aa79e62e Iustin Pop
allArchiveDirs rootdir = do
212 aa79e62e Iustin Pop
  let adir = rootdir </> jobQueueArchiveSubDir
213 aa79e62e Iustin Pop
  contents <- getDirectoryContents adir `Control.Exception.catch`
214 aa79e62e Iustin Pop
               ignoreIOError [] False
215 aa79e62e Iustin Pop
                 ("Failed to list queue directory " ++ adir)
216 aa79e62e Iustin Pop
  let fpaths = map (adir </>) $ filter (not . ("." `isPrefixOf`)) contents
217 aa79e62e Iustin Pop
  filterM (\path ->
218 aa79e62e Iustin Pop
             liftM isDirectory (getFileStatus (adir </> path))
219 aa79e62e Iustin Pop
               `Control.Exception.catch`
220 aa79e62e Iustin Pop
               ignoreIOError False True
221 aa79e62e Iustin Pop
                 ("Failed to stat archive path " ++ path)) fpaths
222 aa79e62e Iustin Pop
223 aa79e62e Iustin Pop
-- | Build list of directories containing job files. Note: compared to
224 aa79e62e Iustin Pop
-- the Python version, this doesn't ignore a potential lost+found
225 aa79e62e Iustin Pop
-- file.
226 aa79e62e Iustin Pop
determineJobDirectories :: FilePath -> Bool -> IO [FilePath]
227 aa79e62e Iustin Pop
determineJobDirectories rootdir archived = do
228 aa79e62e Iustin Pop
  other <- if archived
229 aa79e62e Iustin Pop
             then allArchiveDirs rootdir
230 aa79e62e Iustin Pop
             else return []
231 aa79e62e Iustin Pop
  return $ rootdir:other
232 aa79e62e Iustin Pop
233 aa79e62e Iustin Pop
-- | Computes the list of all jobs in the given directories.
234 aa79e62e Iustin Pop
getJobIDs :: [FilePath] -> IO [JobId]
235 aa79e62e Iustin Pop
getJobIDs = liftM concat . mapM getDirJobIDs
236 aa79e62e Iustin Pop
237 aa79e62e Iustin Pop
-- | Sorts the a list of job IDs.
238 aa79e62e Iustin Pop
sortJobIDs :: [JobId] -> [JobId]
239 aa79e62e Iustin Pop
sortJobIDs = sortBy (comparing fromJobId)
240 aa79e62e Iustin Pop
241 aa79e62e Iustin Pop
-- | Computes the list of jobs in a given directory.
242 aa79e62e Iustin Pop
getDirJobIDs :: FilePath -> IO [JobId]
243 aa79e62e Iustin Pop
getDirJobIDs path = do
244 aa79e62e Iustin Pop
  contents <- getDirectoryContents path `Control.Exception.catch`
245 aa79e62e Iustin Pop
                ignoreIOError [] False
246 aa79e62e Iustin Pop
                  ("Failed to list job directory " ++ path)
247 aa79e62e Iustin Pop
  let jids = foldl (\ids file ->
248 aa79e62e Iustin Pop
                      case parseJobFileId file of
249 aa79e62e Iustin Pop
                        Nothing -> ids
250 aa79e62e Iustin Pop
                        Just new_id -> new_id:ids) [] contents
251 aa79e62e Iustin Pop
  return $ reverse jids
252 aa79e62e Iustin Pop
253 aa79e62e Iustin Pop
-- | Reads the job data from disk.
254 aa79e62e Iustin Pop
readJobDataFromDisk :: FilePath -> Bool -> JobId -> IO (Maybe (String, Bool))
255 aa79e62e Iustin Pop
readJobDataFromDisk rootdir archived jid = do
256 aa79e62e Iustin Pop
  let live_path = liveJobFile rootdir jid
257 aa79e62e Iustin Pop
      archived_path = archivedJobFile rootdir jid
258 aa79e62e Iustin Pop
      all_paths = if archived
259 aa79e62e Iustin Pop
                    then [(live_path, False), (archived_path, True)]
260 aa79e62e Iustin Pop
                    else [(live_path, False)]
261 aa79e62e Iustin Pop
  foldM (\state (path, isarchived) ->
262 aa79e62e Iustin Pop
           liftM (\r -> Just (r, isarchived)) (readFile path)
263 aa79e62e Iustin Pop
             `Control.Exception.catch`
264 aa79e62e Iustin Pop
             ignoreIOError state True
265 aa79e62e Iustin Pop
               ("Failed to read job file " ++ path)) Nothing all_paths
266 aa79e62e Iustin Pop
267 aa79e62e Iustin Pop
-- | Failed to load job error.
268 aa79e62e Iustin Pop
noSuchJob :: Result (QueuedJob, Bool)
269 aa79e62e Iustin Pop
noSuchJob = Bad "Can't load job file"
270 aa79e62e Iustin Pop
271 aa79e62e Iustin Pop
-- | Loads a job from disk.
272 aa79e62e Iustin Pop
loadJobFromDisk :: FilePath -> Bool -> JobId -> IO (Result (QueuedJob, Bool))
273 aa79e62e Iustin Pop
loadJobFromDisk rootdir archived jid = do
274 aa79e62e Iustin Pop
  raw <- readJobDataFromDisk rootdir archived jid
275 aa79e62e Iustin Pop
  -- note: we need some stricness below, otherwise the wrapping in a
276 aa79e62e Iustin Pop
  -- Result will create too much lazyness, and not close the file
277 aa79e62e Iustin Pop
  -- descriptors for the individual jobs
278 aa79e62e Iustin Pop
  return $! case raw of
279 aa79e62e Iustin Pop
             Nothing -> noSuchJob
280 aa79e62e Iustin Pop
             Just (str, arch) ->
281 aa79e62e Iustin Pop
               liftM (\qj -> (qj, arch)) .
282 aa79e62e Iustin Pop
               fromJResult "Parsing job file" $ Text.JSON.decode str