Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / JQueue.hs @ da1dcce1

History | View | Annotate | Download (11.4 kB)

1 aa79e62e Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 aa79e62e Iustin Pop
3 aa79e62e Iustin Pop
{-| Unittests for the job queue functionality.
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) 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 Test.Ganeti.JQueue (testJQueue) where
29 aa79e62e Iustin Pop
30 aa79e62e Iustin Pop
import Control.Applicative
31 aa79e62e Iustin Pop
import Control.Monad (when)
32 aa79e62e Iustin Pop
import Data.Char (isAscii)
33 aa79e62e Iustin Pop
import Data.List (nub, sort)
34 aa79e62e Iustin Pop
import System.Directory
35 aa79e62e Iustin Pop
import System.FilePath
36 aa79e62e Iustin Pop
import System.IO.Temp
37 aa79e62e Iustin Pop
import System.Posix.Files
38 aa79e62e Iustin Pop
import Test.HUnit
39 aa79e62e Iustin Pop
import Test.QuickCheck as QuickCheck
40 aa79e62e Iustin Pop
import Test.QuickCheck.Monadic
41 aa79e62e Iustin Pop
import Text.JSON
42 aa79e62e Iustin Pop
43 aa79e62e Iustin Pop
import Test.Ganeti.TestCommon
44 aa79e62e Iustin Pop
import Test.Ganeti.TestHelper
45 aa79e62e Iustin Pop
import Test.Ganeti.Types ()
46 aa79e62e Iustin Pop
import Test.Ganeti.OpCodes
47 aa79e62e Iustin Pop
48 aa79e62e Iustin Pop
import Ganeti.BasicTypes
49 aa79e62e Iustin Pop
import qualified Ganeti.Constants as C
50 aa79e62e Iustin Pop
import Ganeti.JQueue
51 aa79e62e Iustin Pop
import Ganeti.OpCodes
52 aa79e62e Iustin Pop
import Ganeti.Path
53 aa79e62e Iustin Pop
import Ganeti.Types as Types
54 aa79e62e Iustin Pop
55 aa79e62e Iustin Pop
{-# ANN module "HLint: ignore Use camelCase" #-}
56 aa79e62e Iustin Pop
57 aa79e62e Iustin Pop
-- * Helpers
58 aa79e62e Iustin Pop
59 aa79e62e Iustin Pop
-- | noTimestamp in Just form.
60 aa79e62e Iustin Pop
justNoTs :: Maybe Timestamp
61 aa79e62e Iustin Pop
justNoTs = Just noTimestamp
62 aa79e62e Iustin Pop
63 aa79e62e Iustin Pop
-- | Generates a simple queued opcode.
64 aa79e62e Iustin Pop
genQueuedOpCode :: Gen QueuedOpCode
65 aa79e62e Iustin Pop
genQueuedOpCode =
66 aa79e62e Iustin Pop
  QueuedOpCode <$> pure (ValidOpCode $ wrapOpCode OpClusterQuery) <*>
67 aa79e62e Iustin Pop
    arbitrary <*> pure JSNull <*> pure [] <*>
68 aa79e62e Iustin Pop
    choose (C.opPrioLowest, C.opPrioHighest) <*>
69 aa79e62e Iustin Pop
    pure justNoTs <*> pure justNoTs <*> pure justNoTs
70 aa79e62e Iustin Pop
71 aa79e62e Iustin Pop
-- | Generates an static, empty job.
72 aa79e62e Iustin Pop
emptyJob :: (Monad m) => m QueuedJob
73 aa79e62e Iustin Pop
emptyJob = do
74 aa79e62e Iustin Pop
  jid0 <- makeJobId 0
75 aa79e62e Iustin Pop
  return $ QueuedJob jid0 [] justNoTs justNoTs justNoTs
76 aa79e62e Iustin Pop
77 aa79e62e Iustin Pop
-- | Generates a job ID.
78 aa79e62e Iustin Pop
genJobId :: Gen JobId
79 aa79e62e Iustin Pop
genJobId = do
80 aa79e62e Iustin Pop
  p <- arbitrary::Gen (Types.NonNegative Int)
81 aa79e62e Iustin Pop
  makeJobId $ fromNonNegative p
82 aa79e62e Iustin Pop
83 aa79e62e Iustin Pop
-- * Test cases
84 aa79e62e Iustin Pop
85 aa79e62e Iustin Pop
-- | Tests default priority value.
86 aa79e62e Iustin Pop
case_JobPriorityDef :: Assertion
87 aa79e62e Iustin Pop
case_JobPriorityDef = do
88 aa79e62e Iustin Pop
  ej <- emptyJob
89 aa79e62e Iustin Pop
  assertEqual "for default priority" C.opPrioDefault $ calcJobPriority ej
90 aa79e62e Iustin Pop
91 aa79e62e Iustin Pop
-- | Test arbitrary priorities.
92 aa79e62e Iustin Pop
prop_JobPriority :: Property
93 aa79e62e Iustin Pop
prop_JobPriority =
94 aa79e62e Iustin Pop
  forAll (listOf1 (genQueuedOpCode `suchThat`
95 aa79e62e Iustin Pop
                   (not . opStatusFinalized . qoStatus))) $ \ops -> do
96 aa79e62e Iustin Pop
  jid0 <- makeJobId 0
97 aa79e62e Iustin Pop
  let job = QueuedJob jid0 ops justNoTs justNoTs justNoTs
98 aa79e62e Iustin Pop
  calcJobPriority job ==? minimum (map qoPriority ops)
99 aa79e62e Iustin Pop
100 aa79e62e Iustin Pop
-- | Tests default job status.
101 aa79e62e Iustin Pop
case_JobStatusDef :: Assertion
102 aa79e62e Iustin Pop
case_JobStatusDef = do
103 aa79e62e Iustin Pop
  ej <- emptyJob
104 aa79e62e Iustin Pop
  assertEqual "for job status" JOB_STATUS_SUCCESS $ calcJobStatus ej
105 aa79e62e Iustin Pop
106 aa79e62e Iustin Pop
-- | Test some job status properties.
107 aa79e62e Iustin Pop
prop_JobStatus :: Property
108 aa79e62e Iustin Pop
prop_JobStatus =
109 aa79e62e Iustin Pop
  forAll genJobId $ \jid ->
110 aa79e62e Iustin Pop
  forAll genQueuedOpCode $ \op ->
111 aa79e62e Iustin Pop
  let job1 = QueuedJob jid [op] justNoTs justNoTs justNoTs
112 aa79e62e Iustin Pop
      st1 = calcJobStatus job1
113 aa79e62e Iustin Pop
      op_succ = op { qoStatus = OP_STATUS_SUCCESS }
114 aa79e62e Iustin Pop
      op_err  = op { qoStatus = OP_STATUS_ERROR }
115 aa79e62e Iustin Pop
      op_cnl  = op { qoStatus = OP_STATUS_CANCELING }
116 aa79e62e Iustin Pop
      op_cnd  = op { qoStatus = OP_STATUS_CANCELED }
117 aa79e62e Iustin Pop
      -- computes status for a job with an added opcode before
118 aa79e62e Iustin Pop
      st_pre_op pop = calcJobStatus (job1 { qjOps = pop:qjOps job1 })
119 aa79e62e Iustin Pop
      -- computes status for a job with an added opcode after
120 aa79e62e Iustin Pop
      st_post_op pop = calcJobStatus (job1 { qjOps = qjOps job1 ++ [pop] })
121 aa79e62e Iustin Pop
  in conjoin
122 aa79e62e Iustin Pop
     [ printTestCase "pre-success doesn't change status"
123 aa79e62e Iustin Pop
       (st_pre_op op_succ ==? st1)
124 aa79e62e Iustin Pop
     , printTestCase "post-success doesn't change status"
125 aa79e62e Iustin Pop
       (st_post_op op_succ ==? st1)
126 aa79e62e Iustin Pop
     , printTestCase "pre-error is error"
127 aa79e62e Iustin Pop
       (st_pre_op op_err ==? JOB_STATUS_ERROR)
128 aa79e62e Iustin Pop
     , printTestCase "pre-canceling is canceling"
129 aa79e62e Iustin Pop
       (st_pre_op op_cnl ==? JOB_STATUS_CANCELING)
130 aa79e62e Iustin Pop
     , printTestCase "pre-canceled is canceled"
131 aa79e62e Iustin Pop
       (st_pre_op op_cnd ==? JOB_STATUS_CANCELED)
132 aa79e62e Iustin Pop
     ]
133 aa79e62e Iustin Pop
134 aa79e62e Iustin Pop
-- | Tests job status equivalence with Python. Very similar to OpCodes test.
135 aa79e62e Iustin Pop
case_JobStatusPri_py_equiv :: Assertion
136 aa79e62e Iustin Pop
case_JobStatusPri_py_equiv = do
137 aa79e62e Iustin Pop
  let num_jobs = 2000::Int
138 aa79e62e Iustin Pop
  sample_jobs <- sample' (vectorOf num_jobs $ do
139 aa79e62e Iustin Pop
                            num_ops <- choose (1, 5)
140 aa79e62e Iustin Pop
                            ops <- vectorOf num_ops genQueuedOpCode
141 aa79e62e Iustin Pop
                            jid <- genJobId
142 aa79e62e Iustin Pop
                            return $ QueuedJob jid ops justNoTs justNoTs
143 aa79e62e Iustin Pop
                                               justNoTs)
