Enable tags query over the query socket
[ganeti-local] / htools / Ganeti / Jobs.hs
index 3184a5a..405f833 100644 (file)
@@ -1,10 +1,12 @@
+{-# LANGUAGE TemplateHaskell #-}
+
 {-| Implementation of the job information.
 
 -}
 
 {-
 
-Copyright (C) 2009, 2010, 2011 Google Inc.
+Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
 
 This program is free software; you can redistribute it and/or modify
 it under the terms of the GNU General Public License as published by
@@ -24,73 +26,37 @@ Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
 -}
 
 module Ganeti.Jobs
-    ( OpStatus(..)
-    , JobStatus(..)
-    ) where
+  ( OpStatus(..)
+  , JobStatus(..)
+  ) where
 
 import Text.JSON (readJSON, showJSON, JSON)
-import qualified Text.JSON as J
 
 import qualified Ganeti.Constants as C
-
-data OpStatus = OP_STATUS_QUEUED
-              | OP_STATUS_WAITLOCK
-              | OP_STATUS_CANCELING
-              | OP_STATUS_RUNNING
-              | OP_STATUS_CANCELED
-              | OP_STATUS_SUCCESS
-              | OP_STATUS_ERROR
-                deriving (Eq, Enum, Bounded, Show, Read)
-
-instance JSON OpStatus where
-    showJSON os = showJSON w
-      where w = case os of
-              OP_STATUS_QUEUED -> C.jobStatusQueued
-              OP_STATUS_WAITLOCK -> C.jobStatusWaitlock
-              OP_STATUS_CANCELING -> C.jobStatusCanceling
-              OP_STATUS_RUNNING -> C.jobStatusRunning
-              OP_STATUS_CANCELED -> C.jobStatusCanceled
-              OP_STATUS_SUCCESS -> C.jobStatusSuccess
-              OP_STATUS_ERROR -> C.jobStatusError
-    readJSON s = case readJSON s of
-      J.Ok v | v == C.jobStatusQueued -> J.Ok OP_STATUS_QUEUED
-             | v == C.jobStatusWaitlock -> J.Ok OP_STATUS_WAITLOCK
-             | v == C.jobStatusCanceling -> J.Ok OP_STATUS_CANCELING
-             | v == C.jobStatusRunning -> J.Ok OP_STATUS_RUNNING
-             | v == C.jobStatusCanceled -> J.Ok OP_STATUS_CANCELED
-             | v == C.jobStatusSuccess -> J.Ok OP_STATUS_SUCCESS
-             | v == C.jobStatusError -> J.Ok OP_STATUS_ERROR
-             | otherwise -> J.Error ("Unknown opcode status " ++ v)
-      _ -> J.Error ("Cannot parse opcode status " ++ show s)
+import qualified Ganeti.THH as THH
+
+-- | Our ADT for the OpCode status at runtime (while in a job).
+$(THH.declareSADT "OpStatus"
+       [ ("OP_STATUS_QUEUED",    'C.opStatusQueued)
+       , ("OP_STATUS_WAITING",   'C.opStatusWaiting)
+       , ("OP_STATUS_CANCELING", 'C.opStatusCanceling)
+       , ("OP_STATUS_RUNNING",   'C.opStatusRunning)
+       , ("OP_STATUS_CANCELED",  'C.opStatusCanceled)
+       , ("OP_STATUS_SUCCESS",   'C.opStatusSuccess)
+       , ("OP_STATUS_ERROR",     'C.opStatusError)
+       ])
+$(THH.makeJSONInstance ''OpStatus)
 
 -- | The JobStatus data type. Note that this is ordered especially
 -- such that greater\/lesser comparison on values of this type makes
 -- sense.
-data JobStatus = JOB_STATUS_QUEUED
-               | JOB_STATUS_WAITLOCK
-               | JOB_STATUS_RUNNING
-               | JOB_STATUS_SUCCESS
-               | JOB_STATUS_CANCELING
-               | JOB_STATUS_CANCELED
-               | JOB_STATUS_ERROR
-                 deriving (Eq, Enum, Ord, Bounded, Show, Read)
-
-instance JSON JobStatus where
-    showJSON js = showJSON w
-        where w = case js of
-                JOB_STATUS_QUEUED -> "queued"
-                JOB_STATUS_WAITLOCK -> "waiting"
-                JOB_STATUS_CANCELING -> "canceling"
-                JOB_STATUS_RUNNING -> "running"
-                JOB_STATUS_CANCELED -> "canceled"
-                JOB_STATUS_SUCCESS -> "success"
-                JOB_STATUS_ERROR -> "error"
-    readJSON s = case readJSON s of
-      J.Ok "queued" -> J.Ok JOB_STATUS_QUEUED
-      J.Ok "waiting" -> J.Ok JOB_STATUS_WAITLOCK
-      J.Ok "canceling" -> J.Ok JOB_STATUS_CANCELING
-      J.Ok "running" -> J.Ok JOB_STATUS_RUNNING
-      J.Ok "success" -> J.Ok JOB_STATUS_SUCCESS
-      J.Ok "canceled" -> J.Ok JOB_STATUS_CANCELED
-      J.Ok "error" -> J.Ok JOB_STATUS_ERROR
-      _ -> J.Error ("Unknown job status " ++ show s)
+$(THH.declareSADT "JobStatus"
+       [ ("JOB_STATUS_QUEUED",    'C.jobStatusQueued)
+       , ("JOB_STATUS_WAITING",   'C.jobStatusWaiting)
+       , ("JOB_STATUS_CANCELING", 'C.jobStatusCanceling)
+       , ("JOB_STATUS_RUNNING",   'C.jobStatusRunning)
+       , ("JOB_STATUS_CANCELED",  'C.jobStatusCanceled)
+       , ("JOB_STATUS_SUCCESS",   'C.jobStatusSuccess)
+       , ("JOB_STATUS_ERROR",     'C.jobStatusError)
+       ])
+$(THH.makeJSONInstance ''JobStatus)