391e37986f3bc22a9ecf9ba9e1b5a5a847e77628
[ganeti-local] / htools / Ganeti / Errors.hs
1 {-# LANGUAGE TemplateHaskell #-}
2
3 {-| Implementation of the Ganeti error types.
4
5 This module implements our error hierarchy. Currently we implement one
6 identical to the Python one; later we might one to have separate ones
7 for frontend (clients), master and backend code.
8
9 -}
10
11 {-
12
13 Copyright (C) 2012 Google Inc.
14
15 This program is free software; you can redistribute it and/or modify
16 it under the terms of the GNU General Public License as published by
17 the Free Software Foundation; either version 2 of the License, or
18 (at your option) any later version.
19
20 This program is distributed in the hope that it will be useful, but
21 WITHOUT ANY WARRANTY; without even the implied warranty of
22 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
23 General Public License for more details.
24
25 You should have received a copy of the GNU General Public License
26 along with this program; if not, write to the Free Software
27 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
28 02110-1301, USA.
29
30 -}
31
32 module Ganeti.Errors
33   ( ErrorCode(..)
34   , GanetiException(..)
35   , ErrorResult
36   , excName
37   , errorExitCode
38   , formatError
39   ) where
40
41 import Text.JSON hiding (Result, Ok)
42 import System.Exit
43
44 import Ganeti.THH
45 import Ganeti.BasicTypes
46 import qualified Ganeti.Constants as C
47
48 -- | Error code types for 'OpPrereqError'.
49 $(declareSADT "ErrorCode"
50   [ ("ECodeResolver",  'C.errorsEcodeResolver)
51   , ("ECodeNoRes",     'C.errorsEcodeNores)
52   , ("ECodeInval",     'C.errorsEcodeInval)
53   , ("ECodeState",     'C.errorsEcodeState)
54   , ("ECodeNoEnt",     'C.errorsEcodeNoent)
55   , ("ECodeExists",    'C.errorsEcodeExists)
56   , ("ECodeNotUnique", 'C.errorsEcodeNotunique)
57   , ("ECodeFault",     'C.errorsEcodeFault)
58   , ("ECodeEnviron",   'C.errorsEcodeEnviron)
59   ])
60 $(makeJSONInstance ''ErrorCode)
61
62 $(genException "GanetiException"
63   [ ("GenericError", [excErrMsg])
64   , ("LockError", [excErrMsg])
65   , ("PidFileLockError", [excErrMsg])
66   , ("HypervisorError", [excErrMsg])
67   , ("ProgrammerError", [excErrMsg])
68   , ("BlockDeviceError", [excErrMsg])
69   , ("ConfigurationError", [excErrMsg])
70   , ("ConfigVersionMismatch", [ ("expCode", [t| Int |])
71                               , ("actCode", [t| Int |])])
72   , ("ReservationError", [excErrMsg])
73   , ("RemoteError", [excErrMsg])
74   , ("SignatureError", [excErrMsg])
75   , ("ParameterError", [excErrMsg])
76   , ("ResultValidationError", [excErrMsg])
77   , ("OpPrereqError", [excErrMsg, ("errCode", [t| ErrorCode |])])
78   , ("OpExecError", [excErrMsg])
79   , ("OpResultError", [excErrMsg])
80   , ("OpCodeUnknown", [excErrMsg])
81   , ("JobLost", [excErrMsg])
82   , ("JobFileCorrupted", [excErrMsg])
83   , ("ResolverError", [ ("errHostname", [t| String |])
84                       , ("errResolverCode", [t| Int |])
85                       , ("errResolverMsg", [t| String |])])
86   , ("HooksFailure", [excErrMsg])
87   , ("HooksAbort", [("errs", [t| [(String, String, String)] |])])
88   , ("UnitParseError", [excErrMsg])
89   , ("ParseError", [excErrMsg])
90   , ("TypeEnforcementError", [excErrMsg])
91   , ("X509CertError", [excErrMsg])
92   , ("TagError", [excErrMsg])
93   , ("CommandError", [excErrMsg])
94   , ("StorageError", [excErrMsg])
95   , ("InotifyError", [excErrMsg])
96   , ("JobQueueError", [excErrMsg])
97   , ("JobQueueDrainError", [excErrMsg])
98   , ("JobQueueFull", [])
99   , ("ConfdMagicError", [excErrMsg])
100   , ("ConfdClientError", [excErrMsg])
101   , ("UdpDataSizeError", [excErrMsg])
102   , ("NoCtypesError", [excErrMsg])
103   , ("IPAddressError", [excErrMsg])
104   , ("LuxiError", [excErrMsg])
105   , ("QueryFilterParseError", [excErrMsg]) -- not consistent with Python
106   , ("RapiTestResult", [excErrMsg])
107   , ("FileStoragePathError", [excErrMsg])
108   ])
109
110 instance JSON GanetiException where
111   showJSON = saveGanetiException
112   readJSON = loadGanetiException
113
114 instance FromString GanetiException where
115   mkFromString = GenericError
116
117 -- | Error monad using 'GanetiException' type alias.
118 type ErrorResult = GenericResult GanetiException
119
120 $(genStrOfOp ''GanetiException "excName")
121
122 -- | Returns the exit code of a program that should be used if we got
123 -- back an exception from masterd.
124 errorExitCode :: GanetiException -> ExitCode
125 errorExitCode (ConfigurationError {}) = ExitFailure 2
126 errorExitCode _ = ExitFailure 1
127
128 -- | Formats an exception.
129 formatError :: GanetiException -> String
130 formatError (ConfigurationError msg) =
131   "Corrup configuration file: " ++ msg ++ "\nAborting."
132 formatError (HooksAbort errs) =
133   unlines $
134   "Failure: hooks execution failed:":
135   map (\(node, script, out) ->
136          "  node: " ++ node ++ ", script: " ++ script ++
137                     if null out
138                       then " (no output)"
139                       else ", output: " ++ out
140       ) errs
141 formatError (HooksFailure msg) =
142   "Failure: hooks general failure: " ++ msg
143 formatError (ResolverError host _ _) =
144   -- FIXME: in Python, this uses the system hostname to format the
145   -- error differently if we are failing to resolve our own hostname
146   "Failure: can't resolve hostname " ++ host
147 formatError (OpPrereqError msg code) =
148   "Failure: prerequisites not met for this" ++
149   " operation:\nerror type: " ++ show code ++ ", error details:\n" ++ msg
150 formatError (OpExecError msg) =
151   "Failure: command execution error:\n" ++ msg
152 formatError (TagError msg) =
153   "Failure: invalid tag(s) given:\n" ++ msg
154 formatError (JobQueueDrainError _)=
155   "Failure: the job queue is marked for drain and doesn't accept new requests"
156 formatError JobQueueFull =
157   "Failure: the job queue is full and doesn't accept new" ++
158   " job submissions until old jobs are archived"
159 formatError (TypeEnforcementError msg) =
160   "Parameter Error: " ++ msg
161 formatError (ParameterError msg) =
162   "Failure: unknown/wrong parameter name '" ++ msg ++ "'"
163 formatError (JobLost msg) =
164   "Error checking job status: " ++ msg
165 formatError (QueryFilterParseError msg) =
166   -- FIXME: in Python, this has a more complex error message
167   "Error while parsing query filter: " ++ msg
168 formatError (GenericError msg) =
169   "Unhandled Ganeti error: " ++ msg
170 formatError err =
171   "Unhandled exception: " ++ show err