144 aa79e62e Iustin Pop
  let jobs = head sample_jobs
145 aa79e62e Iustin Pop
      serialized = encode jobs
146 aa79e62e Iustin Pop
  -- check for non-ASCII fields, usually due to 'arbitrary :: String'
147 aa79e62e Iustin Pop
  mapM_ (\job -> when (any (not . isAscii) (encode job)) .
148 aa79e62e Iustin Pop
                 assertFailure $ "Job has non-ASCII fields: " ++ show job
149 aa79e62e Iustin Pop
        ) jobs
150 aa79e62e Iustin Pop
  py_stdout <-
151 aa79e62e Iustin Pop
     runPython "from ganeti import jqueue\n\
152 aa79e62e Iustin Pop
               \from ganeti import serializer\n\
153 aa79e62e Iustin Pop
               \import sys\n\
154 aa79e62e Iustin Pop
               \job_data = serializer.Load(sys.stdin.read())\n\
155 aa79e62e Iustin Pop
               \decoded = [jqueue._QueuedJob.Restore(None, o, False, False)\n\
156 aa79e62e Iustin Pop
               \           for o in job_data]\n\
157 aa79e62e Iustin Pop
               \encoded = [(job.CalcStatus(), job.CalcPriority())\n\
158 aa79e62e Iustin Pop
               \           for job in decoded]\n\
