Make Query operators enforce strictness
[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   , errToResult
37   , errorExitCode
38   , excName
39   , formatError
40   ) where
41
42 import Text.JSON hiding (Result, Ok)
43 import System.Exit
44
45 import Ganeti.THH
46 import Ganeti.BasicTypes
47 import qualified Ganeti.Constants as C
48
49 -- | Error code types for 'OpPrereqError'.
50 $(declareSADT "ErrorCode"
51   [ ("ECodeResolver",  'C.errorsEcodeResolver)
52   , ("ECodeNoRes",     'C.errorsEcodeNores)
53   , ("ECodeInval",     'C.errorsEcodeInval)
54   , ("ECodeState",     'C.errorsEcodeState)
55   , ("ECodeNoEnt",     'C.errorsEcodeNoent)
56   , ("ECodeExists",    'C.errorsEcodeExists)
57   , ("ECodeNotUnique", 'C.errorsEcodeNotunique)
58   , ("ECodeFault",     'C.errorsEcodeFault)
59   , ("ECodeEnviron",   'C.errorsEcodeEnviron)
60   ])
61 $(makeJSONInstance ''ErrorCode)
62
63 $(genException "GanetiException"
64   [ ("GenericError", [excErrMsg])
65   , ("LockError", [excErrMsg])
66   , ("PidFileLockError", [excErrMsg])
67   , ("HypervisorError", [excErrMsg])
68   , ("ProgrammerError", [excErrMsg])
69   , ("BlockDeviceError", [excErrMsg])
70   , ("ConfigurationError", [excErrMsg])
71   , ("ConfigVersionMismatch", [ ("expVer", [t| Int |])
72                               , ("actVer", [t| Int |])])
73   , ("ReservationError", [excErrMsg])
74   , ("RemoteError", [excErrMsg])
75   , ("SignatureError", [excErrMsg])
76   , ("ParameterError", [excErrMsg])
77   , ("ResultValidationError", [excErrMsg])
78   , ("OpPrereqError", [excErrMsg, ("errCode", [t| ErrorCode |])])
79   , ("OpExecError", [excErrMsg])
80   , ("OpResultError", [excErrMsg])
81   , ("OpCodeUnknown", [excErrMsg])
82   , ("JobLost", [excErrMsg])
83   , ("JobFileCorrupted", [excErrMsg])
84   , ("ResolverError", [ ("errHostname", [t| String |])
85                       , ("errResolverCode", [t| Int |])
86                       , ("errResolverMsg", [t| String |])])
87   , ("HooksFailure", [excErrMsg])
88   , ("HooksAbort", [("errs", [t| [(String, String, String)] |])])
89   , ("UnitParseError", [excErrMsg])
90   , ("ParseError", [excErrMsg])
91   , ("TypeEnforcementError", [excErrMsg])
92   , ("X509CertError", [ ("certFileName", [t| String |])
93                       , excErrMsg ])
94   , ("TagError", [excErrMsg])
95   , ("CommandError", [excErrMsg])
96   , ("StorageError", [excErrMsg])
97   , ("InotifyError", [excErrMsg])
98   , ("JobQueueError", [excErrMsg])
99   , ("JobQueueDrainError", [excErrMsg])
100   , ("JobQueueFull", [])
101   , ("ConfdMagicError", [excErrMsg])
102   , ("ConfdClientError", [excErrMsg])
103   , ("UdpDataSizeError", [excErrMsg])
104   , ("NoCtypesError", [excErrMsg])
105   , ("IPAddressError", [excErrMsg])
106   , ("LuxiError", [excErrMsg])
107   , ("QueryFilterParseError", [excErrMsg]) -- not consistent with Python
108   , ("RapiTestResult", [excErrMsg])
109   , ("FileStoragePathError", [excErrMsg])
110   ])
111
112 instance JSON GanetiException where
113   showJSON = saveGanetiException
114   readJSON = loadGanetiException
115
116 instance FromString GanetiException where
117   mkFromString = GenericError
118
119 -- | Error monad using 'GanetiException' type alias.
120 type ErrorResult = GenericResult GanetiException
121
122 $(genStrOfOp ''GanetiException "excName")
123
124 -- | Returns the exit code of a program that should be used if we got
125 -- back an exception from masterd.
126 errorExitCode :: GanetiException -> ExitCode
127 errorExitCode (ConfigurationError {}) = ExitFailure 2
128 errorExitCode _ = ExitFailure 1
129
130 -- | Formats an exception.
131 formatError :: GanetiException -> String
132 formatError (ConfigurationError msg) =
133   "Corrup configuration file: " ++ msg ++ "\nAborting."
134 formatError (HooksAbort errs) =
135   unlines $
136   "Failure: hooks execution failed:":
137   map (\(node, script, out) ->
138          "  node: " ++ node ++ ", script: " ++ script ++
139                     if null out
140                       then " (no output)"
141                       else ", output: " ++ out
142       ) errs
143 formatError (HooksFailure msg) =
144   "Failure: hooks general failure: " ++ msg
145 formatError (ResolverError host _ _) =
146   -- FIXME: in Python, this uses the system hostname to format the
147   -- error differently if we are failing to resolve our own hostname
148   "Failure: can't resolve hostname " ++ host
149 formatError (OpPrereqError msg code) =
150   "Failure: prerequisites not met for this" ++
151   " operation:\nerror type: " ++ show code ++ ", error details:\n" ++ msg
152 formatError (OpExecError msg) =
153   "Failure: command execution error:\n" ++ msg
154 formatError (TagError msg) =
155   "Failure: invalid tag(s) given:\n" ++ msg
156 formatError (JobQueueDrainError _)=
157   "Failure: the job queue is marked for drain and doesn't accept new requests"
158 formatError JobQueueFull =
159   "Failure: the job queue is full and doesn't accept new" ++
160   " job submissions until old jobs are archived"
161 formatError (TypeEnforcementError msg) =
162   "Parameter Error: " ++ msg
163 formatError (ParameterError msg) =
164   "Failure: unknown/wrong parameter name '" ++ msg ++ "'"
165 formatError (JobLost msg) =
166   "Error checking job status: " ++ msg
167 formatError (QueryFilterParseError msg) =
168   -- FIXME: in Python, this has a more complex error message
169   "Error while parsing query filter: " ++ msg
170 formatError (GenericError msg) =
171   "Unhandled Ganeti error: " ++ msg
172 formatError err =
173   "Unhandled exception: " ++ show err
174
175 -- | Convert from an 'ErrorResult' to a standard 'Result'.
176 errToResult :: ErrorResult a -> Result a
177 errToResult (Ok a)  = Ok a
178 errToResult (Bad e) = Bad $ formatError e