Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Confd / Types.hs @ d24fc4b6

History | View | Annotate | Download (6.1 kB)

1 417cc253 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 417cc253 Iustin Pop
3 417cc253 Iustin Pop
{-| Implementation of the Ganeti confd types.
4 417cc253 Iustin Pop
5 417cc253 Iustin Pop
-}
6 417cc253 Iustin Pop
7 417cc253 Iustin Pop
{-
8 417cc253 Iustin Pop
9 417cc253 Iustin Pop
Copyright (C) 2011, 2012 Google Inc.
10 417cc253 Iustin Pop
11 417cc253 Iustin Pop
This program is free software; you can redistribute it and/or modify
12 417cc253 Iustin Pop
it under the terms of the GNU General Public License as published by
13 417cc253 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 417cc253 Iustin Pop
(at your option) any later version.
15 417cc253 Iustin Pop
16 417cc253 Iustin Pop
This program is distributed in the hope that it will be useful, but
17 417cc253 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 417cc253 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 417cc253 Iustin Pop
General Public License for more details.
20 417cc253 Iustin Pop
21 417cc253 Iustin Pop
You should have received a copy of the GNU General Public License
22 417cc253 Iustin Pop
along with this program; if not, write to the Free Software
23 417cc253 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 417cc253 Iustin Pop
02110-1301, USA.
25 417cc253 Iustin Pop
26 417cc253 Iustin Pop
-}
27 417cc253 Iustin Pop
28 cdc2392b Iustin Pop
module Ganeti.Confd.Types
29 417cc253 Iustin Pop
  ( C.confdProtocolVersion
30 417cc253 Iustin Pop
  , C.confdMaxClockSkew
31 417cc253 Iustin Pop
  , C.confdConfigReloadTimeout
32 417cc253 Iustin Pop
  , C.confdConfigReloadRatelimit
33 417cc253 Iustin Pop
  , C.confdMagicFourcc
34 417cc253 Iustin Pop
  , C.confdDefaultReqCoverage
35 417cc253 Iustin Pop
  , C.confdClientExpireTimeout
36 417cc253 Iustin Pop
  , C.maxUdpDataSize
37 04063ba7 Michele Tartara
  , ConfdClient(..)
38 417cc253 Iustin Pop
  , ConfdRequestType(..)
39 417cc253 Iustin Pop
  , ConfdReqQ(..)
40 417cc253 Iustin Pop
  , ConfdReqField(..)
41 417cc253 Iustin Pop
  , ConfdReplyStatus(..)
42 417cc253 Iustin Pop
  , ConfdNodeRole(..)
43 417cc253 Iustin Pop
  , ConfdErrorType(..)
44 417cc253 Iustin Pop
  , ConfdRequest(..)
45 04063ba7 Michele Tartara
  , newConfdRequest
46 417cc253 Iustin Pop
  , ConfdReply(..)
47 417cc253 Iustin Pop
  , ConfdQuery(..)
48 417cc253 Iustin Pop
  , SignedMessage(..)
49 417cc253 Iustin Pop
  ) where