159 aa79e62e Iustin Pop
               \print serializer.Dump(encoded)" serialized
160 aa79e62e Iustin Pop
     >>= checkPythonResult
161 aa79e62e Iustin Pop
  let deserialised = decode py_stdout::Text.JSON.Result [(String, Int)]
162 aa79e62e Iustin Pop
  decoded <- case deserialised of
163 aa79e62e Iustin Pop
               Text.JSON.Ok jobs' -> return jobs'
164 aa79e62e Iustin Pop
               Error msg ->
165 aa79e62e Iustin Pop
                 assertFailure ("Unable to decode jobs: " ++ msg)
166 aa79e62e Iustin Pop
                 -- this already raised an expection, but we need it
167 aa79e62e Iustin Pop
                 -- for proper types
168 aa79e62e Iustin Pop
                 >> fail "Unable to decode jobs"
169 aa79e62e Iustin Pop
  assertEqual "Mismatch in number of returned jobs"
170 aa79e62e Iustin Pop
    (length decoded) (length jobs)
171 aa79e62e Iustin Pop
  mapM_ (\(py_sp, job) ->
172 aa79e62e Iustin Pop
           let hs_sp = (jobStatusToRaw $ calcJobStatus job,
173 aa79e62e Iustin Pop
                        calcJobPriority job)
174 aa79e62e Iustin Pop
           in assertEqual ("Different result after encoding/decoding for " ++
175 aa79e62e Iustin Pop
                           show job) py_sp hs_sp
176 aa79e62e Iustin Pop
        ) $ zip decoded jobs
