root / src / Ganeti / Confd / Types.hs @ 8e4e0268
History | View | Annotate | Download (6.1 kB)
1 |
{-# LANGUAGE TemplateHaskell #-} |
---|---|
2 |
|
3 |
{-| Implementation of the Ganeti confd types. |
4 |
|
5 |
-} |
6 |
|
7 |
{- |
8 |
|
9 |
Copyright (C) 2011, 2012 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.Confd.Types |
29 |
( C.confdProtocolVersion |
30 |
, C.confdMaxClockSkew |
31 |
, C.confdConfigReloadTimeout |
32 |
, C.confdConfigReloadRatelimit |
33 |
, C.confdMagicFourcc |
34 |
, C.confdDefaultReqCoverage |
35 |
, C.confdClientExpireTimeout |
36 |
, C.maxUdpDataSize |
37 |
, ConfdClient(..) |
38 |
, ConfdRequestType(..) |
39 |
, ConfdReqQ(..) |
40 |
, ConfdReqField(..) |
41 |
, ConfdReplyStatus(..) |
42 |
, ConfdNodeRole(..) |
43 |
, ConfdErrorType(..) |
44 |
, ConfdRequest(..) |
45 |
, newConfdRequest |
46 |
, ConfdReply(..) |
47 |
, ConfdQuery(..) |
48 |
, SignedMessage(..) |
49 |
) where |
50 |
|
51 |
import Text.JSON |
52 |
import qualified Network.Socket as S |
53 |
|
54 |
import qualified Ganeti.Constants as C |
55 |
import qualified Ganeti.ConstantUtils as ConstantUtils |
56 |
import Ganeti.Hash |
57 |
import Ganeti.THH |
58 |
import Ganeti.Utils (newUUID) |
59 |
|
60 |
{- |
61 |
Note that we re-export as is from Constants the following simple items: |
62 |
- confdProtocolVersion |
63 |
- confdMaxClockSkew |
64 |
- confdConfigReloadTimeout |
65 |
- confdConfigReloadRatelimit |
66 |
- confdMagicFourcc |
67 |
- confdDefaultReqCoverage |
68 |
- confdClientExpireTimeout |
69 |
- maxUdpDataSize |
70 |
|
71 |
-} |
72 |
|
73 |
$(declareIADT "ConfdRequestType" |
74 |
[ ("ReqPing", 'C.confdReqPing ) |
75 |
, ("ReqNodeRoleByName", 'C.confdReqNodeRoleByname ) |
76 |
, ("ReqNodePipList", 'C.confdReqNodePipList ) |
77 |
, ("ReqNodePipByInstPip", 'C.confdReqNodePipByInstanceIp ) |
78 |
, ("ReqClusterMaster", 'C.confdReqClusterMaster ) |
79 |
, ("ReqMcPipList", 'C.confdReqMcPipList ) |
80 |
, ("ReqInstIpsList", 'C.confdReqInstancesIpsList ) |
81 |
, ("ReqNodeDrbd", 'C.confdReqNodeDrbd ) |
82 |
, ("ReqNodeInstances", 'C.confdReqNodeInstances) |
83 |
]) |
84 |
$(makeJSONInstance ''ConfdRequestType) |
85 |
|
86 |
$(declareSADT "ConfdReqField" |
87 |
[ ("ReqFieldName", 'C.confdReqfieldName ) |
88 |
, ("ReqFieldIp", 'C.confdReqfieldIp ) |
89 |
, ("ReqFieldMNodePip", 'C.confdReqfieldMnodePip ) |
90 |
]) |
91 |
$(makeJSONInstance ''ConfdReqField) |
92 |
|
93 |
-- Confd request query fields. These are used to narrow down queries. |
94 |
-- These must be strings rather than integers, because json-encoding |
95 |
-- converts them to strings anyway, as they're used as dict-keys. |
96 |
|
97 |
$(buildObject "ConfdReqQ" "confdReqQ" |
98 |
[ renameField "Ip" . |
99 |
optionalField $ |
100 |
simpleField ConstantUtils.confdReqqIp [t| String |] |
101 |
, renameField "IpList" . |
102 |
defaultField [| [] |] $ |
103 |
simpleField ConstantUtils.confdReqqIplist [t| [String] |] |
104 |
, renameField "Link" . |
105 |
optionalField $ |
106 |
simpleField ConstantUtils.confdReqqLink [t| String |] |
107 |
, renameField "Fields" . |
108 |
defaultField [| [] |] $ |
109 |
simpleField ConstantUtils.confdReqqFields [t| [ConfdReqField] |] |
110 |
]) |
111 |
|
112 |
-- | Confd query type. This is complex enough that we can't |
113 |
-- automatically derive it via THH. |
114 |
data ConfdQuery = EmptyQuery |
115 |
| PlainQuery String |
116 |
| DictQuery ConfdReqQ |
117 |
deriving (Show, Eq) |
118 |
|
119 |
instance JSON ConfdQuery where |
120 |
readJSON o = case o of |
121 |
JSNull -> return EmptyQuery |
122 |
JSString s -> return . PlainQuery . fromJSString $ s |
123 |
JSObject _ -> fmap DictQuery (readJSON o::Result ConfdReqQ) |
124 |
_ -> fail $ "Cannot deserialise into ConfdQuery\ |
125 |
\ the value '" ++ show o ++ "'" |
126 |
showJSON cq = case cq of |
127 |
EmptyQuery -> JSNull |
128 |
PlainQuery s -> showJSON s |
129 |
DictQuery drq -> showJSON drq |
130 |
|
131 |
$(declareIADT "ConfdReplyStatus" |
132 |
[ ( "ReplyStatusOk", 'C.confdReplStatusOk ) |
133 |
, ( "ReplyStatusError", 'C.confdReplStatusError ) |
134 |
, ( "ReplyStatusNotImpl", 'C.confdReplStatusNotimplemented ) |
135 |
]) |
136 |
$(makeJSONInstance ''ConfdReplyStatus) |
137 |
|
138 |
$(declareIADT "ConfdNodeRole" |
139 |
[ ( "NodeRoleMaster", 'C.confdNodeRoleMaster ) |
140 |
, ( "NodeRoleCandidate", 'C.confdNodeRoleCandidate ) |
141 |
, ( "NodeRoleOffline", 'C.confdNodeRoleOffline ) |
142 |
, ( "NodeRoleDrained", 'C.confdNodeRoleDrained ) |
143 |
, ( "NodeRoleRegular", 'C.confdNodeRoleRegular ) |
144 |
]) |
145 |
$(makeJSONInstance ''ConfdNodeRole) |
146 |
|
147 |
|
148 |
-- Note that the next item is not a frozenset in Python, but we make |
149 |
-- it a separate type for safety |
150 |
|
151 |
$(declareIADT "ConfdErrorType" |
152 |
[ ( "ConfdErrorUnknownEntry", 'C.confdErrorUnknownEntry ) |
153 |
, ( "ConfdErrorInternal", 'C.confdErrorInternal ) |
154 |
, ( "ConfdErrorArgument", 'C.confdErrorArgument ) |
155 |
]) |
156 |
$(makeJSONInstance ''ConfdErrorType) |
157 |
|
158 |
$(buildObject "ConfdRequest" "confdRq" |
159 |
[ simpleField "protocol" [t| Int |] |
160 |
, simpleField "type" [t| ConfdRequestType |] |
161 |
, defaultField [| EmptyQuery |] $ simpleField "query" [t| ConfdQuery |] |
162 |
, simpleField "rsalt" [t| String |] |
163 |
]) |
164 |
|
165 |
-- | Client side helper function for creating requests. It automatically fills |
166 |
-- in some default values. |
167 |
newConfdRequest :: ConfdRequestType -> ConfdQuery -> IO ConfdRequest |
168 |
newConfdRequest reqType query = do |
169 |
rsalt <- newUUID |
170 |
return $ ConfdRequest C.confdProtocolVersion reqType query rsalt |
171 |
|
172 |
$(buildObject "ConfdReply" "confdReply" |
173 |
[ simpleField "protocol" [t| Int |] |
174 |
, simpleField "status" [t| ConfdReplyStatus |] |
175 |
, simpleField "answer" [t| JSValue |] |
176 |
, simpleField "serial" [t| Int |] |
177 |
]) |
178 |
|
179 |
$(buildObject "SignedMessage" "signedMsg" |
180 |
[ simpleField "hmac" [t| String |] |
181 |
, simpleField "msg" [t| String |] |
182 |
, simpleField "salt" [t| String |] |
183 |
]) |
184 |
|
185 |
-- | Data type containing information used by the Confd client. |
186 |
data ConfdClient = ConfdClient |
187 |
{ hmacKey :: HashKey -- ^ The hmac used for authentication |
188 |
, peers :: [String] -- ^ The list of nodes to query |
189 |
, serverPort :: S.PortNumber -- ^ The port where confd server is listening |
190 |
} |