Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Harep.hs @ 4ba5f148

History | View | Annotate | Download (14.3 kB)

1 b6d9bec8 Dato Simó
{-| Auto-repair tool for Ganeti.
2 b6d9bec8 Dato Simó
3 b6d9bec8 Dato Simó
-}
4 b6d9bec8 Dato Simó
5 b6d9bec8 Dato Simó
{-
6 b6d9bec8 Dato Simó
7 b6d9bec8 Dato Simó
Copyright (C) 2013 Google Inc.
8 b6d9bec8 Dato Simó
9 b6d9bec8 Dato Simó
This program is free software; you can redistribute it and/or modify
10 b6d9bec8 Dato Simó
it under the terms of the GNU General Public License as published by
11 b6d9bec8 Dato Simó
the Free Software Foundation; either version 2 of the License, or
12 b6d9bec8 Dato Simó
(at your option) any later version.
13 b6d9bec8 Dato Simó
14 b6d9bec8 Dato Simó
This program is distributed in the hope that it will be useful, but
15 b6d9bec8 Dato Simó
WITHOUT ANY WARRANTY; without even the implied warranty of
16 b6d9bec8 Dato Simó
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 b6d9bec8 Dato Simó
General Public License for more details.
18 b6d9bec8 Dato Simó
19 b6d9bec8 Dato Simó
You should have received a copy of the GNU General Public License
20 b6d9bec8 Dato Simó
along with this program; if not, write to the Free Software
21 b6d9bec8 Dato Simó
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 b6d9bec8 Dato Simó
02110-1301, USA.
23 b6d9bec8 Dato Simó
24 b6d9bec8 Dato Simó
-}
25 b6d9bec8 Dato Simó
26 b6d9bec8 Dato Simó
module Ganeti.HTools.Program.Harep
27 b6d9bec8 Dato Simó
  ( main
28 b6d9bec8 Dato Simó
  , arguments
29 b6d9bec8 Dato Simó
  , options) where
30 b6d9bec8 Dato Simó
31 a5e58418 Dato Simó
import Control.Exception (bracket)
32 b6d9bec8 Dato Simó
import Control.Monad
33 3416e3e7 Dato Simó
import Data.Function
34 3416e3e7 Dato Simó
import Data.List
35 3416e3e7 Dato Simó
import Data.Maybe
36 3416e3e7 Dato Simó
import Data.Ord
37 3416e3e7 Dato Simó
import System.Time
38 b6d9bec8 Dato Simó
39 3416e3e7 Dato Simó
import Ganeti.BasicTypes
40 b6d9bec8 Dato Simó
import Ganeti.Common
41 a5e58418 Dato Simó
import Ganeti.Errors
42 a5e58418 Dato Simó
import Ganeti.Jobs
43 a5e58418 Dato Simó
import Ganeti.OpCodes
44 4ba5f148 Dato Simó
import Ganeti.OpParams
45 3416e3e7 Dato Simó
import Ganeti.Types
46 b6d9bec8 Dato Simó
import Ganeti.Utils
47 3416e3e7 Dato Simó
import qualified Ganeti.Constants as C
48 a5e58418 Dato Simó
import qualified Ganeti.Luxi as L
49 3416e3e7 Dato Simó
import qualified Ganeti.Path as Path
50 b6d9bec8 Dato Simó
51 b6d9bec8 Dato Simó
import Ganeti.HTools.CLI
52 3416e3e7 Dato Simó
import Ganeti.HTools.Loader
53 3416e3e7 Dato Simó
import Ganeti.HTools.ExtLoader
54 3416e3e7 Dato Simó
import Ganeti.HTools.Types
55 3416e3e7 Dato Simó
import qualified Ganeti.HTools.Container as Container
56 3416e3e7 Dato Simó
import qualified Ganeti.HTools.Instance as Instance
57 4ba5f148 Dato Simó
import qualified Ganeti.HTools.Node as Node
58 b6d9bec8 Dato Simó
59 b6d9bec8 Dato Simó
-- | Options list and functions.
60 b6d9bec8 Dato Simó
options :: IO [OptType]
61 b6d9bec8 Dato Simó
options = do
62 b6d9bec8 Dato Simó
  luxi <- oLuxiSocket