177 aa79e62e Iustin Pop
178 aa79e62e Iustin Pop
-- | Tests listing of Job ids.
179 aa79e62e Iustin Pop
prop_ListJobIDs :: Property
180 aa79e62e Iustin Pop
prop_ListJobIDs = monadicIO $ do
181 aa79e62e Iustin Pop
  jobs <- pick $ resize 10 (listOf1 genJobId `suchThat` (\l -> l == nub l))
182 aa79e62e Iustin Pop
  (e, f, g) <-
183 aa79e62e Iustin Pop
    run . withSystemTempDirectory "jqueue-test." $ \tempdir -> do
184 aa79e62e Iustin Pop
    empty_dir <- getJobIDs [tempdir]
185 aa79e62e Iustin Pop
    mapM_ (\jid -> writeFile (tempdir </> jobFileName jid) "") jobs
186 aa79e62e Iustin Pop
    full_dir <- getJobIDs [tempdir]
187 aa79e62e Iustin Pop
    invalid_dir <- getJobIDs [tempdir </> "no-such-dir"]
188 aa79e62e Iustin Pop
    return (empty_dir, sortJobIDs full_dir, invalid_dir)
189 aa79e62e Iustin Pop
  stop $ conjoin [ printTestCase "empty directory" $ e ==? []
190 aa79e62e Iustin Pop
                 , printTestCase "directory with valid names" $
191 aa79e62e Iustin Pop
                   f ==? sortJobIDs jobs
192 aa79e62e Iustin Pop
                 , printTestCase "invalid directory" $ g ==? []
193 aa79e62e Iustin Pop
                 ]
194 aa79e62e Iustin Pop
195 aa79e62e Iustin Pop
-- | Tests loading jobs from disk.
196 aa79e62e Iustin Pop
prop_LoadJobs :: Property
197 aa79e62e Iustin Pop
prop_LoadJobs = monadicIO $ do
198 aa79e62e Iustin Pop
  ops <- pick $ resize 5 (listOf1 genQueuedOpCode)
199 aa79e62e Iustin Pop
  jid <- pick genJobId
200 aa79e62e Iustin Pop
  let job = QueuedJob jid ops justNoTs justNoTs justNoTs
201 aa79e62e Iustin Pop
      job_s = encode job
202 aa79e62e Iustin Pop
  -- check that jobs in the right directories are parsed correctly
203 aa79e62e Iustin Pop
  (missing, current, archived, missing_current, broken) <-
204 aa79e62e Iustin Pop
    run  . withSystemTempDirectory "jqueue-test." $ \tempdir -> do
205 aa79e62e Iustin Pop
    let load a = loadJobFromDisk tempdir a jid
206 aa79e62e Iustin Pop
        live_path = liveJobFile tempdir jid
207 aa79e62e Iustin Pop
        arch_path = archivedJobFile tempdir jid
208 aa79e62e Iustin Pop
    createDirectory $ tempdir </> jobQueueArchiveSubDir
209 aa79e62e Iustin Pop
    createDirectory $ dropFileName arch_path
210 aa79e62e Iustin Pop
    -- missing job
211 aa79e62e Iustin Pop
    missing <- load True
212 aa79e62e Iustin Pop
    writeFile live_path job_s
213 aa79e62e Iustin Pop
    -- this should exist
