Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Confd / Types.hs @ 11e90588

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