Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / JQueue.hs @ 4b49a72b

History | View | Annotate | Download (11.3 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 4b49a72b Klaus Aehlig
    , queuedOpCodeFromMetaOpCode
33 aa79e62e Iustin Pop
    , Timestamp
34 aa79e62e Iustin Pop
    , noTimestamp
35 aa79e62e Iustin Pop
    , opStatusFinalized
36 aa79e62e Iustin Pop
    , extractOpSummary
37 aa79e62e Iustin Pop
    , calcJobStatus
38 aa79e62e Iustin Pop
    , calcJobPriority
39 aa79e62e Iustin Pop
    , jobFileName
40 aa79e62e Iustin Pop
    , liveJobFile
41 aa79e62e Iustin Pop
    , archivedJobFile
42 aa79e62e Iustin Pop
    , determineJobDirectories
43 aa79e62e Iustin Pop
    , getJobIDs
44 aa79e62e Iustin Pop
    , sortJobIDs
45 aa79e62e Iustin Pop
    , loadJobFromDisk
46 aa79e62e Iustin Pop
    , noSuchJob
47 aa79e62e Iustin Pop
    ) where
48 aa79e62e Iustin Pop
49 aa79e62e Iustin Pop
import Control.Exception
50 aa79e62e Iustin Pop
import Control.Monad
51 aa79e62e Iustin Pop
import Data.List
52 4b49a72b Klaus Aehlig
import Data.Maybe
53 aa79e62e Iustin Pop
import Data.Ord (comparing)
54 aa79e62e Iustin Pop
-- workaround what seems to be a bug in ghc 7.4's TH shadowing code
55 aa79e62e Iustin Pop
import Prelude hiding (log, id)
56 aa79e62e Iustin Pop
import System.Directory
57 aa79e62e Iustin Pop
import System.FilePath
58 aa79e62e Iustin Pop
import System.IO.Error (isDoesNotExistError)
59 aa79e62e Iustin Pop
import System.Posix.Files
60 aa79e62e Iustin Pop
import qualified Text.JSON
61 aa79e62e Iustin Pop
import Text.JSON.Types
62 aa79e62e Iustin Pop
63 aa79e62e Iustin Pop
import Ganeti.BasicTypes
64 aa79e62e Iustin Pop
import qualified Ganeti.Constants as C
65 aa79e62e Iustin Pop
import Ganeti.JSON
66 aa79e62e Iustin Pop
import Ganeti.Logging
67 aa79e62e Iustin Pop
import Ganeti.OpCodes
68 aa79e62e Iustin Pop
import Ganeti.Path
69 aa79e62e Iustin Pop
import Ganeti.THH
70 aa79e62e Iustin Pop
import Ganeti.Types
71 aa79e62e Iustin Pop
72 aa79e62e Iustin Pop
-- * Data types
73 aa79e62e Iustin Pop
74 aa79e62e Iustin Pop
-- | The ganeti queue timestamp type
75 aa79e62e Iustin Pop
type Timestamp = (Int, Int)
76 aa79e62e Iustin Pop
77 aa79e62e Iustin Pop
-- | Missing timestamp type.
78 aa79e62e Iustin Pop
noTimestamp :: Timestamp
79 aa79e62e Iustin Pop
noTimestamp = (-1, -1)
80 aa79e62e Iustin Pop
81 aa79e62e Iustin Pop
-- | An input opcode.
82 aa79e62e Iustin Pop
data InputOpCode = ValidOpCode MetaOpCode -- ^ OpCode was parsed successfully
83 aa79e62e Iustin Pop
                 | InvalidOpCode JSValue  -- ^ Invalid opcode
84 aa79e62e Iustin Pop
                   deriving (Show, Eq)
85 aa79e62e Iustin Pop
86 aa79e62e Iustin Pop
-- | JSON instance for 'InputOpCode', trying to parse it and if
87 aa79e62e Iustin Pop
-- failing, keeping the original JSValue.
88 aa79e62e Iustin Pop
instance Text.JSON.JSON InputOpCode where
89 aa79e62e Iustin Pop
  showJSON (ValidOpCode mo) = Text.JSON.showJSON mo