63 b6d9bec8 Dato Simó
  return
64 b6d9bec8 Dato Simó
    [ luxi
65 b6d9bec8 Dato Simó
    ]
66 b6d9bec8 Dato Simó
67 b6d9bec8 Dato Simó
arguments :: [ArgCompletion]
68 b6d9bec8 Dato Simó
arguments = []
69 b6d9bec8 Dato Simó
70 3416e3e7 Dato Simó
data InstanceData = InstanceData { arInstance :: Instance.Instance
71 3416e3e7 Dato Simó
                                 , arState :: AutoRepairStatus
72 3416e3e7 Dato Simó
                                 , tagsToRemove :: [String]
73 3416e3e7 Dato Simó
                                 }
74 3416e3e7 Dato Simó
                    deriving (Eq, Show)
75 3416e3e7 Dato Simó
76 3416e3e7 Dato Simó
-- | Parse a tag into an 'AutoRepairData' record.
77 3416e3e7 Dato Simó
--
78 3416e3e7 Dato Simó
-- @Nothing@ is returned if the tag is not an auto-repair tag, or if it's
79 3416e3e7 Dato Simó
-- malformed.
80 3416e3e7 Dato Simó
parseInitTag :: String -> Maybe AutoRepairData
81 3416e3e7 Dato Simó
parseInitTag tag =
82 3416e3e7 Dato Simó
  let parsePending = do
83 3416e3e7 Dato Simó
        subtag <- chompPrefix C.autoRepairTagPending tag
84 3416e3e7 Dato Simó
        case sepSplit ':' subtag of
85 3416e3e7 Dato Simó
          [rtype, uuid, ts, jobs] -> makeArData rtype uuid ts jobs
86 3416e3e7 Dato Simó
          _                       -> fail ("Invalid tag: " ++ show tag)
87 3416e3e7 Dato Simó
88 3416e3e7 Dato Simó
      parseResult = do
89 3416e3e7 Dato Simó
        subtag <- chompPrefix C.autoRepairTagResult tag
90 3416e3e7 Dato Simó
        case sepSplit ':' subtag of
91 3416e3e7 Dato Simó
          [rtype, uuid, ts, result, jobs] -> do
92 3416e3e7 Dato Simó
            arData <- makeArData rtype uuid ts jobs
93 3416e3e7 Dato Simó
            result' <- autoRepairResultFromRaw result