214 aa79e62e Iustin Pop
    current <- load False
215 aa79e62e Iustin Pop
    removeFile live_path
216 aa79e62e Iustin Pop
    writeFile arch_path job_s
217 aa79e62e Iustin Pop
    -- this should exist (archived)
218 aa79e62e Iustin Pop
    archived <- load True
219 aa79e62e Iustin Pop
    -- this should be missing
220 aa79e62e Iustin Pop
    missing_current <- load False
221 aa79e62e Iustin Pop
    removeFile arch_path
222 aa79e62e Iustin Pop
    writeFile live_path "invalid job"
223 aa79e62e Iustin Pop
    broken <- load True
224 aa79e62e Iustin Pop
    return (missing, current, archived, missing_current, broken)
225 aa79e62e Iustin Pop
  stop $ conjoin [ missing ==? noSuchJob
226 aa79e62e Iustin Pop
                 , current ==? Ganeti.BasicTypes.Ok (job, False)
227 aa79e62e Iustin Pop
                 , archived ==? Ganeti.BasicTypes.Ok (job, True)
228 aa79e62e Iustin Pop
                 , missing_current ==? noSuchJob
229 aa79e62e Iustin Pop
                 , printTestCase "broken job" (isBad broken)
230 aa79e62e Iustin Pop
                 ]
231 aa79e62e Iustin Pop
232 aa79e62e Iustin Pop
-- | Tests computing job directories. Creates random directories,
233 aa79e62e Iustin Pop
-- files and stale symlinks in a directory, and checks that we return
234 aa79e62e Iustin Pop
-- \"the right thing\".
235 aa79e62e Iustin Pop
prop_DetermineDirs :: Property
236 aa79e62e Iustin Pop
prop_DetermineDirs = monadicIO $ do
237 aa79e62e Iustin Pop
  count <- pick $ choose (2, 10)
238 aa79e62e Iustin Pop
  nums <- pick $ genUniquesList count
239 aa79e62e Iustin Pop
          (arbitrary::Gen (QuickCheck.Positive Int))
240 aa79e62e Iustin Pop
  let (valid, invalid) = splitAt (count `div` 2) $
241 aa79e62e Iustin Pop
                         map (\(QuickCheck.Positive i) -> show i) nums
242 aa79e62e Iustin Pop
  (tempdir, non_arch, with_arch, invalid_root) <-
243 aa79e62e Iustin Pop
    run  . withSystemTempDirectory "jqueue-test." $ \tempdir -> do
244 aa79e62e Iustin Pop
    let arch_dir = tempdir </> jobQueueArchiveSubDir
245 aa79e62e Iustin Pop
    createDirectory arch_dir
246 aa79e62e Iustin Pop
    mapM_ (createDirectory . (arch_dir </>)) valid
247 aa79e62e Iustin Pop
    mapM_ (\p -> writeFile (arch_dir </> p) "") invalid
248 aa79e62e Iustin Pop
    mapM_ (\p -> createSymbolicLink "/dev/null/no/such/file"
249 aa79e62e Iustin Pop
                 (arch_dir </> p <.> "missing")) invalid
250 aa79e62e Iustin Pop
    non_arch <- determineJobDirectories tempdir False
251 aa79e62e Iustin Pop
    with_arch <- determineJobDirectories tempdir True
252 aa79e62e Iustin Pop
    invalid_root <- determineJobDirectories (tempdir </> "no-such-subdir") True
253 aa79e62e Iustin Pop
    return (tempdir, non_arch, with_arch, invalid_root)
254 aa79e62e Iustin Pop
  let arch_dir = tempdir </> jobQueueArchiveSubDir
255 aa79e62e Iustin Pop
  stop $ conjoin [ non_arch ==? [tempdir]
256 aa79e62e Iustin Pop
                 , sort with_arch ==? sort (tempdir:map (arch_dir </>) valid)
257 aa79e62e Iustin Pop
                 , invalid_root ==? [tempdir </> "no-such-subdir"]
258 aa79e62e Iustin Pop
                 ]