90 aa79e62e Iustin Pop
  showJSON (InvalidOpCode inv) = inv
91 aa79e62e Iustin Pop
  readJSON v = case Text.JSON.readJSON v of
92 aa79e62e Iustin Pop
                 Text.JSON.Error _ -> return $ InvalidOpCode v
93 aa79e62e Iustin Pop
                 Text.JSON.Ok mo -> return $ ValidOpCode mo
94 aa79e62e Iustin Pop
95 aa79e62e Iustin Pop
-- | Invalid opcode summary.
96 aa79e62e Iustin Pop
invalidOp :: String
97 aa79e62e Iustin Pop
invalidOp = "INVALID_OP"
98 aa79e62e Iustin Pop
99 aa79e62e Iustin Pop
-- | Tries to extract the opcode summary from an 'InputOpCode'. This
100 aa79e62e Iustin Pop
-- duplicates some functionality from the 'opSummary' function in
101 aa79e62e Iustin Pop
-- "Ganeti.OpCodes".
102 aa79e62e Iustin Pop
extractOpSummary :: InputOpCode -> String
103 aa79e62e Iustin Pop
extractOpSummary (ValidOpCode metaop) = opSummary $ metaOpCode metaop
104 aa79e62e Iustin Pop
extractOpSummary (InvalidOpCode (JSObject o)) =
105 aa79e62e Iustin Pop
  case fromObjWithDefault (fromJSObject o) "OP_ID" ("OP_" ++ invalidOp) of
106 aa79e62e Iustin Pop
    Just s -> drop 3 s -- drop the OP_ prefix
107 aa79e62e Iustin Pop
    Nothing -> invalidOp
108 aa79e62e Iustin Pop
extractOpSummary _ = invalidOp
109 aa79e62e Iustin Pop
110 aa79e62e Iustin Pop
$(buildObject "QueuedOpCode" "qo"
111 aa79e62e Iustin Pop
  [ simpleField "input"           [t| InputOpCode |]
112 aa79e62e Iustin Pop
  , simpleField "status"          [t| OpStatus    |]
113 aa79e62e Iustin Pop
  , simpleField "result"          [t| JSValue     |]
114 aa79e62e Iustin Pop
  , defaultField [| [] |] $
115 aa79e62e Iustin Pop
    simpleField "log"             [t| [(Int, Timestamp, ELogType, JSValue)] |]
116 aa79e62e Iustin Pop
  , simpleField "priority"        [t| Int         |]
117 aa79e62e Iustin Pop
  , optionalNullSerField $
118 aa79e62e Iustin Pop
    simpleField "start_timestamp" [t| Timestamp   |]
119 aa79e62e Iustin Pop
  , optionalNullSerField $
120 aa79e62e Iustin Pop
    simpleField "exec_timestamp"  [t| Timestamp   |]
121 aa79e62e Iustin Pop
  , optionalNullSerField $
122 aa79e62e Iustin Pop
    simpleField "end_timestamp"   [t| Timestamp   |]
123 aa79e62e Iustin Pop
  ])
124 aa79e62e Iustin Pop
125 aa79e62e Iustin Pop
$(buildObject "QueuedJob" "qj"
126 aa79e62e Iustin Pop
  [ simpleField "id"                 [t| JobId          |]
127 aa79e62e Iustin Pop
  , simpleField "ops"                [t| [QueuedOpCode] |]
128 aa79e62e Iustin Pop
  , optionalNullSerField $
129 aa79e62e Iustin Pop
    simpleField "received_timestamp" [t| Timestamp      |]
130 aa79e62e Iustin Pop
  , optionalNullSerField $
131 aa79e62e Iustin Pop
    simpleField "start_timestamp"    [t| Timestamp      |]
132 aa79e62e Iustin Pop
  , optionalNullSerField $
133 aa79e62e Iustin Pop
    simpleField "end_timestamp"      [t| Timestamp      |]
134 aa79e62e Iustin Pop
  ])