94 3416e3e7 Dato Simó
            return arData { arResult = Just result' }
95 3416e3e7 Dato Simó
          _                               -> fail ("Invalid tag: " ++ show tag)
96 3416e3e7 Dato Simó
97 3416e3e7 Dato Simó
      makeArData rtype uuid ts jobs = do
98 3416e3e7 Dato Simó
        rtype' <- autoRepairTypeFromRaw rtype
99 3416e3e7 Dato Simó
        ts' <- tryRead "auto-repair time" ts
100 3416e3e7 Dato Simó
        jobs' <- mapM makeJobIdS $ sepSplit '+' jobs
101 3416e3e7 Dato Simó
        return AutoRepairData { arType = rtype'
102 3416e3e7 Dato Simó
                              , arUuid = uuid
103 3416e3e7 Dato Simó
                              , arTime = TOD ts' 0
104 3416e3e7 Dato Simó
                              , arJobs = jobs'
105 3416e3e7 Dato Simó
                              , arResult = Nothing
106 3416e3e7 Dato Simó
                              , arTag = tag
107 3416e3e7 Dato Simó
                              }
108 3416e3e7 Dato Simó
  in
109 3416e3e7 Dato Simó
   parsePending `mplus` parseResult
110 3416e3e7 Dato Simó
111 3416e3e7 Dato Simó
-- | Return the 'AutoRepairData' element of an 'AutoRepairStatus' type.
112 3416e3e7 Dato Simó
getArData :: AutoRepairStatus -> Maybe AutoRepairData
113 3416e3e7 Dato Simó
getArData status =
114 3416e3e7 Dato Simó
  case status of
115 3416e3e7 Dato Simó
    ArHealthy (Just d) -> Just d
116 3416e3e7 Dato Simó
    ArFailedRepair  d  -> Just d
117 3416e3e7 Dato Simó
    ArPendingRepair d  -> Just d
118 3416e3e7 Dato Simó
    ArNeedsRepair   d  -> Just d
119 3416e3e7 Dato Simó
    _                  -> Nothing
120 3416e3e7 Dato Simó
121 a5e58418 Dato Simó
-- | Return a short name for each auto-repair status.
122 a5e58418 Dato Simó
--
123 a5e58418 Dato Simó
-- This is a more concise representation of the status, because the default
124 a5e58418 Dato Simó
-- "Show" formatting includes all the accompanying auto-repair data.
125 a5e58418 Dato Simó
arStateName :: AutoRepairStatus -> String
126 a5e58418 Dato Simó
arStateName status =
127 a5e58418 Dato Simó
  case status of
128 a5e58418 Dato Simó
    ArHealthy _       -> "Healthy"
129 a5e58418 Dato Simó
    ArFailedRepair _  -> "Failure"
130 a5e58418 Dato Simó
    ArPendingRepair _ -> "Pending repair"
131 a5e58418 Dato Simó
    ArNeedsRepair _   -> "Needs repair"
132 a5e58418 Dato Simó
133 3416e3e7 Dato Simó
-- | Return a new list of tags to remove that includes @arTag@ if present.
134 3416e3e7 Dato Simó
delCurTag :: InstanceData -> [String]
135 3416e3e7 Dato Simó
delCurTag instData =
136 3416e3e7 Dato Simó
  let arData = getArData $ arState instData
137 3416e3e7 Dato Simó
      rmTags = tagsToRemove instData
138 3416e3e7 Dato Simó
  in
139 3416e3e7 Dato Simó
   case arData of
140 3416e3e7 Dato Simó
     Just d  -> arTag d : rmTags
141 3416e3e7 Dato Simó
     Nothing -> rmTags
142 3416e3e7 Dato Simó
143 3416e3e7 Dato Simó
-- | Set the initial auto-repair state of an instance from its auto-repair tags.
144 3416e3e7 Dato Simó
--
145 3416e3e7 Dato Simó
-- The rules when there are multiple tags is:
146 3416e3e7 Dato Simó
--
147 3416e3e7 Dato Simó
--   * the earliest failure result always wins
148 3416e3e7 Dato Simó
--
149 3416e3e7 Dato Simó
--   * two or more pending repairs results in a fatal error
150 3416e3e7 Dato Simó
--
151 3416e3e7 Dato Simó
--   * a pending result from id X and a success result from id Y result in error
152 3416e3e7 Dato Simó
--     if Y is newer than X
153 3416e3e7 Dato Simó
--
154 3416e3e7 Dato Simó
--   * if there are no pending repairs, the newest success result wins,
155 3416e3e7 Dato Simó
--     otherwise the pending result is used.
156 3416e3e7 Dato Simó
setInitialState :: Instance.Instance -> Result InstanceData
157 3416e3e7 Dato Simó
setInitialState inst =
158 3416e3e7 Dato Simó
  let arData = mapMaybe parseInitTag $ Instance.allTags inst
159 3416e3e7 Dato Simó
      -- Group all the AutoRepairData records by id (i.e. by repair task), and
160 3416e3e7 Dato Simó
      -- present them from oldest to newest.
161 3416e3e7 Dato Simó
      arData' = sortBy (comparing arUuid) arData
162 3416e3e7 Dato Simó
      arGroups = groupBy ((==) `on` arUuid) arData'
163 3416e3e7 Dato Simó
      arGroups' = sortBy (comparing $ minimum . map arTime) arGroups
164 3416e3e7 Dato Simó
  in
165 3416e3e7 Dato Simó
   foldM arStatusCmp (InstanceData inst (ArHealthy Nothing) []) arGroups'
166 3416e3e7 Dato Simó
167 3416e3e7 Dato Simó
-- | Update the initial status of an instance with new repair task tags.
168 3416e3e7 Dato Simó
--
169 3416e3e7 Dato Simó
-- This function gets called once per repair group in an instance's tag, and it
170 3416e3e7 Dato Simó
-- determines whether to set the status of the instance according to this new
171 3416e3e7 Dato Simó
-- group, or to keep the existing state. See the documentation for
172 3416e3e7 Dato Simó
-- 'setInitialState' for the rules to be followed when determining this.
173 3416e3e7 Dato Simó
arStatusCmp :: InstanceData -> [AutoRepairData] -> Result InstanceData
174 3416e3e7 Dato Simó
arStatusCmp instData arData =
175 3416e3e7 Dato Simó
  let curSt = arState instData
176 3416e3e7 Dato Simó
      arData' = sortBy (comparing keyfn) arData
177 3416e3e7 Dato Simó
      keyfn d = (arResult d, arTime d)
178 3416e3e7 Dato Simó
      newData = last arData'
179 3416e3e7 Dato Simó
      newSt = case arResult newData of
180 3416e3e7 Dato Simó
                Just ArSuccess -> ArHealthy $ Just newData
181 3416e3e7 Dato Simó
                Just ArEnoperm -> ArHealthy $ Just newData
182 3416e3e7 Dato Simó
                Just ArFailure -> ArFailedRepair newData
183 3416e3e7 Dato Simó
                Nothing        -> ArPendingRepair newData
184 3416e3e7 Dato Simó
  in
185 3416e3e7 Dato Simó
   case curSt of
186 3416e3e7 Dato Simó
     ArFailedRepair _ -> Ok instData  -- Always keep the earliest failure.
187 3416e3e7 Dato Simó
     ArHealthy _      -> Ok instData { arState = newSt
188 3416e3e7 Dato Simó
                                     , tagsToRemove = delCurTag instData
189 3416e3e7 Dato Simó
                                     }
190 3416e3e7 Dato Simó
     ArPendingRepair d -> Bad (
191 3416e3e7 Dato Simó
       "An unfinished repair was found in instance " ++
192 3416e3e7 Dato Simó
       Instance.name (arInstance instData) ++ ": found tag " ++
193 3416e3e7 Dato Simó
       show (arTag newData) ++ ", but older pending tag " ++
194 3416e3e7 Dato Simó
       show (arTag d) ++ "exists.")
195 3416e3e7 Dato Simó
196 3416e3e7 Dato Simó
     ArNeedsRepair _ -> Bad
197 3416e3e7 Dato Simó
       "programming error: ArNeedsRepair found as an initial state"
198 3416e3e7 Dato Simó
199 a5e58418 Dato Simó
-- | Query jobs of a pending repair, returning the new instance data.
200 a5e58418 Dato Simó
processPending :: L.Client -> InstanceData -> IO InstanceData
201 a5e58418 Dato Simó
processPending client instData =
202 a5e58418 Dato Simó
  case arState instData of
203 a5e58418 Dato Simó
    (ArPendingRepair arData) -> do
204 a5e58418 Dato Simó
      sts <- L.queryJobsStatus client $ arJobs arData
205 a5e58418 Dato Simó
      time <- getClockTime
206 a5e58418 Dato Simó
      case sts of
207 a5e58418 Dato Simó
        Bad e -> exitErr $ "could not check job status: " ++ formatError e
208 a5e58418 Dato Simó
        Ok sts' ->
209 a5e58418 Dato Simó
          if any (<= JOB_STATUS_RUNNING) sts' then
210 a5e58418 Dato Simó
            return instData -- (no change)
211 a5e58418 Dato Simó
          else do
212 a5e58418 Dato Simó
            let iname = Instance.name $ arInstance instData
213 a5e58418 Dato Simó
                srcSt = arStateName $ arState instData
214 a5e58418 Dato Simó
                destSt = arStateName arState'
215 a5e58418 Dato Simó
            putStrLn ("Moving " ++ iname ++ " from " ++ show srcSt ++ " to " ++
216 a5e58418 Dato Simó
                      show destSt)
217 a5e58418 Dato Simó
            commitChange client instData'
218 a5e58418 Dato Simó
          where
219 a5e58418 Dato Simó
            instData' =
220 a5e58418 Dato Simó
              instData { arState = arState'
221 a5e58418 Dato Simó
                       , tagsToRemove = delCurTag instData
222 a5e58418 Dato Simó
                       }
223 a5e58418 Dato Simó
            arState' =
224 a5e58418 Dato Simó
              if all (== JOB_STATUS_SUCCESS) sts' then
225 a5e58418 Dato Simó
                ArHealthy $ Just (updateTag $ arData { arResult = Just ArSuccess
226 a5e58418 Dato Simó
                                                     , arTime = time })
227 a5e58418 Dato Simó
              else
228 a5e58418 Dato Simó
                ArFailedRepair (updateTag $ arData { arResult = Just ArFailure
229 a5e58418 Dato Simó
                                                   , arTime = time })
230 a5e58418 Dato Simó
231 a5e58418 Dato Simó
    _ -> return instData
232 a5e58418 Dato Simó
233 a5e58418 Dato Simó
-- | Update the tag of an 'AutoRepairData' record to match all the other fields.
234 a5e58418 Dato Simó
updateTag :: AutoRepairData -> AutoRepairData
235 a5e58418 Dato Simó
updateTag arData =
236 a5e58418 Dato Simó
  let ini = [autoRepairTypeToRaw $ arType arData,
237 a5e58418 Dato Simó
             arUuid arData,
238 a5e58418 Dato Simó
             clockTimeToString $ arTime arData]
239 a5e58418 Dato Simó
      end = [intercalate "+" . map (show . fromJobId) $ arJobs arData]
240 a5e58418 Dato Simó
      (pfx, middle) =
241 a5e58418 Dato Simó
         case arResult arData of
242 a5e58418 Dato Simó
          Nothing -> (C.autoRepairTagPending, [])
243 a5e58418 Dato Simó
          Just rs -> (C.autoRepairTagResult, [autoRepairResultToRaw rs])
244 a5e58418 Dato Simó
  in
245 a5e58418 Dato Simó
   arData { arTag = pfx ++ intercalate ":" (ini ++ middle ++ end) }
246 a5e58418 Dato Simó
247 a5e58418 Dato Simó
-- | Apply and remove tags from an instance as indicated by 'InstanceData'.
248 a5e58418 Dato Simó
--
249 a5e58418 Dato Simó
-- If the /arState/ of the /InstanceData/ record has an associated
250 a5e58418 Dato Simó
-- 'AutoRepairData', add its tag to the instance object. Additionally, if
251 a5e58418 Dato Simó
-- /tagsToRemove/ is not empty, remove those tags from the instance object. The
252 a5e58418 Dato Simó
-- returned /InstanceData/ object always has an empty /tagsToRemove/.
253 a5e58418 Dato Simó
commitChange :: L.Client -> InstanceData -> IO InstanceData
254 a5e58418 Dato Simó
commitChange client instData = do
255 a5e58418 Dato Simó
  let iname = Instance.name $ arInstance instData
256 a5e58418 Dato Simó
      arData = getArData $ arState instData
257 a5e58418 Dato Simó
      rmTags = tagsToRemove instData
258 a5e58418 Dato Simó
      execJobsWaitOk' opcodes = do
259 a5e58418 Dato Simó
        res <- execJobsWaitOk [map wrapOpCode opcodes] client
260 a5e58418 Dato Simó
        case res of
261 a5e58418 Dato Simó
          Ok _ -> return ()
262 a5e58418 Dato Simó
          Bad e -> exitErr e
263 a5e58418 Dato Simó
264 a5e58418 Dato Simó
  when (isJust arData) $ do
265 a5e58418 Dato Simó
    let tag = arTag $ fromJust arData
266 a5e58418 Dato Simó
    putStrLn (">>> Adding the following tag to " ++ iname ++ ":\n" ++ show tag)
267 a5e58418 Dato Simó
    execJobsWaitOk' [OpTagsSet (TagInstance iname) [tag]]
268 a5e58418 Dato Simó
269 a5e58418 Dato Simó
  unless (null rmTags) $ do
270 a5e58418 Dato Simó
    putStr (">>> Removing the following tags from " ++ iname ++ ":\n" ++
271 a5e58418 Dato Simó
            unlines (map show rmTags))
272 a5e58418 Dato Simó
    execJobsWaitOk' [OpTagsDel (TagInstance iname) rmTags]
273 a5e58418 Dato Simó
274 a5e58418 Dato Simó
  return instData { tagsToRemove = [] }
275 a5e58418 Dato Simó
276 4ba5f148 Dato Simó
-- | Detect brokeness with an instance and suggest repair type and jobs to run.
277 4ba5f148 Dato Simó
detectBroken :: Node.List -> Instance.Instance
278 4ba5f148 Dato Simó
             -> Maybe (AutoRepairType, [OpCode])
279 4ba5f148 Dato Simó
detectBroken nl inst =
280 4ba5f148 Dato Simó
  let disk = Instance.diskTemplate inst
281 4ba5f148 Dato Simó
      iname = Instance.name inst
282 4ba5f148 Dato Simó
      offPri = Node.offline $ Container.find (Instance.pNode inst) nl
283 4ba5f148 Dato Simó
      offSec = Node.offline $ Container.find (Instance.sNode inst) nl
284 4ba5f148 Dato Simó
  in
285 4ba5f148 Dato Simó
   case disk of
286 4ba5f148 Dato Simó
     DTDrbd8
287 4ba5f148 Dato Simó
       | offPri && offSec ->
288 4ba5f148 Dato Simó
         Just (
289 4ba5f148 Dato Simó
           ArReinstall,
290 4ba5f148 Dato Simó
           [ OpInstanceRecreateDisks { opInstanceName = iname
291 4ba5f148 Dato Simó
                                     , opRecreateDisksInfo = RecreateDisksAll
292 4ba5f148 Dato Simó
                                     , opNodes = []
293 4ba5f148 Dato Simó
                                       -- FIXME: there should be a better way to
294 4ba5f148 Dato Simó
                                       -- specify opcode paramteres than abusing
295 4ba5f148 Dato Simó
                                       -- mkNonEmpty in this way (using the fact
296 4ba5f148 Dato Simó
                                       -- that Maybe is used both for optional
297 4ba5f148 Dato Simó
                                       -- fields, and to express failure).
298 4ba5f148 Dato Simó
                                     , opIallocator = mkNonEmpty "hail"
299 4ba5f148 Dato Simó
                                     }
300 4ba5f148 Dato Simó
           , OpInstanceReinstall { opInstanceName = iname
301 4ba5f148 Dato Simó
                                 , opOsType = Nothing
302 4ba5f148 Dato Simó
                                 , opTempOsParams = Nothing
303 4ba5f148 Dato Simó
                                 , opForceVariant = False
304 4ba5f148 Dato Simó
                                 }
305 4ba5f148 Dato Simó
           ])
306 4ba5f148 Dato Simó
       | offPri ->
307 4ba5f148 Dato Simó
         Just (
308 4ba5f148 Dato Simó
           ArFailover,
309 4ba5f148 Dato Simó
           [ OpInstanceFailover { opInstanceName = iname
310 4ba5f148 Dato Simó
                                  -- FIXME: ditto, see above.
311 4ba5f148 Dato Simó
                                , opShutdownTimeout = fromJust $ mkNonNegative
312 4ba5f148 Dato Simó
                                                      C.defaultShutdownTimeout
313 4ba5f148 Dato Simó
                                , opIgnoreConsistency = False
314 4ba5f148 Dato Simó
                                , opTargetNode = Nothing
315 4ba5f148 Dato Simó
                                , opIgnoreIpolicy = False
316 4ba5f148 Dato Simó
                                , opIallocator = Nothing
317 4ba5f148 Dato Simó
                                }
318 4ba5f148 Dato Simó
           ])
319 4ba5f148 Dato Simó
       | offSec ->
320 4ba5f148 Dato Simó
         Just (
321 4ba5f148 Dato Simó
           ArFixStorage,
322 4ba5f148 Dato Simó
           [ OpInstanceReplaceDisks { opInstanceName = iname
323 4ba5f148 Dato Simó
                                    , opReplaceDisksMode = ReplaceNewSecondary
324 4ba5f148 Dato Simó
                                    , opReplaceDisksList = []
325 4ba5f148 Dato Simó
                                    , opRemoteNode = Nothing
326 4ba5f148 Dato Simó
                                      -- FIXME: ditto, see above.
327 4ba5f148 Dato Simó
                                    , opIallocator = mkNonEmpty "hail"
328 4ba5f148 Dato Simó
                                    , opEarlyRelease = False
329 4ba5f148 Dato Simó
                                    , opIgnoreIpolicy = False
330 4ba5f148 Dato Simó
                                    }
331 4ba5f148 Dato Simó
            ])
332 4ba5f148 Dato Simó
       | otherwise -> Nothing
333 4ba5f148 Dato Simó
334 4ba5f148 Dato Simó
     DTPlain
335 4ba5f148 Dato Simó
       | offPri ->
336 4ba5f148 Dato Simó
         Just (
337 4ba5f148 Dato Simó
           ArReinstall,
338 4ba5f148 Dato Simó
           [ OpInstanceRecreateDisks { opInstanceName = iname
339 4ba5f148 Dato Simó
                                     , opRecreateDisksInfo = RecreateDisksAll
340 4ba5f148 Dato Simó
                                     , opNodes = []
341 4ba5f148 Dato Simó
                                       -- FIXME: ditto, see above.
342 4ba5f148 Dato Simó
                                     , opIallocator = mkNonEmpty "hail"
343 4ba5f148 Dato Simó
                                     }
344 4ba5f148 Dato Simó
           , OpInstanceReinstall { opInstanceName = iname
345 4ba5f148 Dato Simó
                                 , opOsType = Nothing
346 4ba5f148 Dato Simó
                                 , opTempOsParams = Nothing
347 4ba5f148 Dato Simó
                                 , opForceVariant = False
348 4ba5f148 Dato Simó
                                 }
349 4ba5f148 Dato Simó
           ])
350 4ba5f148 Dato Simó
       | otherwise -> Nothing
351 4ba5f148 Dato Simó
352 4ba5f148 Dato Simó
     _ -> Nothing  -- Other cases are unimplemented for now: DTDiskless,
353 4ba5f148 Dato Simó
                   -- DTFile, DTSharedFile, DTBlock, DTRbd, DTExt.
354 4ba5f148 Dato Simó
355 b6d9bec8 Dato Simó
-- | Main function.
356 b6d9bec8 Dato Simó
main :: Options -> [String] -> IO ()
357 3416e3e7 Dato Simó
main opts args = do
358 b6d9bec8 Dato Simó
  unless (null args) $
359 b6d9bec8 Dato Simó
    exitErr "this program doesn't take any arguments."
360 b6d9bec8 Dato Simó
361 3416e3e7 Dato Simó
  luxiDef <- Path.defaultLuxiSocket
362 3416e3e7 Dato Simó
  let master = fromMaybe luxiDef $ optLuxi opts
363 3416e3e7 Dato Simó
      opts' = opts { optLuxi = Just master }
364 3416e3e7 Dato Simó
365 4ba5f148 Dato Simó
  (ClusterData _ nl il _ _) <- loadExternalData opts'
366 3416e3e7 Dato Simó
367 3416e3e7 Dato Simó
  let iniDataRes = mapM setInitialState $ Container.elems il
368 a5e58418 Dato Simó
  iniData <- exitIfBad "when parsing auto-repair tags" iniDataRes
369 a5e58418 Dato Simó
370 a5e58418 Dato Simó
  -- First step: check all pending repairs, see if they are completed.
371 4ba5f148 Dato Simó
  iniData' <- bracket (L.getClient master) L.closeClient $
372 4ba5f148 Dato Simó
              forM iniData . processPending
373 4ba5f148 Dato Simó
374 4ba5f148 Dato Simó
  -- Second step: detect any problems.
375 4ba5f148 Dato Simó
  let _unused_repairs = map (detectBroken nl . arInstance) iniData'
376 3416e3e7 Dato Simó
377 b6d9bec8 Dato Simó
  return ()