Re-enable standard hlint warnings
[ganeti-local] / htools / Ganeti / Config.hs
1 {-| Implementation of the Ganeti configuration database.
2
3 -}
4
5 {-
6
7 Copyright (C) 2011, 2012 Google Inc.
8
9 This program is free software; you can redistribute it and/or modify
10 it under the terms of the GNU General Public License as published by
11 the Free Software Foundation; either version 2 of the License, or
12 (at your option) any later version.
13
14 This program is distributed in the hope that it will be useful, but
15 WITHOUT ANY WARRANTY; without even the implied warranty of
16 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 General Public License for more details.
18
19 You should have received a copy of the GNU General Public License
20 along with this program; if not, write to the Free Software
21 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 02110-1301, USA.
23
24 -}
25
26 module Ganeti.Config
27     ( LinkIpMap
28     , loadConfig
29     , getNodeInstances
30     , getDefaultNicLink
31     , getInstancesIpByLink
32     , getNode
33     , getInstance
34     , getInstPrimaryNode
35     , getInstMinorsForNode
36     , buildLinkIpInstnameMap
37     , instNodes
38     ) where
39
40 import Control.Monad (liftM)
41 import Data.List (foldl')
42 import qualified Data.Map as M
43 import qualified Data.Set as S
44 import qualified Text.JSON as J
45
46 import Ganeti.HTools.JSON
47 import Ganeti.BasicTypes
48
49 import qualified Ganeti.Constants as C
50 import Ganeti.Objects
51
52 -- | Type alias for the link and ip map.
53 type LinkIpMap = M.Map String (M.Map String String)
54
55 -- | Reads the config file.
56 readConfig :: FilePath -> IO String
57 readConfig = readFile
58
59 -- | Parses the configuration file.
60 parseConfig :: String -> Result ConfigData
61 parseConfig = fromJResult "parsing configuration" . J.decodeStrict
62
63 -- | Wrapper over 'readConfig' and 'parseConfig'.
64 loadConfig :: FilePath -> IO (Result ConfigData)
65 loadConfig = fmap parseConfig . readConfig
66
67 -- * Query functions
68
69 -- | Computes the nodes covered by a disk.
70 computeDiskNodes :: Disk -> S.Set String
71 computeDiskNodes dsk =
72   case diskLogicalId dsk of
73     LIDDrbd8 nodeA nodeB _ _ _ _ -> S.fromList [nodeA, nodeB]
74     _ -> S.empty
75
76 -- | Computes all disk-related nodes of an instance. For non-DRBD,
77 -- this will be empty, for DRBD it will contain both the primary and
78 -- the secondaries.
79 instDiskNodes :: Instance -> S.Set String
80 instDiskNodes = S.unions . map computeDiskNodes . instDisks
81
82 -- | Computes all nodes of an instance.
83 instNodes :: Instance -> S.Set String
84 instNodes inst = instPrimaryNode inst `S.insert` instDiskNodes inst
85
86 -- | Computes the secondary nodes of an instance. Since this is valid
87 -- only for DRBD, we call directly 'instDiskNodes', skipping over the
88 -- extra primary insert.
89 instSecondaryNodes :: Instance -> S.Set String
90 instSecondaryNodes inst =
91   instPrimaryNode inst `S.delete` instDiskNodes inst
92
93 -- | Get instances of a given node.
94 getNodeInstances :: ConfigData -> String -> ([Instance], [Instance])
95 getNodeInstances cfg nname =
96     let all_inst = M.elems . fromContainer . configInstances $ cfg
97         pri_inst = filter ((== nname) . instPrimaryNode) all_inst
98         sec_inst = filter ((nname `S.member`) . instSecondaryNodes) all_inst
99     in (pri_inst, sec_inst)
100
101 -- | Returns the default cluster link.
102 getDefaultNicLink :: ConfigData -> String
103 getDefaultNicLink =
104   nicpLink . (M.! C.ppDefault) . fromContainer .
105   clusterNicparams . configCluster
106
107 -- | Returns instances of a given link.
108 getInstancesIpByLink :: LinkIpMap -> String -> [String]
109 getInstancesIpByLink linkipmap link =
110   M.keys $ M.findWithDefault M.empty link linkipmap
111
112 -- | Generic lookup function that converts from a possible abbreviated
113 -- name to a full name.
114 getItem :: String -> String -> M.Map String a -> Result a
115 getItem kind name allitems = do
116   let lresult = lookupName (M.keys allitems) name
117       err = \details -> Bad $ kind ++ " name " ++ name ++ " " ++ details
118   fullname <- case lrMatchPriority lresult of
119                 PartialMatch -> Ok $ lrContent lresult
120                 ExactMatch -> Ok $ lrContent lresult
121                 MultipleMatch -> err "has multiple matches"
122                 FailMatch -> err "not found"
123   maybe (err "not found after successfull match?!") Ok $
124         M.lookup fullname allitems
125
126 -- | Looks up a node.
127 getNode :: ConfigData -> String -> Result Node
128 getNode cfg name = getItem "Node" name (fromContainer $ configNodes cfg)
129
130 -- | Looks up an instance.
131 getInstance :: ConfigData -> String -> Result Instance
132 getInstance cfg name =
133   getItem "Instance" name (fromContainer $ configInstances cfg)
134
135 -- | Looks up an instance's primary node.
136 getInstPrimaryNode :: ConfigData -> String -> Result Node
137 getInstPrimaryNode cfg name =
138   liftM instPrimaryNode (getInstance cfg name) >>= getNode cfg
139
140 -- | Filters DRBD minors for a given node.
141 getDrbdMinorsForNode :: String -> Disk -> [(Int, String)]
142 getDrbdMinorsForNode node disk =
143   let child_minors = concatMap (getDrbdMinorsForNode node) (diskChildren disk)
144       this_minors =
145         case diskLogicalId disk of
146           LIDDrbd8 nodeA nodeB _ minorA minorB _
147             | nodeA == node -> [(minorA, nodeB)]
148             | nodeB == node -> [(minorB, nodeA)]
149           _ -> []
150   in this_minors ++ child_minors
151
152 -- | String for primary role.
153 rolePrimary :: String
154 rolePrimary = "primary"
155
156 -- | String for secondary role.
157 roleSecondary :: String
158 roleSecondary = "secondary"
159
160 -- | Gets the list of DRBD minors for an instance that are related to
161 -- a given node.
162 getInstMinorsForNode :: String -> Instance
163                      -> [(String, Int, String, String, String, String)]
164 getInstMinorsForNode node inst =
165   let role = if node == instPrimaryNode inst
166                then rolePrimary
167                else roleSecondary
168       iname = instName inst
169   -- FIXME: the disk/ build there is hack-ish; unify this in a
170   -- separate place, or reuse the iv_name (but that is deprecated on
171   -- the Python side)
172   in concatMap (\(idx, dsk) ->
173             [(node, minor, iname, "disk/" ++ show idx, role, peer)
174                | (minor, peer) <- getDrbdMinorsForNode node dsk]) .
175      zip [(0::Int)..] . instDisks $ inst
176
177 -- | Builds link -> ip -> instname map.
178 --
179 -- TODO: improve this by splitting it into multiple independent functions:
180 --
181 -- * abstract the \"fetch instance with filled params\" functionality
182 --
183 -- * abstsract the [instance] -> [(nic, instance_name)] part
184 --
185 -- * etc.
186 buildLinkIpInstnameMap :: ConfigData -> LinkIpMap
187 buildLinkIpInstnameMap cfg =
188   let cluster = configCluster cfg
189       instances = M.elems . fromContainer . configInstances $ cfg
190       defparams = (M.!) (fromContainer $ clusterNicparams cluster) C.ppDefault
191       nics = concatMap (\i -> [(instName i, nic) | nic <- instNics i])
192              instances
193   in foldl' (\accum (iname, nic) ->
194                let pparams = nicNicparams nic
195                    fparams = fillNICParams defparams pparams
196                    link = nicpLink fparams
197                in case nicIp nic of
198                     Nothing -> accum
199                     Just ip -> let oldipmap = M.findWithDefault (M.empty)
200                                               link accum
201                                    newipmap = M.insert ip iname oldipmap
202                                in M.insert link newipmap accum
203             ) M.empty nics