Cleanup HTools.Types/BasicTypes imports
[ganeti-local] / htools / Ganeti / OpCodes.hs
index 4b750af..566c5db 100644 (file)
@@ -1,10 +1,12 @@
+{-# LANGUAGE TemplateHaskell #-}
+
 {-| Implementation of the opcodes.
 
 -}
 
 {-
 
-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,116 +26,84 @@ Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
 -}
 
 module Ganeti.OpCodes
-    ( OpCode(..)
-    , ReplaceDisksMode(..)
-    , opID
-    ) where
+  ( OpCode(..)
+  , ReplaceDisksMode(..)
+  , DiskIndex
+  , mkDiskIndex
+  , unDiskIndex
+  , opID
+  , allOpIDs
+  ) where
 
-import Control.Monad
 import Text.JSON (readJSON, showJSON, makeObj, JSON)
-import qualified Text.JSON as J
-import Text.JSON.Types
-
-import Ganeti.HTools.Utils
-
-data ReplaceDisksMode = ReplaceOnPrimary
-                  | ReplaceOnSecondary
-                  | ReplaceNewSecondary
-                  | ReplaceAuto
-                  deriving (Show, Read, Eq)
-
-instance JSON ReplaceDisksMode where
-    showJSON m = case m of
-                 ReplaceOnPrimary -> showJSON "replace_on_primary"
-                 ReplaceOnSecondary -> showJSON "replace_on_secondary"
-                 ReplaceNewSecondary -> showJSON "replace_new_secondary"
-                 ReplaceAuto -> showJSON "replace_auto"
-    readJSON s = case readJSON s of
-                   J.Ok "replace_on_primary" -> J.Ok ReplaceOnPrimary
-                   J.Ok "replace_on_secondary" -> J.Ok ReplaceOnSecondary
-                   J.Ok "replace_new_secondary" -> J.Ok ReplaceNewSecondary
-                   J.Ok "replace_auto" -> J.Ok ReplaceAuto
-                   _ -> J.Error "Can't parse a valid ReplaceDisksMode"
-
-data OpCode = OpTestDelay Double Bool [String]
-            | OpReplaceDisks String (Maybe String) ReplaceDisksMode
-              [Int] (Maybe String)
-            | OpFailoverInstance String Bool
-            | OpMigrateInstance String Bool Bool Bool
-            deriving (Show, Read, Eq)
-
-
-opID :: OpCode -> String
-opID (OpTestDelay _ _ _) = "OP_TEST_DELAY"
-opID (OpReplaceDisks _ _ _ _ _) = "OP_INSTANCE_REPLACE_DISKS"
-opID (OpFailoverInstance _ _) = "OP_INSTANCE_FAILOVER"
-opID (OpMigrateInstance _ _ _ _) = "OP_INSTANCE_MIGRATE"
-
-loadOpCode :: JSValue -> J.Result OpCode
-loadOpCode v = do
-  o <- liftM J.fromJSObject (readJSON v)
-  let extract x = fromObj o x
-  op_id <- extract "OP_ID"
-  case op_id of
-    "OP_TEST_DELAY" -> do
-                 on_nodes  <- extract "on_nodes"
-                 on_master <- extract "on_master"
-                 duration  <- extract "duration"
-                 return $ OpTestDelay duration on_master on_nodes
-    "OP_INSTANCE_REPLACE_DISKS" -> do
-                 inst   <- extract "instance_name"
-                 node   <- maybeFromObj o "remote_node"
-                 mode   <- extract "mode"
-                 disks  <- extract "disks"
-                 ialloc <- maybeFromObj o "iallocator"
-                 return $ OpReplaceDisks inst node mode disks ialloc
-    "OP_INSTANCE_FAILOVER" -> do
-                 inst    <- extract "instance_name"
-                 consist <- extract "ignore_consistency"
-                 return $ OpFailoverInstance inst consist
-    "OP_INSTANCE_MIGRATE" -> do
-                 inst    <- extract "instance_name"
-                 live    <- extract "live"
-                 cleanup <- extract "cleanup"
-                 allow_failover <- extract "allow_failover"
-                 return $ OpMigrateInstance inst live cleanup allow_failover
-    _ -> J.Error $ "Unknown opcode " ++ op_id
-
-saveOpCode :: OpCode -> JSValue
-saveOpCode op@(OpTestDelay duration on_master on_nodes) =
-    let ol = [ ("OP_ID", showJSON $ opID op)
-             , ("duration", showJSON duration)
-             , ("on_master", showJSON on_master)
-             , ("on_nodes", showJSON on_nodes) ]
-    in makeObj ol
-
-saveOpCode op@(OpReplaceDisks inst node mode disks iallocator) =
-    let ol = [ ("OP_ID", showJSON $ opID op)
-             , ("instance_name", showJSON inst)
-             , ("mode", showJSON mode)
-             , ("disks", showJSON disks)]
-        ol2 = case node of
-                Just n -> ("remote_node", showJSON n):ol
-                Nothing -> ol
-        ol3 = case iallocator of
-                Just i -> ("iallocator", showJSON i):ol2
-                Nothing -> ol2
-    in makeObj ol3
-
-saveOpCode op@(OpFailoverInstance inst consist) =
-    let ol = [ ("OP_ID", showJSON $ opID op)
-             , ("instance_name", showJSON inst)
-             , ("ignore_consistency", showJSON consist) ]
-    in makeObj ol
-
-saveOpCode op@(OpMigrateInstance inst live cleanup allow_failover) =
-    let ol = [ ("OP_ID", showJSON $ opID op)
-             , ("instance_name", showJSON inst)
-             , ("live", showJSON live)
-             , ("cleanup", showJSON cleanup)
-             , ("allow_failover", showJSON allow_failover) ]
-    in makeObj ol
+
+import qualified Ganeti.Constants as C
+import Ganeti.THH
+
+import Ganeti.JSON
+
+-- | Replace disks type.
+$(declareSADT "ReplaceDisksMode"
+  [ ("ReplaceOnPrimary",    'C.replaceDiskPri)
+  , ("ReplaceOnSecondary",  'C.replaceDiskSec)
+  , ("ReplaceNewSecondary", 'C.replaceDiskChg)
+  , ("ReplaceAuto",         'C.replaceDiskAuto)
+  ])
+$(makeJSONInstance ''ReplaceDisksMode)
+
+-- | Disk index type (embedding constraints on the index value via a
+-- smart constructor).
+newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
+  deriving (Show, Read, Eq, Ord)
+
+-- | Smart constructor for 'DiskIndex'.
+mkDiskIndex :: (Monad m) => Int -> m DiskIndex
+mkDiskIndex i | i >= 0 && i < C.maxDisks = return (DiskIndex i)
+              | otherwise = fail $ "Invalid value for disk index '" ++
+                            show i ++ "', required between 0 and " ++
+                            show C.maxDisks
+
+instance JSON DiskIndex where
+  readJSON v = readJSON v >>= mkDiskIndex
+  showJSON = showJSON . unDiskIndex
+
+-- | OpCode representation.
+--
+-- We only implement a subset of Ganeti opcodes, but only what we
+-- actually use in the htools codebase.
+$(genOpCode "OpCode"
+  [ ("OpTestDelay",
+     [ simpleField "duration"  [t| Double   |]
+     , simpleField "on_master" [t| Bool     |]
+     , simpleField "on_nodes"  [t| [String] |]
+     ])
+  , ("OpInstanceReplaceDisks",
+     [ simpleField "instance_name" [t| String |]
+     , optionalField $ simpleField "remote_node" [t| String |]
+     , simpleField "mode"  [t| ReplaceDisksMode |]
+     , simpleField "disks" [t| [DiskIndex] |]
+     , optionalField $ simpleField "iallocator" [t| String |]
+     ])
+  , ("OpInstanceFailover",
+     [ simpleField "instance_name"      [t| String |]
+     , simpleField "ignore_consistency" [t| Bool   |]
+     , optionalField $ simpleField "target_node" [t| String |]
+     ])
+  , ("OpInstanceMigrate",
+     [ simpleField "instance_name"  [t| String |]
+     , simpleField "live"           [t| Bool   |]
+     , simpleField "cleanup"        [t| Bool   |]
+     , defaultField [| False |] $ simpleField "allow_failover" [t| Bool |]
+     , optionalField $ simpleField "target_node" [t| String |]
+     ])
+  ])
+
+-- | Returns the OP_ID for a given opcode value.
+$(genOpID ''OpCode "opID")
+
+-- | A list of all defined/supported opcode IDs.
+$(genAllOpIDs ''OpCode "allOpIDs")
 
 instance JSON OpCode where
-    readJSON = loadOpCode
-    showJSON = saveOpCode
+  readJSON = loadOpCode
+  showJSON = saveOpCode