259 aa79e62e Iustin Pop
260 aa79e62e Iustin Pop
-- | Tests the JSON serialisation for 'InputOpCode'.
261 aa79e62e Iustin Pop
prop_InputOpCode :: MetaOpCode -> Int -> Property
262 aa79e62e Iustin Pop
prop_InputOpCode meta i =
263 aa79e62e Iustin Pop
  conjoin [ readJSON (showJSON valid)   ==? Text.JSON.Ok valid
264 aa79e62e Iustin Pop
          , readJSON (showJSON invalid) ==? Text.JSON.Ok invalid
265 aa79e62e Iustin Pop
          ]
266 aa79e62e Iustin Pop
    where valid = ValidOpCode meta
267 aa79e62e Iustin Pop
          invalid = InvalidOpCode (showJSON i)
268 aa79e62e Iustin Pop
269 aa79e62e Iustin Pop
-- | Tests 'extractOpSummary'.
270 aa79e62e Iustin Pop
prop_extractOpSummary :: MetaOpCode -> Int -> Property
271 aa79e62e Iustin Pop
prop_extractOpSummary meta i =
272 aa79e62e Iustin Pop
  conjoin [ printTestCase "valid opcode" $
273 aa79e62e Iustin Pop
            extractOpSummary (ValidOpCode meta)      ==? summary
274 aa79e62e Iustin Pop
          , printTestCase "invalid opcode, correct object" $
275 aa79e62e Iustin Pop
            extractOpSummary (InvalidOpCode jsobj)   ==? summary
276 aa79e62e Iustin Pop
          , printTestCase "invalid opcode, empty object" $
277 aa79e62e Iustin Pop
            extractOpSummary (InvalidOpCode emptyo)  ==? invalid
278 aa79e62e Iustin Pop
          , printTestCase "invalid opcode, object with invalid OP_ID" $
279 aa79e62e Iustin Pop
            extractOpSummary (InvalidOpCode invobj)  ==? invalid
280 aa79e62e Iustin Pop
          , printTestCase "invalid opcode, not jsobject" $
281 aa79e62e Iustin Pop
            extractOpSummary (InvalidOpCode jsinval) ==? invalid
282 aa79e62e Iustin Pop
          ]
283 aa79e62e Iustin Pop
    where summary = opSummary (metaOpCode meta)
284 aa79e62e Iustin Pop
          jsobj = showJSON $ toJSObject [("OP_ID",
285 aa79e62e Iustin Pop
                                          showJSON ("OP_" ++ summary))]
286 aa79e62e Iustin Pop
          emptyo = showJSON $ toJSObject ([]::[(String, JSValue)])
287 aa79e62e Iustin Pop
          invobj = showJSON $ toJSObject [("OP_ID", showJSON False)]
288 aa79e62e Iustin Pop
          jsinval = showJSON i
289 aa79e62e Iustin Pop
          invalid = "INVALID_OP"
290 aa79e62e Iustin Pop
291 aa79e62e Iustin Pop
testSuite "JQueue"
292 aa79e62e Iustin Pop
            [ 'case_JobPriorityDef
293 aa79e62e Iustin Pop
            , 'prop_JobPriority
294 aa79e62e Iustin Pop
            , 'case_JobStatusDef
295 aa79e62e Iustin Pop
            , 'prop_JobStatus
296 aa79e62e Iustin Pop
            , 'case_JobStatusPri_py_equiv
297 aa79e62e Iustin Pop
            , 'prop_ListJobIDs
298 aa79e62e Iustin Pop
            , 'prop_LoadJobs
299 aa79e62e Iustin Pop
            , 'prop_DetermineDirs
300 aa79e62e Iustin Pop
            , 'prop_InputOpCode
301 aa79e62e Iustin Pop
            , 'prop_extractOpSummary
302 aa79e62e Iustin Pop
            ]