Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Errors.hs @ ace37e24

History | View | Annotate | Download (6.2 kB)

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