135 aa79e62e Iustin Pop
136 4b49a72b Klaus Aehlig
-- | Convenience function to obtain a QueuedOpCode from a MetaOpCode
137 4b49a72b Klaus Aehlig
queuedOpCodeFromMetaOpCode :: MetaOpCode -> QueuedOpCode
138 4b49a72b Klaus Aehlig
queuedOpCodeFromMetaOpCode op =
139 4b49a72b Klaus Aehlig
  QueuedOpCode { qoInput = ValidOpCode op
140 4b49a72b Klaus Aehlig
               , qoStatus = OP_STATUS_QUEUED
141 4b49a72b Klaus Aehlig
               , qoPriority = opSubmitPriorityToRaw . opPriority . metaParams
142 4b49a72b Klaus Aehlig
                              $ op
143 4b49a72b Klaus Aehlig
               , qoLog = []
144 4b49a72b Klaus Aehlig
               , qoResult = JSNull
145 4b49a72b Klaus Aehlig
               , qoStartTimestamp = Nothing
146 4b49a72b Klaus Aehlig
               , qoEndTimestamp = Nothing
147 4b49a72b Klaus Aehlig
               , qoExecTimestamp = Nothing
148 4b49a72b Klaus Aehlig
               }
149 4b49a72b Klaus Aehlig
150 aa79e62e Iustin Pop
-- | Job file prefix.
151 aa79e62e Iustin Pop
jobFilePrefix :: String
152 aa79e62e Iustin Pop
jobFilePrefix = "job-"
153 aa79e62e Iustin Pop
154 aa79e62e Iustin Pop
-- | Computes the filename for a given job ID.
155 aa79e62e Iustin Pop
jobFileName :: JobId -> FilePath
156 aa79e62e Iustin Pop
jobFileName jid = jobFilePrefix ++ show (fromJobId jid)
157 aa79e62e Iustin Pop
158 aa79e62e Iustin Pop
-- | Parses a job ID from a file name.
159 aa79e62e Iustin Pop
parseJobFileId :: (Monad m) => FilePath -> m JobId
160 aa79e62e Iustin Pop
parseJobFileId path =
161 aa79e62e Iustin Pop
  case stripPrefix jobFilePrefix path of
162 aa79e62e Iustin Pop
    Nothing -> fail $ "Job file '" ++ path ++
163 aa79e62e Iustin Pop
                      "' doesn't have the correct prefix"
164 aa79e62e Iustin Pop
    Just suffix -> makeJobIdS suffix
165 aa79e62e Iustin Pop
166 aa79e62e Iustin Pop
-- | Computes the full path to a live job.
167 aa79e62e Iustin Pop
liveJobFile :: FilePath -> JobId -> FilePath
168 aa79e62e Iustin Pop
liveJobFile rootdir jid = rootdir </> jobFileName jid
169 aa79e62e Iustin Pop
170 aa79e62e Iustin Pop
-- | Computes the full path to an archives job. BROKEN.
171 aa79e62e Iustin Pop
archivedJobFile :: FilePath -> JobId -> FilePath
172 aa79e62e Iustin Pop
archivedJobFile rootdir jid =
173 aa79e62e Iustin Pop
  let subdir = show (fromJobId jid `div` C.jstoreJobsPerArchiveDirectory)
174 aa79e62e Iustin Pop
  in rootdir </> jobQueueArchiveSubDir </> subdir </> jobFileName jid
