Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / OpCodes.hs @ e9aaa3c6

History | View | Annotate | Download (5.3 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of the opcodes.
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2009, 2010, 2011 Google Inc.
10

    
11
This program is free software; you can redistribute it and/or modify
12
it under the terms of the GNU General Public License as published by
13
the Free Software Foundation; either version 2 of the License, or
14
(at your option) any later version.
15

    
16
This program is distributed in the hope that it will be useful, but
17
WITHOUT ANY WARRANTY; without even the implied warranty of
18
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19
General Public License for more details.
20

    
21
You should have received a copy of the GNU General Public License
22
along with this program; if not, write to the Free Software
23
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24
02110-1301, USA.
25

    
26
-}
27

    
28
module Ganeti.OpCodes
29
    ( OpCode(..)
30
    , ReplaceDisksMode(..)
31
    , opID
32
    ) where
33

    
34
import Control.Monad
35
import Text.JSON (readJSON, showJSON, makeObj, JSON)
36
import qualified Text.JSON as J
37
import Text.JSON.Types
38

    
39
import qualified Ganeti.Constants as C
40
import qualified Ganeti.THH as THH
41

    
42
import Ganeti.HTools.Utils
43

    
44
-- | Replace disks type.
45
$(THH.declareSADT "ReplaceDisksMode"
46
     [ ("ReplaceOnPrimary",    'C.replaceDiskPri)
47
     , ("ReplaceOnSecondary",  'C.replaceDiskSec)
48
     , ("ReplaceNewSecondary", 'C.replaceDiskChg)
49
     , ("ReplaceAuto",         'C.replaceDiskAuto)
50
     ])
51
$(THH.makeJSONInstance ''ReplaceDisksMode)
52

    
53
-- | OpCode representation.
54
--
55
-- We only implement a subset of Ganeti opcodes, but only what we
56
-- actually use in the htools codebase.
57
data OpCode = OpTestDelay Double Bool [String]
58
            | OpInstanceReplaceDisks String (Maybe String) ReplaceDisksMode
59
              [Int] (Maybe String)
60
            | OpInstanceFailover String Bool (Maybe String)
61
            | OpInstanceMigrate String Bool Bool Bool (Maybe String)
62
            deriving (Show, Read, Eq)
63

    
64

    
65
-- | Computes the OP_ID for an OpCode.
66
opID :: OpCode -> String
67
opID (OpTestDelay _ _ _) = "OP_TEST_DELAY"
68
opID (OpInstanceReplaceDisks _ _ _ _ _) = "OP_INSTANCE_REPLACE_DISKS"
69
opID (OpInstanceFailover {}) = "OP_INSTANCE_FAILOVER"
70
opID (OpInstanceMigrate  {}) = "OP_INSTANCE_MIGRATE"
71

    
72
-- | Loads an OpCode from the JSON serialised form.
73
loadOpCode :: JSValue -> J.Result OpCode
74
loadOpCode v = do
75
  o <- liftM J.fromJSObject (readJSON v)
76
  let extract x = fromObj o x
77
  op_id <- extract "OP_ID"
78
  case op_id of
79
    "OP_TEST_DELAY" -> do
80
                 on_nodes  <- extract "on_nodes"
81
                 on_master <- extract "on_master"
82
                 duration  <- extract "duration"
83
                 return $ OpTestDelay duration on_master on_nodes
84
    "OP_INSTANCE_REPLACE_DISKS" -> do
85
                 inst   <- extract "instance_name"
86
                 node   <- maybeFromObj o "remote_node"
87
                 mode   <- extract "mode"
88
                 disks  <- extract "disks"
89
                 ialloc <- maybeFromObj o "iallocator"
90
                 return $ OpInstanceReplaceDisks inst node mode disks ialloc
91
    "OP_INSTANCE_FAILOVER" -> do
92
                 inst    <- extract "instance_name"
93
                 consist <- extract "ignore_consistency"
94
                 tnode   <- maybeFromObj o "target_node"
95
                 return $ OpInstanceFailover inst consist tnode
96
    "OP_INSTANCE_MIGRATE" -> do
97
                 inst    <- extract "instance_name"
98
                 live    <- extract "live"
99
                 cleanup <- extract "cleanup"
100
                 allow_failover <- fromObjWithDefault o "allow_failover" False
101
                 tnode   <- maybeFromObj o "target_node"
102
                 return $ OpInstanceMigrate inst live cleanup
103
                        allow_failover tnode
104
    _ -> J.Error $ "Unknown opcode " ++ op_id
105

    
106
-- | Serialises an opcode to JSON.
107
saveOpCode :: OpCode -> JSValue
108
saveOpCode op@(OpTestDelay duration on_master on_nodes) =
109
    let ol = [ ("OP_ID", showJSON $ opID op)
110
             , ("duration", showJSON duration)
111
             , ("on_master", showJSON on_master)
112
             , ("on_nodes", showJSON on_nodes) ]
113
    in makeObj ol
114

    
115
saveOpCode op@(OpInstanceReplaceDisks inst node mode disks iallocator) =
116
    let ol = [ ("OP_ID", showJSON $ opID op)
117
             , ("instance_name", showJSON inst)
118
             , ("mode", showJSON mode)
119
             , ("disks", showJSON disks)]
120
        ol2 = case node of
121
                Just n -> ("remote_node", showJSON n):ol
122
                Nothing -> ol
123
        ol3 = case iallocator of
124
                Just i -> ("iallocator", showJSON i):ol2
125
                Nothing -> ol2
126
    in makeObj ol3
127

    
128
saveOpCode op@(OpInstanceFailover inst consist tnode) =
129
    let ol = [ ("OP_ID", showJSON $ opID op)
130
             , ("instance_name", showJSON inst)
131
             , ("ignore_consistency", showJSON consist) ]
132
        ol' = case tnode of
133
                Nothing -> ol
134
                Just node -> ("target_node", showJSON node):ol
135
    in makeObj ol'
136

    
137
saveOpCode op@(OpInstanceMigrate inst live cleanup allow_failover tnode) =
138
    let ol = [ ("OP_ID", showJSON $ opID op)
139
             , ("instance_name", showJSON inst)
140
             , ("live", showJSON live)
141
             , ("cleanup", showJSON cleanup)
142
             , ("allow_failover", showJSON allow_failover) ]
143
        ol' = case tnode of
144
                Nothing -> ol
145
                Just node -> ("target_node", showJSON node):ol
146
    in makeObj ol'
147

    
148
instance JSON OpCode where
149
    readJSON = loadOpCode
150
    showJSON = saveOpCode