50 417cc253 Iustin Pop
51 417cc253 Iustin Pop
import Text.JSON
52 04063ba7 Michele Tartara
import qualified Network.Socket as S
53 417cc253 Iustin Pop
54 417cc253 Iustin Pop
import qualified Ganeti.Constants as C
55 8e4e0268 Jose A. Lopes
import qualified Ganeti.ConstantUtils as ConstantUtils
56 04063ba7 Michele Tartara
import Ganeti.Hash
57 417cc253 Iustin Pop
import Ganeti.THH
58 04063ba7 Michele Tartara
import Ganeti.Utils (newUUID)
59 417cc253 Iustin Pop
60 417cc253 Iustin Pop
{-
61 417cc253 Iustin Pop
   Note that we re-export as is from Constants the following simple items:
62 417cc253 Iustin Pop
   - confdProtocolVersion
63 417cc253 Iustin Pop
   - confdMaxClockSkew
64 417cc253 Iustin Pop
   - confdConfigReloadTimeout
65 417cc253 Iustin Pop
   - confdConfigReloadRatelimit
66 417cc253 Iustin Pop
   - confdMagicFourcc
67 417cc253 Iustin Pop
   - confdDefaultReqCoverage
68 417cc253 Iustin Pop
   - confdClientExpireTimeout
69 417cc253 Iustin Pop
   - maxUdpDataSize
70 417cc253 Iustin Pop
71 417cc253 Iustin Pop
-}
72 417cc253 Iustin Pop
73 417cc253 Iustin Pop
$(declareIADT "ConfdRequestType"
74 417cc253 Iustin Pop
  [ ("ReqPing",             'C.confdReqPing )
75 417cc253 Iustin Pop
  , ("ReqNodeRoleByName",   'C.confdReqNodeRoleByname )
76 417cc253 Iustin Pop
  , ("ReqNodePipList",      'C.confdReqNodePipList )
77 417cc253 Iustin Pop
  , ("ReqNodePipByInstPip", 'C.confdReqNodePipByInstanceIp )
78 417cc253 Iustin Pop
  , ("ReqClusterMaster",    'C.confdReqClusterMaster )
79 417cc253 Iustin Pop
  , ("ReqMcPipList",        'C.confdReqMcPipList )
80 417cc253 Iustin Pop
  , ("ReqInstIpsList",      'C.confdReqInstancesIpsList )
81 d81ec8b7 Iustin Pop
  , ("ReqNodeDrbd",         'C.confdReqNodeDrbd )
82 332a83ca Michele Tartara
  , ("ReqNodeInstances",    'C.confdReqNodeInstances)
83 417cc253 Iustin Pop
  ])
84 417cc253 Iustin Pop
$(makeJSONInstance ''ConfdRequestType)
85 417cc253 Iustin Pop
86 417cc253 Iustin Pop
$(declareSADT "ConfdReqField"
87 417cc253 Iustin Pop
  [ ("ReqFieldName",     'C.confdReqfieldName )
88 417cc253 Iustin Pop
  , ("ReqFieldIp",       'C.confdReqfieldIp )
89 417cc253 Iustin Pop
  , ("ReqFieldMNodePip", 'C.confdReqfieldMnodePip )
90 417cc253 Iustin Pop
  ])
91 417cc253 Iustin Pop
$(makeJSONInstance ''ConfdReqField)
92 417cc253 Iustin Pop
93 417cc253 Iustin Pop
-- Confd request query fields. These are used to narrow down queries.
94 417cc253 Iustin Pop
-- These must be strings rather than integers, because json-encoding
95 417cc253 Iustin Pop
-- converts them to strings anyway, as they're used as dict-keys.
96 417cc253 Iustin Pop
97 417cc253 Iustin Pop
$(buildObject "ConfdReqQ" "confdReqQ"
98 2cdaf225 Iustin Pop
  [ renameField "Ip" .
99 8e4e0268 Jose A. Lopes
    optionalField $
100 8e4e0268 Jose A. Lopes
    simpleField ConstantUtils.confdReqqIp [t| String |]
101 2cdaf225 Iustin Pop
  , renameField "IpList" .
102 8e4e0268 Jose A. Lopes
    defaultField [| [] |] $
103 8e4e0268 Jose A. Lopes
    simpleField ConstantUtils.confdReqqIplist [t| [String] |]
104 8e4e0268 Jose A. Lopes
  , renameField "Link" .
105 8e4e0268 Jose A. Lopes
    optionalField $
106 8e4e0268 Jose A. Lopes
    simpleField ConstantUtils.confdReqqLink [t| String |]
107 8e4e0268 Jose A. Lopes
  , renameField "Fields" .
108 8e4e0268 Jose A. Lopes
    defaultField [| [] |] $
109 8e4e0268 Jose A. Lopes
    simpleField ConstantUtils.confdReqqFields [t| [ConfdReqField] |]
110 417cc253 Iustin Pop
  ])
111 417cc253 Iustin Pop
112 417cc253 Iustin Pop
-- | Confd query type. This is complex enough that we can't
113 417cc253 Iustin Pop
-- automatically derive it via THH.
114 417cc253 Iustin Pop
data ConfdQuery = EmptyQuery
115 417cc253 Iustin Pop
                | PlainQuery String
116 417cc253 Iustin Pop
                | DictQuery  ConfdReqQ
117 139c0683 Iustin Pop
                  deriving (Show, Eq)
118 417cc253 Iustin Pop
119 417cc253 Iustin Pop
instance JSON ConfdQuery where
120 417cc253 Iustin Pop
  readJSON o = case o of
121 417cc253 Iustin Pop
                 JSNull     -> return EmptyQuery
122 417cc253 Iustin Pop
                 JSString s -> return . PlainQuery . fromJSString $ s
123 417cc253 Iustin Pop
                 JSObject _ -> fmap DictQuery (readJSON o::Result ConfdReqQ)
124 417cc253 Iustin Pop
                 _ -> fail $ "Cannot deserialise into ConfdQuery\
125 417cc253 Iustin Pop
                             \ the value '" ++ show o ++ "'"
126 417cc253 Iustin Pop
  showJSON cq = case cq of
127 417cc253 Iustin Pop
                  EmptyQuery -> JSNull
128 417cc253 Iustin Pop
                  PlainQuery s -> showJSON s
129 417cc253 Iustin Pop
                  DictQuery drq -> showJSON drq
130 417cc253 Iustin Pop
131 417cc253 Iustin Pop
$(declareIADT "ConfdReplyStatus"
132 417cc253 Iustin Pop
  [ ( "ReplyStatusOk",      'C.confdReplStatusOk )
133 417cc253 Iustin Pop
  , ( "ReplyStatusError",   'C.confdReplStatusError )
134 417cc253 Iustin Pop
  , ( "ReplyStatusNotImpl", 'C.confdReplStatusNotimplemented )
135 417cc253 Iustin Pop
  ])
136 417cc253 Iustin Pop
$(makeJSONInstance ''ConfdReplyStatus)
137 417cc253 Iustin Pop
138 417cc253 Iustin Pop
$(declareIADT "ConfdNodeRole"
139 417cc253 Iustin Pop
  [ ( "NodeRoleMaster",    'C.confdNodeRoleMaster )
140 417cc253 Iustin Pop
  , ( "NodeRoleCandidate", 'C.confdNodeRoleCandidate )
141 417cc253 Iustin Pop
  , ( "NodeRoleOffline",   'C.confdNodeRoleOffline )
142 417cc253 Iustin Pop
  , ( "NodeRoleDrained",   'C.confdNodeRoleDrained )
143 417cc253 Iustin Pop
  , ( "NodeRoleRegular",   'C.confdNodeRoleRegular )
144 417cc253 Iustin Pop
  ])
145 417cc253 Iustin Pop
$(makeJSONInstance ''ConfdNodeRole)
146 417cc253 Iustin Pop
147 417cc253 Iustin Pop
148 417cc253 Iustin Pop
-- Note that the next item is not a frozenset in Python, but we make
149 417cc253 Iustin Pop
-- it a separate type for safety
150 417cc253 Iustin Pop
151 417cc253 Iustin Pop
$(declareIADT "ConfdErrorType"
152 417cc253 Iustin Pop
  [ ( "ConfdErrorUnknownEntry", 'C.confdErrorUnknownEntry )
153 417cc253 Iustin Pop
  , ( "ConfdErrorInternal",     'C.confdErrorInternal )
154 417cc253 Iustin Pop
  , ( "ConfdErrorArgument",     'C.confdErrorArgument )
155 417cc253 Iustin Pop
  ])
156 417cc253 Iustin Pop
$(makeJSONInstance ''ConfdErrorType)
157 417cc253 Iustin Pop
158 5b11f8db Iustin Pop
$(buildObject "ConfdRequest" "confdRq"
159 417cc253 Iustin Pop
  [ simpleField "protocol" [t| Int |]
160 417cc253 Iustin Pop
  , simpleField "type"     [t| ConfdRequestType |]
161 417cc253 Iustin Pop
  , defaultField [| EmptyQuery |] $ simpleField "query" [t| ConfdQuery |]
162 417cc253 Iustin Pop
  , simpleField "rsalt"    [t| String |]
163 417cc253 Iustin Pop
  ])
164 417cc253 Iustin Pop
165 04063ba7 Michele Tartara
-- | Client side helper function for creating requests. It automatically fills
166 04063ba7 Michele Tartara
-- in some default values.
167 04063ba7 Michele Tartara
newConfdRequest :: ConfdRequestType -> ConfdQuery -> IO ConfdRequest
168 04063ba7 Michele Tartara
newConfdRequest reqType query = do
169 04063ba7 Michele Tartara
  rsalt <- newUUID
170 04063ba7 Michele Tartara
  return $ ConfdRequest C.confdProtocolVersion reqType query rsalt
171 04063ba7 Michele Tartara
172 417cc253 Iustin Pop
$(buildObject "ConfdReply" "confdReply"
173 417cc253 Iustin Pop
  [ simpleField "protocol" [t| Int              |]
174 417cc253 Iustin Pop
  , simpleField "status"   [t| ConfdReplyStatus |]
175 417cc253 Iustin Pop
  , simpleField "answer"   [t| JSValue          |]
176 417cc253 Iustin Pop
  , simpleField "serial"   [t| Int              |]
177 417cc253 Iustin Pop
  ])
178 417cc253 Iustin Pop
179 417cc253 Iustin Pop
$(buildObject "SignedMessage" "signedMsg"
180 417cc253 Iustin Pop
  [ simpleField "hmac" [t| String |]
181 417cc253 Iustin Pop
  , simpleField "msg"  [t| String |]
182 417cc253 Iustin Pop
  , simpleField "salt" [t| String |]
183 417cc253 Iustin Pop
  ])
184 04063ba7 Michele Tartara
185 04063ba7 Michele Tartara
-- | Data type containing information used by the Confd client.
186 04063ba7 Michele Tartara
data ConfdClient = ConfdClient
187 04063ba7 Michele Tartara
  { hmacKey :: HashKey         -- ^ The hmac used for authentication
188 04063ba7 Michele Tartara
  , peers :: [String]          -- ^ The list of nodes to query
189 04063ba7 Michele Tartara
  , serverPort :: S.PortNumber -- ^ The port where confd server is listening
190 04063ba7 Michele Tartara
  }