175 aa79e62e Iustin Pop
176 aa79e62e Iustin Pop
-- | Map from opcode status to job status.
177 aa79e62e Iustin Pop
opStatusToJob :: OpStatus -> JobStatus
178 aa79e62e Iustin Pop
opStatusToJob OP_STATUS_QUEUED    = JOB_STATUS_QUEUED
179 aa79e62e Iustin Pop
opStatusToJob OP_STATUS_WAITING   = JOB_STATUS_WAITING
180 aa79e62e Iustin Pop
opStatusToJob OP_STATUS_SUCCESS   = JOB_STATUS_SUCCESS
181 aa79e62e Iustin Pop
opStatusToJob OP_STATUS_RUNNING   = JOB_STATUS_RUNNING
182 aa79e62e Iustin Pop
opStatusToJob OP_STATUS_CANCELING = JOB_STATUS_CANCELING
183 aa79e62e Iustin Pop
opStatusToJob OP_STATUS_CANCELED  = JOB_STATUS_CANCELED
184 aa79e62e Iustin Pop
opStatusToJob OP_STATUS_ERROR     = JOB_STATUS_ERROR
185 aa79e62e Iustin Pop
186 aa79e62e Iustin Pop
-- | Computes a queued job's status.
187 aa79e62e Iustin Pop
calcJobStatus :: QueuedJob -> JobStatus
188 aa79e62e Iustin Pop
calcJobStatus QueuedJob { qjOps = ops } =
189 aa79e62e Iustin Pop
  extractOpSt (map qoStatus ops) JOB_STATUS_QUEUED True
190 aa79e62e Iustin Pop
    where
191 aa79e62e Iustin Pop
      terminalStatus OP_STATUS_ERROR     = True
192 aa79e62e Iustin Pop
      terminalStatus OP_STATUS_CANCELING = True
193 aa79e62e Iustin Pop
      terminalStatus OP_STATUS_CANCELED  = True
194 aa79e62e Iustin Pop
      terminalStatus _                   = False
195 aa79e62e Iustin Pop
      softStatus     OP_STATUS_SUCCESS   = True
196 aa79e62e Iustin Pop
      softStatus     OP_STATUS_QUEUED    = True
197 aa79e62e Iustin Pop
      softStatus     _                   = False
198 aa79e62e Iustin Pop
      extractOpSt [] _ True = JOB_STATUS_SUCCESS
199 aa79e62e Iustin Pop
      extractOpSt [] d False = d
200 aa79e62e Iustin Pop
      extractOpSt (x:xs) d old_all
201 aa79e62e Iustin Pop
           | terminalStatus x = opStatusToJob x -- abort recursion
202 aa79e62e Iustin Pop
           | softStatus x     = extractOpSt xs d new_all -- continue unchanged
203 aa79e62e Iustin Pop
           | otherwise        = extractOpSt xs (opStatusToJob x) new_all
204 aa79e62e Iustin Pop
           where new_all = x == OP_STATUS_SUCCESS && old_all
205 aa79e62e Iustin Pop
206 aa79e62e Iustin Pop
-- | Determine whether an opcode status is finalized.
207 aa79e62e Iustin Pop
opStatusFinalized :: OpStatus -> Bool
208 aa79e62e Iustin Pop
opStatusFinalized = (> OP_STATUS_RUNNING)
209 aa79e62e Iustin Pop
210 aa79e62e Iustin Pop
-- | Compute a job's priority.
211 aa79e62e Iustin Pop
calcJobPriority :: QueuedJob -> Int
212 aa79e62e Iustin Pop
calcJobPriority QueuedJob { qjOps = ops } =
213 aa79e62e Iustin Pop
  helper . map qoPriority $ filter (not . opStatusFinalized . qoStatus) ops
214 aa79e62e Iustin Pop
    where helper [] = C.opPrioDefault
215 aa79e62e Iustin Pop
          helper ps = minimum ps
216 aa79e62e Iustin Pop
217 aa79e62e Iustin Pop
-- | Log but ignore an 'IOError'.
218 aa79e62e Iustin Pop
ignoreIOError :: a -> Bool -> String -> IOError -> IO a
219 aa79e62e Iustin Pop
ignoreIOError a ignore_noent msg e = do
220 aa79e62e Iustin Pop
  unless (isDoesNotExistError e && ignore_noent) .
221 aa79e62e Iustin Pop
    logWarning $ msg ++ ": " ++ show e
222 aa79e62e Iustin Pop
  return a
