Fix parsing of absolute job dependencies
[ganeti-local] / htools / Ganeti / Objects.hs
index d20edb4..18ca6df 100644 (file)
@@ -29,13 +29,17 @@ Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
 -}
 
 module Ganeti.Objects
-  ( HvParams
+  ( VType(..)
+  , vTypeFromRaw
+  , HvParams
   , OsParams
-  , NICMode(..)
   , PartialNicParams(..)
   , FilledNicParams(..)
   , fillNicParams
+  , allNicParamFields
   , PartialNic(..)
+  , FileDriver(..)
+  , BlockDriver(..)
   , DiskMode(..)
   , DiskType(..)
   , DiskLogicalId(..)
@@ -44,7 +48,7 @@ module Ganeti.Objects
   , PartialBeParams(..)
   , FilledBeParams(..)
   , fillBeParams
-  , Hypervisor(..)
+  , allBeParamFields
   , AdminState(..)
   , adminStateFromRaw
   , Instance(..)
@@ -52,11 +56,16 @@ module Ganeti.Objects
   , PartialNDParams(..)
   , FilledNDParams(..)
   , fillNDParams
+  , allNDParamFields
   , Node(..)
+  , NodeRole(..)
+  , nodeRoleToRaw
+  , roleDescription
   , AllocPolicy(..)
   , FilledISpecParams(..)
   , PartialISpecParams(..)
   , fillISpecParams
+  , allISpecParamFields
   , FilledIPolicy(..)
   , PartialIPolicy(..)
   , fillIPolicy
@@ -72,17 +81,25 @@ module Ganeti.Objects
   , ClusterNicParams
   , Cluster(..)
   , ConfigData(..)
+  , TimeStampObject(..)
+  , UuidObject(..)
+  , SerialNoObject(..)
+  , TagsObject(..)
+  , DictObject(..) -- re-exported from THH
+  , TagSet -- re-exported from THH
+  , Network(..)
   ) where
 
 import Data.List (foldl')
 import Data.Maybe
 import qualified Data.Map as Map
-import Text.JSON (makeObj, showJSON, readJSON, JSON, JSValue(..))
+import qualified Data.Set as Set
+import Text.JSON (showJSON, readJSON, JSON, JSValue(..))
 import qualified Text.JSON as J
 
 import qualified Ganeti.Constants as C
-import Ganeti.HTools.JSON
-
+import Ganeti.JSON
+import Ganeti.Types
 import Ganeti.THH
 
 -- * Generic definitions
@@ -94,6 +111,16 @@ fillDict defaults custom skip_keys =
   let updated = Map.union custom defaults
   in foldl' (flip Map.delete) updated skip_keys
 
+-- | The VTYPES, a mini-type system in Python.
+$(declareSADT "VType"
+  [ ("VTypeString",      'C.vtypeString)
+  , ("VTypeMaybeString", 'C.vtypeMaybeString)
+  , ("VTypeBool",        'C.vtypeBool)
+  , ("VTypeSize",        'C.vtypeSize)
+  , ("VTypeInt",         'C.vtypeInt)
+  ])
+$(makeJSONInstance ''VType)
+
 -- | The hypervisor parameter type. This is currently a simple map,
 -- without type checking on key/value pairs.
 type HvParams = Container JSValue
@@ -103,13 +130,43 @@ type HvParams = Container JSValue
 -- the values are always strings.
 type OsParams = Container String
 
--- * NIC definitions
+-- | Class of objects that have timestamps.
+class TimeStampObject a where
+  cTimeOf :: a -> Double
+  mTimeOf :: a -> Double
+
+-- | Class of objects that have an UUID.
+class UuidObject a where
+  uuidOf :: a -> String
+
+-- | Class of object that have a serial number.
+class SerialNoObject a where
+  serialOf :: a -> Int
+
+-- | Class of objects that have tags.
+class TagsObject a where
+  tagsOf :: a -> Set.Set String
+
+-- * Node role object
 
-$(declareSADT "NICMode"
-  [ ("NMBridged", 'C.nicModeBridged)
-  , ("NMRouted",  'C.nicModeRouted)
+$(declareSADT "NodeRole"
+  [ ("NROffline",   'C.nrOffline)
+  , ("NRDrained",   'C.nrDrained)
+  , ("NRRegular",   'C.nrRegular)
+  , ("NRCandidate", 'C.nrMcandidate)
+  , ("NRMaster",    'C.nrMaster)
   ])
-$(makeJSONInstance ''NICMode)
+$(makeJSONInstance ''NodeRole)
+
+-- | The description of the node role.
+roleDescription :: NodeRole -> String
+roleDescription NROffline   = "offline"
+roleDescription NRDrained   = "drained"
+roleDescription NRRegular   = "regular"
+roleDescription NRCandidate = "master candidate"
+roleDescription NRMaster    = "master"
+
+-- * NIC definitions
 
 $(buildParam "Nic" "nicp"
   [ simpleField "mode" [t| NICMode |]
@@ -139,13 +196,6 @@ $(declareSADT "DiskType"
   ])
 $(makeJSONInstance ''DiskType)
 
--- | The file driver type.
-$(declareSADT "FileDriver"
-  [ ("FileLoop",   'C.fdLoop)
-  , ("FileBlktap", 'C.fdBlktap)
-  ])
-$(makeJSONInstance ''FileDriver)
-
 -- | The persistent block driver type. Currently only one type is allowed.
 $(declareSADT "BlockDriver"
   [ ("BlockDrvManual", 'C.blockdevDriverManual)
@@ -167,7 +217,7 @@ data DiskLogicalId
   | LIDFile FileDriver String -- ^ Driver, path
   | LIDBlockDev BlockDriver String -- ^ Driver, path (must be under /dev)
   | LIDRados String String -- ^ Unused, path
-    deriving (Read, Show, Eq)
+    deriving (Show, Eq)
 
 -- | Mapping from a logical id to a disk type.
 lidDiskType :: DiskLogicalId -> DiskType
@@ -212,35 +262,35 @@ decodeDLId obj lid = do
           mB' <- readJSON mB
           k'  <- readJSON k
           return $ LIDDrbd8 nA' nB' p' mA' mB' k'
-        _ -> fail $ "Can't read logical_id for DRBD8 type"
+        _ -> fail "Can't read logical_id for DRBD8 type"
     LD_LV ->
       case lid of
         JSArray [vg, lv] -> do
           vg' <- readJSON vg
           lv' <- readJSON lv
           return $ LIDPlain vg' lv'
-        _ -> fail $ "Can't read logical_id for plain type"
+        _ -> fail "Can't read logical_id for plain type"
     LD_FILE ->
       case lid of
         JSArray [driver, path] -> do
           driver' <- readJSON driver
           path'   <- readJSON path
           return $ LIDFile driver' path'
-        _ -> fail $ "Can't read logical_id for file type"
+        _ -> fail "Can't read logical_id for file type"
     LD_BLOCKDEV ->
       case lid of
         JSArray [driver, path] -> do
           driver' <- readJSON driver
           path'   <- readJSON path
           return $ LIDBlockDev driver' path'
-        _ -> fail $ "Can't read logical_id for blockdev type"
+        _ -> fail "Can't read logical_id for blockdev type"
     LD_RADOS ->
       case lid of
         JSArray [driver, path] -> do
           driver' <- readJSON driver
           path'   <- readJSON path
           return $ LIDRados driver' path'
-        _ -> fail $ "Can't read logical_id for rdb type"
+        _ -> fail "Can't read logical_id for rdb type"
 
 -- | Disk data structure.
 --
@@ -253,10 +303,10 @@ data Disk = Disk
   , diskIvName     :: String
   , diskSize       :: Int
   , diskMode       :: DiskMode
-  } deriving (Read, Show, Eq)
+  } deriving (Show, Eq)
 
 $(buildObjectSerialisation "Disk"
-  [ customField 'decodeDLId 'encodeFullDLId $
+  [ customField 'decodeDLId 'encodeFullDLId ["dev_type"] $
       simpleField "logical_id"    [t| DiskLogicalId   |]
 --  , simpleField "physical_id" [t| String   |]
   , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
@@ -265,33 +315,8 @@ $(buildObjectSerialisation "Disk"
   , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
   ])
 
--- * Hypervisor definitions
-
--- | This may be due to change when we add hypervisor parameters.
-$(declareSADT "Hypervisor"
-  [ ( "Kvm",    'C.htKvm )
-  , ( "XenPvm", 'C.htXenPvm )
-  , ( "Chroot", 'C.htChroot )
-  , ( "XenHvm", 'C.htXenHvm )
-  , ( "Lxc",    'C.htLxc )
-  , ( "Fake",   'C.htFake )
-  ])
-$(makeJSONInstance ''Hypervisor)
-
 -- * Instance definitions
 
--- | Instance disk template type. **Copied from HTools/Types.hs**
-$(declareSADT "DiskTemplate"
-  [ ("DTDiskless",   'C.dtDiskless)
-  , ("DTFile",       'C.dtFile)
-  , ("DTSharedFile", 'C.dtSharedFile)
-  , ("DTPlain",      'C.dtPlain)
-  , ("DTBlock",      'C.dtBlock)
-  , ("DTDrbd8",      'C.dtDrbd8)
-  , ("DTRados",      'C.dtRbd)
-  ])
-$(makeJSONInstance ''DiskTemplate)
-
 $(declareSADT "AdminState"
   [ ("AdminOffline", 'C.adminstOffline)
   , ("AdminDown",    'C.adminstDown)
@@ -299,7 +324,7 @@ $(declareSADT "AdminState"
   ])
 $(makeJSONInstance ''AdminState)
 
-$(buildParam "Be" "bep" $
+$(buildParam "Be" "bep"
   [ simpleField "minmem"       [t| Int  |]
   , simpleField "maxmem"       [t| Int  |]
   , simpleField "vcpus"        [t| Int  |]
@@ -325,19 +350,33 @@ $(buildObject "Instance" "inst" $
   ++ serialFields
   ++ tagsFields)
 
+instance TimeStampObject Instance where
+  cTimeOf = instCtime
+  mTimeOf = instMtime
+
+instance UuidObject Instance where
+  uuidOf = instUuid
+
+instance SerialNoObject Instance where
+  serialOf = instSerial
+
+instance TagsObject Instance where
+  tagsOf = instTags
+
 -- * IPolicy definitions
 
-$(buildParam "ISpec" "ispec" $
+$(buildParam "ISpec" "ispec"
   [ simpleField C.ispecMemSize     [t| Int |]
   , simpleField C.ispecDiskSize    [t| Int |]
   , simpleField C.ispecDiskCount   [t| Int |]
   , simpleField C.ispecCpuCount    [t| Int |]
+  , simpleField C.ispecNicCount    [t| Int |]
   , simpleField C.ispecSpindleUse  [t| Int |]
   ])
 
 -- | Custom partial ipolicy. This is not built via buildParam since it
 -- has a special 2-level inheritance mode.
-$(buildObject "PartialIPolicy" "ipolicy" $
+$(buildObject "PartialIPolicy" "ipolicy"
   [ renameField "MinSpecP" $ simpleField "min" [t| PartialISpecParams |]
   , renameField "MaxSpecP" $ simpleField "max" [t| PartialISpecParams |]
   , renameField "StdSpecP" $ simpleField "std" [t| PartialISpecParams |]
@@ -351,7 +390,7 @@ $(buildObject "PartialIPolicy" "ipolicy" $
 
 -- | Custom filled ipolicy. This is not built via buildParam since it
 -- has a special 2-level inheritance mode.
-$(buildObject "FilledIPolicy" "ipolicy" $
+$(buildObject "FilledIPolicy" "ipolicy"
   [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
   , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
   , renameField "StdSpec" $ simpleField "std" [t| FilledISpecParams |]
@@ -384,7 +423,7 @@ fillIPolicy (FilledIPolicy { ipolicyMinSpec       = fmin
                 }
 -- * Node definitions
 
-$(buildParam "ND" "ndp" $
+$(buildParam "ND" "ndp"
   [ simpleField "oob_program"   [t| String |]
   , simpleField "spindle_count" [t| Int    |]
   ])
@@ -407,22 +446,20 @@ $(buildObject "Node" "node" $
   ++ serialFields
   ++ tagsFields)
 
--- * NodeGroup definitions
+instance TimeStampObject Node where
+  cTimeOf = nodeCtime
+  mTimeOf = nodeMtime
 
--- | The Group allocation policy type.
---
--- Note that the order of constructors is important as the automatic
--- Ord instance will order them in the order they are defined, so when
--- changing this data type be careful about the interaction with the
--- desired sorting order.
---
--- FIXME: COPIED from Types.hs; we need to eliminate this duplication later
-$(declareSADT "AllocPolicy"
-  [ ("AllocPreferred",   'C.allocPolicyPreferred)
-  , ("AllocLastResort",  'C.allocPolicyLastResort)
-  , ("AllocUnallocable", 'C.allocPolicyUnallocable)
-  ])
-$(makeJSONInstance ''AllocPolicy)
+instance UuidObject Node where
+  uuidOf = nodeUuid
+
+instance SerialNoObject Node where
+  serialOf = nodeSerial
+
+instance TagsObject Node where
+  tagsOf = nodeTags
+
+-- * NodeGroup definitions
 
 -- | The disk parameters type.
 type DiskParams = Container (Container JSValue)
@@ -440,6 +477,19 @@ $(buildObject "NodeGroup" "group" $
   ++ serialFields
   ++ tagsFields)
 
+instance TimeStampObject NodeGroup where
+  cTimeOf = groupCtime
+  mTimeOf = groupMtime
+
+instance UuidObject NodeGroup where
+  uuidOf = groupUuid
+
+instance SerialNoObject NodeGroup where
+  serialOf = groupSerial
+
+instance TagsObject NodeGroup where
+  tagsOf = groupTags
+
 -- | IP family type
 $(declareIADT "IpFamily"
   [ ("IpFamilyV4", 'C.ip4Family)
@@ -489,7 +539,7 @@ $(buildObject "Cluster" "cluster" $
   , simpleField "cluster_name"            [t| String           |]
   , simpleField "file_storage_dir"        [t| String           |]
   , simpleField "shared_file_storage_dir" [t| String           |]
-  , simpleField "enabled_hypervisors"     [t| [String]         |]
+  , simpleField "enabled_hypervisors"     [t| [Hypervisor]     |]
   , simpleField "hvparams"                [t| ClusterHvParams  |]
   , simpleField "os_hvp"                  [t| OsHvParams       |]
   , simpleField "beparams"                [t| ClusterBeParams  |]
@@ -509,11 +559,24 @@ $(buildObject "Cluster" "cluster" $
   , simpleField "prealloc_wipe_disks"     [t| Bool             |]
   , simpleField "ipolicy"                 [t| FilledIPolicy    |]
  ]
- ++ serialFields
  ++ timeStampFields
  ++ uuidFields
+ ++ serialFields
  ++ tagsFields)
 
+instance TimeStampObject Cluster where
+  cTimeOf = clusterCtime
+  mTimeOf = clusterMtime
+
+instance UuidObject Cluster where
+  uuidOf = clusterUuid
+
+instance SerialNoObject Cluster where
+  serialOf = clusterSerial
+
+instance TagsObject Cluster where
+  tagsOf = clusterTags
+
 -- * ConfigData definitions
 
 $(buildObject "ConfigData" "config" $
@@ -525,3 +588,42 @@ $(buildObject "ConfigData" "config" $
   , simpleField "instances"  [t| Container Instance  |]
   ]
   ++ serialFields)
+
+instance SerialNoObject ConfigData where
+  serialOf = configSerial
+
+-- * Network definitions
+
+-- FIXME: Not all types might be correct here, since they
+-- haven't been exhaustively deduced from the python code yet.
+$(buildObject "Network" "network" $
+  [ simpleField "name"             [t| NonEmptyString |]
+  , optionalField $
+    simpleField "network_type"     [t| NetworkType |]
+  , optionalField $
+    simpleField "mac_prefix"       [t| String |]
+  , optionalField $
+    simpleField "family"           [t| Int |]
+  , simpleField "network"          [t| NonEmptyString |]
+  , optionalField $
+    simpleField "network6"         [t| String |]
+  , optionalField $
+    simpleField "gateway"          [t| String |]
+  , optionalField $
+    simpleField "gateway6"         [t| String |]
+  , optionalField $
+    simpleField "size"             [t| J.JSValue |]
+  , optionalField $
+    simpleField "reservations"     [t| String |]
+  , optionalField $
+    simpleField "ext_reservations" [t| String |]
+  ]
+  ++ serialFields
+  ++ tagsFields)
+
+instance SerialNoObject Network where
+  serialOf = networkSerial
+
+instance TagsObject Network where
+  tagsOf = networkTags
+