223 aa79e62e Iustin Pop
224 aa79e62e Iustin Pop
-- | Compute the list of existing archive directories. Note that I/O
225 aa79e62e Iustin Pop
-- exceptions are swallowed and ignored.
226 aa79e62e Iustin Pop
allArchiveDirs :: FilePath -> IO [FilePath]
227 aa79e62e Iustin Pop
allArchiveDirs rootdir = do
228 aa79e62e Iustin Pop
  let adir = rootdir </> jobQueueArchiveSubDir
229 aa79e62e Iustin Pop
  contents <- getDirectoryContents adir `Control.Exception.catch`
230 aa79e62e Iustin Pop
               ignoreIOError [] False
231 aa79e62e Iustin Pop
                 ("Failed to list queue directory " ++ adir)
232 aa79e62e Iustin Pop
  let fpaths = map (adir </>) $ filter (not . ("." `isPrefixOf`)) contents
233 aa79e62e Iustin Pop
  filterM (\path ->
234 aa79e62e Iustin Pop
             liftM isDirectory (getFileStatus (adir </> path))
235 aa79e62e Iustin Pop
               `Control.Exception.catch`
236 aa79e62e Iustin Pop
               ignoreIOError False True
237 aa79e62e Iustin Pop
                 ("Failed to stat archive path " ++ path)) fpaths
238 aa79e62e Iustin Pop
239 aa79e62e Iustin Pop
-- | Build list of directories containing job files. Note: compared to
240 aa79e62e Iustin Pop
-- the Python version, this doesn't ignore a potential lost+found
241 aa79e62e Iustin Pop
-- file.
242 aa79e62e Iustin Pop
determineJobDirectories :: FilePath -> Bool -> IO [FilePath]
243 aa79e62e Iustin Pop
determineJobDirectories rootdir archived = do
244 aa79e62e Iustin Pop
  other <- if archived
245 aa79e62e Iustin Pop
             then allArchiveDirs rootdir
246 aa79e62e Iustin Pop
             else return []
247 aa79e62e Iustin Pop
  return $ rootdir:other
248 aa79e62e Iustin Pop
249 3cecd73c Michele Tartara
-- Function equivalent to the \'sequence\' function, that cannot be used because
250 3cecd73c Michele Tartara
-- of library version conflict on Lucid.
251 3cecd73c Michele Tartara
-- FIXME: delete this and just use \'sequence\' instead when Lucid compatibility
252 3cecd73c Michele Tartara
-- will not be required anymore.
253 3cecd73c Michele Tartara
sequencer :: [Either IOError [JobId]] -> Either IOError [[JobId]]
254 3cecd73c Michele Tartara
sequencer l = fmap reverse $ foldl seqFolder (Right []) l
255 3cecd73c Michele Tartara
256 3cecd73c Michele Tartara
-- | Folding function for joining multiple [JobIds] into one list.
257 3cecd73c Michele Tartara
seqFolder :: Either IOError [[JobId]]
258 3cecd73c Michele Tartara
          -> Either IOError [JobId]
259 3cecd73c Michele Tartara
          -> Either IOError [[JobId]]
260 3cecd73c Michele Tartara
seqFolder (Left e) _ = Left e
261 3cecd73c Michele Tartara
seqFolder (Right _) (Left e) = Left e
262 3cecd73c Michele Tartara
seqFolder (Right l) (Right el) = Right $ el:l
263 3cecd73c Michele Tartara
264 aa79e62e Iustin Pop
-- | Computes the list of all jobs in the given directories.
265 be0cb2d7 Michele Tartara
getJobIDs :: [FilePath] -> IO (Either IOError [JobId])
266 3cecd73c Michele Tartara
getJobIDs paths = liftM (fmap concat . sequencer) (mapM getDirJobIDs paths)
267 aa79e62e Iustin Pop
268 aa79e62e Iustin Pop
-- | Sorts the a list of job IDs.
269 aa79e62e Iustin Pop
sortJobIDs :: [JobId] -> [JobId]
270 aa79e62e Iustin Pop
sortJobIDs = sortBy (comparing fromJobId)
271 aa79e62e Iustin Pop
272 aa79e62e Iustin Pop
-- | Computes the list of jobs in a given directory.
273 be0cb2d7 Michele Tartara
getDirJobIDs :: FilePath -> IO (Either IOError [JobId])
274 aa79e62e Iustin Pop
getDirJobIDs path = do
275 be0cb2d7 Michele Tartara
  either_contents <-
276 be0cb2d7 Michele Tartara
    try (getDirectoryContents path) :: IO (Either IOError [FilePath])
277 be0cb2d7 Michele Tartara
  case either_contents of
278 be0cb2d7 Michele Tartara
    Left e -> do
279 be0cb2d7 Michele Tartara
      logWarning $ "Failed to list job directory " ++ path ++ ": " ++ show e
280 be0cb2d7 Michele Tartara
      return $ Left e
281 be0cb2d7 Michele Tartara
    Right contents -> do
282 be0cb2d7 Michele Tartara
      let jids = foldl (\ids file ->
283 be0cb2d7 Michele Tartara
                         case parseJobFileId file of
284 be0cb2d7 Michele Tartara
                           Nothing -> ids
285 be0cb2d7 Michele Tartara
                           Just new_id -> new_id:ids) [] contents
286 be0cb2d7 Michele Tartara
      return . Right $ reverse jids
287 aa79e62e Iustin Pop
288 aa79e62e Iustin Pop
-- | Reads the job data from disk.
289 aa79e62e Iustin Pop
readJobDataFromDisk :: FilePath -> Bool -> JobId -> IO (Maybe (String, Bool))
290 aa79e62e Iustin Pop
readJobDataFromDisk rootdir archived jid = do
291 aa79e62e Iustin Pop
  let live_path = liveJobFile rootdir jid
292 aa79e62e Iustin Pop
      archived_path = archivedJobFile rootdir jid
293 aa79e62e Iustin Pop
      all_paths = if archived
294 aa79e62e Iustin Pop
                    then [(live_path, False), (archived_path, True)]
295 aa79e62e Iustin Pop
                    else [(live_path, False)]
296 aa79e62e Iustin Pop
  foldM (\state (path, isarchived) ->
297 aa79e62e Iustin Pop
           liftM (\r -> Just (r, isarchived)) (readFile path)
298 aa79e62e Iustin Pop
             `Control.Exception.catch`
299 aa79e62e Iustin Pop
             ignoreIOError state True
300 aa79e62e Iustin Pop
               ("Failed to read job file " ++ path)) Nothing all_paths
301 aa79e62e Iustin Pop
302 aa79e62e Iustin Pop
-- | Failed to load job error.
303 aa79e62e Iustin Pop
noSuchJob :: Result (QueuedJob, Bool)
304 aa79e62e Iustin Pop
noSuchJob = Bad "Can't load job file"
305 aa79e62e Iustin Pop
306 aa79e62e Iustin Pop
-- | Loads a job from disk.
307 aa79e62e Iustin Pop
loadJobFromDisk :: FilePath -> Bool -> JobId -> IO (Result (QueuedJob, Bool))
308 aa79e62e Iustin Pop
loadJobFromDisk rootdir archived jid = do
309 aa79e62e Iustin Pop
  raw <- readJobDataFromDisk rootdir archived jid
310 aa79e62e Iustin Pop
  -- note: we need some stricness below, otherwise the wrapping in a
311 aa79e62e Iustin Pop
  -- Result will create too much lazyness, and not close the file
312 aa79e62e Iustin Pop
  -- descriptors for the individual jobs
313 aa79e62e Iustin Pop
  return $! case raw of
314 aa79e62e Iustin Pop
             Nothing -> noSuchJob
315 aa79e62e Iustin Pop
             Just (str, arch) ->
316 aa79e62e Iustin Pop
               liftM (\qj -> (qj, arch)) .
317 aa79e62e Iustin Pop
               fromJResult "Parsing job file" $ Text.JSON.decode str