Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Server.hs @ 7711f32b

History | View | Annotate | Download (19.1 kB)

1 d120506c Agata Murawska
{-| Implementation of the Ganeti Query2 server.
2 25b54de0 Iustin Pop
3 25b54de0 Iustin Pop
-}
4 25b54de0 Iustin Pop
5 25b54de0 Iustin Pop
{-
6 25b54de0 Iustin Pop
7 72747d91 Iustin Pop
Copyright (C) 2012, 2013 Google Inc.
8 25b54de0 Iustin Pop
9 25b54de0 Iustin Pop
This program is free software; you can redistribute it and/or modify
10 25b54de0 Iustin Pop
it under the terms of the GNU General Public License as published by
11 25b54de0 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 25b54de0 Iustin Pop
(at your option) any later version.
13 25b54de0 Iustin Pop
14 25b54de0 Iustin Pop
This program is distributed in the hope that it will be useful, but
15 25b54de0 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 25b54de0 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 25b54de0 Iustin Pop
General Public License for more details.
18 25b54de0 Iustin Pop
19 25b54de0 Iustin Pop
You should have received a copy of the GNU General Public License
20 25b54de0 Iustin Pop
along with this program; if not, write to the Free Software
21 25b54de0 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 25b54de0 Iustin Pop
02110-1301, USA.
23 25b54de0 Iustin Pop
24 25b54de0 Iustin Pop
-}
25 25b54de0 Iustin Pop
26 4cab6703 Iustin Pop
module Ganeti.Query.Server
27 670e954a Thomas Thrainer
  ( main
28 670e954a Thomas Thrainer
  , checkMain
29 670e954a Thomas Thrainer
  , prepMain
30 0d0ac025 Iustin Pop
  ) where
31 25b54de0 Iustin Pop
32 f2374060 Iustin Pop
import Control.Applicative
33 25b54de0 Iustin Pop
import Control.Concurrent
34 25b54de0 Iustin Pop
import Control.Exception
35 c6013594 Klaus Aehlig
import Control.Monad (forever, when, zipWithM, liftM)
36 7711f32b Klaus Aehlig
import Control.Monad.IO.Class
37 25b54de0 Iustin Pop
import Data.Bits (bitSize)
38 c87997d2 Jose A. Lopes
import qualified Data.Set as Set (toList)
39 670e954a Thomas Thrainer
import Data.IORef
40 be7531a9 Klaus Aehlig
import Data.Maybe (fromMaybe)
41 25b54de0 Iustin Pop
import qualified Text.JSON as J
42 6222b3a3 Klaus Aehlig
import Text.JSON (encode, showJSON, JSValue(..))
43 25b54de0 Iustin Pop
import System.Info (arch)
44 d5665e10 Klaus Aehlig
import System.Directory
45 25b54de0 Iustin Pop
46 25b54de0 Iustin Pop
import qualified Ganeti.Constants as C
47 c87997d2 Jose A. Lopes
import qualified Ganeti.ConstantUtils as ConstantUtils (unFrozenSet)
48 5183e8be Iustin Pop
import Ganeti.Errors
49 9eeb0aa5 Michael Hanselmann
import qualified Ganeti.Path as Path
50 0d0ac025 Iustin Pop
import Ganeti.Daemon
51 25b54de0 Iustin Pop
import Ganeti.Objects
52 f2374060 Iustin Pop
import qualified Ganeti.Config as Config
53 218e3b0f Thomas Thrainer
import Ganeti.ConfigReader
54 25b54de0 Iustin Pop
import Ganeti.BasicTypes
55 e5fba493 Klaus Aehlig
import Ganeti.JQueue
56 b5fa2700 Klaus Aehlig
import Ganeti.JQScheduler
57 25b54de0 Iustin Pop
import Ganeti.Logging
58 25b54de0 Iustin Pop
import Ganeti.Luxi
59 4cab6703 Iustin Pop
import qualified Ganeti.Query.Language as Qlang
60 1c3231aa Thomas Thrainer
import qualified Ganeti.Query.Cluster as QCluster
61 7711f32b Klaus Aehlig
import Ganeti.Path ( queueDir, jobQueueLockFile, jobQueueDrainFile
62 7711f32b Klaus Aehlig
                   , defaultMasterSocket)
63 946f1fb3 Klaus Aehlig
import Ganeti.Rpc
64 4cbe9bda Iustin Pop
import Ganeti.Query.Query
65 c4e0d065 Klaus Aehlig
import Ganeti.Query.Filter (makeSimpleFilter)
66 6e94b75c Jose A. Lopes
import Ganeti.Types
67 c7003a76 Petr Pudlak
import qualified Ganeti.UDSServer as U (Handler(..), listener)
68 857cbfb1 Klaus Aehlig
import Ganeti.Utils (lockFile, exitIfBad, watchFile, safeRenameFile)
69 3cb9bd38 Jose A. Lopes
import qualified Ganeti.Version as Version
70 25b54de0 Iustin Pop
71 cd67e337 Iustin Pop
-- | Helper for classic queries.
72 cd67e337 Iustin Pop
handleClassicQuery :: ConfigData      -- ^ Cluster config
73 cd67e337 Iustin Pop
                   -> Qlang.ItemType  -- ^ Query type
74 037762a9 Iustin Pop
                   -> [Either String Integer] -- ^ Requested names
75 037762a9 Iustin Pop
                                              -- (empty means all)
76 cd67e337 Iustin Pop
                   -> [String]        -- ^ Requested fields
77 cd67e337 Iustin Pop
                   -> Bool            -- ^ Whether to do sync queries or not
78 5183e8be Iustin Pop
                   -> IO (GenericResult GanetiException JSValue)
79 c4e0d065 Klaus Aehlig
handleClassicQuery _ _ _ _ True =
80 5183e8be Iustin Pop
  return . Bad $ OpPrereqError "Sync queries are not allowed" ECodeInval
81 c4e0d065 Klaus Aehlig
handleClassicQuery cfg qkind names fields _ = do
82 c4e0d065 Klaus Aehlig
  let flt = makeSimpleFilter (nameField qkind) names
83 cd67e337 Iustin Pop
  qr <- query cfg True (Qlang.Query qkind fields flt)
84 cd67e337 Iustin Pop
  return $ showJSON <$> (qr >>= queryCompat)
85 cd67e337 Iustin Pop
86 25b54de0 Iustin Pop
-- | Minimal wrapper to handle the missing config case.
87 9131274c Jose A. Lopes
handleCallWrapper :: MVar () -> JQStatus ->  Result ConfigData
88 e5fba493 Klaus Aehlig
                     -> LuxiOp -> IO (ErrorResult JSValue)
89 b5fa2700 Klaus Aehlig
handleCallWrapper _ _ (Bad msg) _ =
90 5183e8be Iustin Pop
  return . Bad . ConfigurationError $
91 5183e8be Iustin Pop
           "I do not have access to a valid configuration, cannot\
92 5183e8be Iustin Pop
           \ process queries: " ++ msg
93 b5fa2700 Klaus Aehlig
handleCallWrapper qlock qstat (Ok config) op = handleCall qlock qstat config op
94 25b54de0 Iustin Pop
95 25b54de0 Iustin Pop
-- | Actual luxi operation handler.
96 9131274c Jose A. Lopes
handleCall :: MVar () -> JQStatus
97 b5fa2700 Klaus Aehlig
              -> ConfigData -> LuxiOp -> IO (ErrorResult JSValue)
98 b5fa2700 Klaus Aehlig
handleCall _ _ cdata QueryClusterInfo =
99 25b54de0 Iustin Pop
  let cluster = configCluster cdata
100 1c3231aa Thomas Thrainer
      master = QCluster.clusterMasterNodeName cdata
101 25b54de0 Iustin Pop
      hypervisors = clusterEnabledHypervisors cluster
102 966e1580 Helga Velroyen
      diskTemplates = clusterEnabledDiskTemplates cluster
103 72747d91 Iustin Pop
      def_hv = case hypervisors of
104 72747d91 Iustin Pop
                 x:_ -> showJSON x
105 72747d91 Iustin Pop
                 [] -> JSNull
106 25b54de0 Iustin Pop
      bits = show (bitSize (0::Int)) ++ "bits"
107 25b54de0 Iustin Pop
      arch_tuple = [bits, arch]
108 5b11f8db Iustin Pop
      obj = [ ("software_version", showJSON C.releaseVersion)
109 5b11f8db Iustin Pop
            , ("protocol_version", showJSON C.protocolVersion)
110 5b11f8db Iustin Pop
            , ("config_version", showJSON C.configVersion)
111 c87997d2 Jose A. Lopes
            , ("os_api_version", showJSON . maximum .
112 c87997d2 Jose A. Lopes
                                 Set.toList . ConstantUtils.unFrozenSet $
113 c87997d2 Jose A. Lopes
                                 C.osApiVersions)
114 5b11f8db Iustin Pop
            , ("export_version", showJSON C.exportVersion)
115 3cb9bd38 Jose A. Lopes
            , ("vcs_version", showJSON Version.version)
116 5b11f8db Iustin Pop
            , ("architecture", showJSON arch_tuple)
117 25b54de0 Iustin Pop
            , ("name", showJSON $ clusterClusterName cluster)
118 1c3231aa Thomas Thrainer
            , ("master", showJSON (case master of
119 1c3231aa Thomas Thrainer
                                     Ok name -> name
120 1c3231aa Thomas Thrainer
                                     _ -> undefined))
121 72747d91 Iustin Pop
            , ("default_hypervisor", def_hv)
122 5b11f8db Iustin Pop
            , ("enabled_hypervisors", showJSON hypervisors)
123 a2160e57 Iustin Pop
            , ("hvparams", showJSON $ clusterHvparams cluster)
124 a2160e57 Iustin Pop
            , ("os_hvp", showJSON $ clusterOsHvp cluster)
125 25b54de0 Iustin Pop
            , ("beparams", showJSON $ clusterBeparams cluster)
126 25b54de0 Iustin Pop
            , ("osparams", showJSON $ clusterOsparams cluster)
127 25b54de0 Iustin Pop
            , ("ipolicy", showJSON $ clusterIpolicy cluster)
128 25b54de0 Iustin Pop
            , ("nicparams", showJSON $ clusterNicparams cluster)
129 25b54de0 Iustin Pop
            , ("ndparams", showJSON $ clusterNdparams cluster)
130 a2160e57 Iustin Pop
            , ("diskparams", showJSON $ clusterDiskparams cluster)
131 25b54de0 Iustin Pop
            , ("candidate_pool_size",
132 25b54de0 Iustin Pop
               showJSON $ clusterCandidatePoolSize cluster)
133 178ad717 Klaus Aehlig
            , ("max_running_jobs",
134 178ad717 Klaus Aehlig
               showJSON $ clusterMaxRunningJobs cluster)
135 25b54de0 Iustin Pop
            , ("master_netdev",  showJSON $ clusterMasterNetdev cluster)
136 25b54de0 Iustin Pop
            , ("master_netmask", showJSON $ clusterMasterNetmask cluster)
137 25b54de0 Iustin Pop
            , ("use_external_mip_script",
138 25b54de0 Iustin Pop
               showJSON $ clusterUseExternalMipScript cluster)
139 64b0309a Dimitris Aragiorgis
            , ("volume_group_name",
140 64b0309a Dimitris Aragiorgis
               maybe JSNull showJSON (clusterVolumeGroupName cluster))
141 25b54de0 Iustin Pop
            , ("drbd_usermode_helper",
142 25b54de0 Iustin Pop
               maybe JSNull showJSON (clusterDrbdUsermodeHelper cluster))
143 25b54de0 Iustin Pop
            , ("file_storage_dir", showJSON $ clusterFileStorageDir cluster)
144 25b54de0 Iustin Pop
            , ("shared_file_storage_dir",
145 25b54de0 Iustin Pop
               showJSON $ clusterSharedFileStorageDir cluster)
146 d3e6fd0e Santi Raffa
            , ("gluster_storage_dir",
147 d3e6fd0e Santi Raffa
               showJSON $ clusterGlusterStorageDir cluster)
148 25b54de0 Iustin Pop
            , ("maintain_node_health",
149 25b54de0 Iustin Pop
               showJSON $ clusterMaintainNodeHealth cluster)
150 25b54de0 Iustin Pop
            , ("ctime", showJSON $ clusterCtime cluster)
151 25b54de0 Iustin Pop
            , ("mtime", showJSON $ clusterMtime cluster)
152 25b54de0 Iustin Pop
            , ("uuid", showJSON $ clusterUuid cluster)
153 25b54de0 Iustin Pop
            , ("tags", showJSON $ clusterTags cluster)
154 25b54de0 Iustin Pop
            , ("uid_pool", showJSON $ clusterUidPool cluster)
155 25b54de0 Iustin Pop
            , ("default_iallocator",
156 25b54de0 Iustin Pop
               showJSON $ clusterDefaultIallocator cluster)
157 0359e5d0 Spyros Trigazis
            , ("default_iallocator_params",
158 0359e5d0 Spyros Trigazis
              showJSON $ clusterDefaultIallocatorParams cluster)
159 25b54de0 Iustin Pop
            , ("reserved_lvs", showJSON $ clusterReservedLvs cluster)
160 25b54de0 Iustin Pop
            , ("primary_ip_version",
161 25b54de0 Iustin Pop
               showJSON . ipFamilyToVersion $ clusterPrimaryIpFamily cluster)
162 7b9ceea7 Helga Velroyen
            , ("prealloc_wipe_disks",
163 7b9ceea7 Helga Velroyen
               showJSON $ clusterPreallocWipeDisks cluster)
164 7b9ceea7 Helga Velroyen
            , ("hidden_os", showJSON $ clusterHiddenOs cluster)
165 7b9ceea7 Helga Velroyen
            , ("blacklisted_os", showJSON $ clusterBlacklistedOs cluster)
166 966e1580 Helga Velroyen
            , ("enabled_disk_templates", showJSON diskTemplates)
167 25b54de0 Iustin Pop
            ]
168 25b54de0 Iustin Pop
169 1c3231aa Thomas Thrainer
  in case master of
170 1c3231aa Thomas Thrainer
    Ok _ -> return . Ok . J.makeObj $ obj
171 1c3231aa Thomas Thrainer
    Bad ex -> return $ Bad ex
172 25b54de0 Iustin Pop
173 b5fa2700 Klaus Aehlig
handleCall _ _ cfg (QueryTags kind name) = do
174 f2374060 Iustin Pop
  let tags = case kind of
175 6e94b75c Jose A. Lopes
               TagKindCluster  -> Ok . clusterTags $ configCluster cfg
176 e10c4a69 Hrvoje Ribicic
               TagKindGroup    -> groupTags   <$> Config.getGroup    cfg name
177 e10c4a69 Hrvoje Ribicic
               TagKindNode     -> nodeTags    <$> Config.getNode     cfg name
178 e10c4a69 Hrvoje Ribicic
               TagKindInstance -> instTags    <$> Config.getInstance cfg name
179 e10c4a69 Hrvoje Ribicic
               TagKindNetwork  -> networkTags <$> Config.getNetwork  cfg name
180 6e94b75c Jose A. Lopes
  return (J.showJSON <$> tags)
181 f2374060 Iustin Pop
182 b5fa2700 Klaus Aehlig
handleCall _ _ cfg (Query qkind qfields qfilter) = do
183 fa2c927c Agata Murawska
  result <- query cfg True (Qlang.Query qkind qfields qfilter)
184 4cbe9bda Iustin Pop
  return $ J.showJSON <$> result
185 4cbe9bda Iustin Pop
186 b5fa2700 Klaus Aehlig
handleCall _ _ _ (QueryFields qkind qfields) = do
187 518023a9 Iustin Pop
  let result = queryFields (Qlang.QueryFields qkind qfields)
188 518023a9 Iustin Pop
  return $ J.showJSON <$> result
189 518023a9 Iustin Pop
190 b5fa2700 Klaus Aehlig
handleCall _ _ cfg (QueryNodes names fields lock) =
191 037762a9 Iustin Pop
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRNode)
192 c4e0d065 Klaus Aehlig
    (map Left names) fields lock
193 cd67e337 Iustin Pop
194 b5fa2700 Klaus Aehlig
handleCall _ _ cfg (QueryInstances names fields lock) =
195 89352544 Helga Velroyen
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRInstance)
196 89352544 Helga Velroyen
    (map Left names) fields lock
197 89352544 Helga Velroyen
198 b5fa2700 Klaus Aehlig
handleCall _ _ cfg (QueryGroups names fields lock) =
199 037762a9 Iustin Pop
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRGroup)
200 c4e0d065 Klaus Aehlig
    (map Left names) fields lock
201 cd67e337 Iustin Pop
202 b5fa2700 Klaus Aehlig
handleCall _ _ cfg (QueryJobs names fields) =
203 a7e484c4 Iustin Pop
  handleClassicQuery cfg (Qlang.ItemTypeLuxi Qlang.QRJob)
204 c4e0d065 Klaus Aehlig
    (map (Right . fromIntegral . fromJobId) names)  fields False
205 a7e484c4 Iustin Pop
206 b5fa2700 Klaus Aehlig
handleCall _ _ cfg (QueryNetworks names fields lock) =
207 795d035d Klaus Aehlig
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRNetwork)
208 795d035d Klaus Aehlig
    (map Left names) fields lock
209 795d035d Klaus Aehlig
210 be7531a9 Klaus Aehlig
handleCall _ _ cfg (QueryConfigValues fields) = do
211 be7531a9 Klaus Aehlig
  let params = [ ("cluster_name", return . showJSON . clusterClusterName
212 be7531a9 Klaus Aehlig
                                    . configCluster $ cfg)
213 be7531a9 Klaus Aehlig
               , ("watcher_pause", liftM (maybe JSNull showJSON)
214 be7531a9 Klaus Aehlig
                                     QCluster.isWatcherPaused)
215 be7531a9 Klaus Aehlig
               , ("master_node", return . genericResult (const JSNull) showJSON
216 be7531a9 Klaus Aehlig
                                   $ QCluster.clusterMasterNodeName cfg)
217 1264bd58 Klaus Aehlig
               , ("drain_flag", liftM (showJSON . not) isQueueOpen)
218 be7531a9 Klaus Aehlig
               ] :: [(String, IO JSValue)]
219 be7531a9 Klaus Aehlig
  let answer = map (fromMaybe (return JSNull) . flip lookup params) fields
220 be7531a9 Klaus Aehlig
  answerEval <- sequence answer
221 be7531a9 Klaus Aehlig
  return . Ok . showJSON $ answerEval
222 be7531a9 Klaus Aehlig
223 b5fa2700 Klaus Aehlig
handleCall qlock qstat cfg (SubmitJobToDrainedQueue ops) =
224 e5fba493 Klaus Aehlig
  do
225 f5b765f0 Klaus Aehlig
    let mcs = Config.getMasterCandidates cfg
226 f5b765f0 Klaus Aehlig
    jobid <- allocateJobId mcs qlock
227 e5fba493 Klaus Aehlig
    case jobid of
228 e5fba493 Klaus Aehlig
      Bad s -> return . Bad . GenericError $ s
229 e5fba493 Klaus Aehlig
      Ok jid -> do
230 c6013594 Klaus Aehlig
        ts <- currentTimestamp
231 c6013594 Klaus Aehlig
        job <- liftM (setReceivedTimestamp ts)
232 c6013594 Klaus Aehlig
                 $ queuedJobFromOpCodes jid ops
233 e5fba493 Klaus Aehlig
        qDir <- queueDir
234 e5fba493 Klaus Aehlig
        write_result <- writeJobToDisk qDir job
235 e5fba493 Klaus Aehlig
        case write_result of
236 e5fba493 Klaus Aehlig
          Bad s -> return . Bad . GenericError $ s
237 e5fba493 Klaus Aehlig
          Ok () -> do
238 f5b765f0 Klaus Aehlig
            _ <- replicateManyJobs qDir mcs [job]
239 b5fa2700 Klaus Aehlig
            _ <- forkIO $ enqueueNewJobs qstat [job]
240 e5fba493 Klaus Aehlig
            return . Ok . showJSON . fromJobId $ jid
241 e5fba493 Klaus Aehlig
242 b5fa2700 Klaus Aehlig
handleCall qlock qstat cfg (SubmitJob ops) =
243 e5fba493 Klaus Aehlig
  do
244 e5fba493 Klaus Aehlig
    open <- isQueueOpen
245 e5fba493 Klaus Aehlig
    if not open
246 e5fba493 Klaus Aehlig
       then return . Bad . GenericError $ "Queue drained"
247 b5fa2700 Klaus Aehlig
       else handleCall qlock qstat cfg (SubmitJobToDrainedQueue ops)
248 e5fba493 Klaus Aehlig
249 b5fa2700 Klaus Aehlig
handleCall qlock qstat cfg (SubmitManyJobs lops) =
250 94d6d0a3 Klaus Aehlig
  do
251 94d6d0a3 Klaus Aehlig
    open <- isQueueOpen
252 94d6d0a3 Klaus Aehlig
    if not open
253 94d6d0a3 Klaus Aehlig
      then return . Bad . GenericError $ "Queue drained"
254 94d6d0a3 Klaus Aehlig
      else do
255 f5b765f0 Klaus Aehlig
        let mcs = Config.getMasterCandidates cfg
256 f5b765f0 Klaus Aehlig
        result_jobids <- allocateJobIds mcs qlock (length lops)
257 94d6d0a3 Klaus Aehlig
        case result_jobids of
258 94d6d0a3 Klaus Aehlig
          Bad s -> return . Bad . GenericError $ s
259 94d6d0a3 Klaus Aehlig
          Ok jids -> do
260 c6013594 Klaus Aehlig
            ts <- currentTimestamp
261 c6013594 Klaus Aehlig
            jobs <- liftM (map $ setReceivedTimestamp ts)
262 c6013594 Klaus Aehlig
                      $ zipWithM queuedJobFromOpCodes jids lops
263 94d6d0a3 Klaus Aehlig
            qDir <- queueDir
264 94d6d0a3 Klaus Aehlig
            write_results <- mapM (writeJobToDisk qDir) jobs
265 f5b765f0 Klaus Aehlig
            let annotated_results = zip write_results jobs
266 94d6d0a3 Klaus Aehlig
                succeeded = map snd $ filter (isOk . fst) annotated_results
267 94d6d0a3 Klaus Aehlig
            when (any isBad write_results) . logWarning
268 94d6d0a3 Klaus Aehlig
              $ "Writing some jobs failed " ++ show annotated_results
269 f5b765f0 Klaus Aehlig
            replicateManyJobs qDir mcs succeeded
270 b5fa2700 Klaus Aehlig
            _ <- forkIO $ enqueueNewJobs qstat succeeded
271 94d6d0a3 Klaus Aehlig
            return . Ok . JSArray
272 f5b765f0 Klaus Aehlig
              . map (\(res, job) ->
273 94d6d0a3 Klaus Aehlig
                      if isOk res
274 f5b765f0 Klaus Aehlig
                        then showJSON (True, fromJobId $ qjId job)
275 94d6d0a3 Klaus Aehlig
                        else showJSON (False, genericResult id (const "") res))
276 94d6d0a3 Klaus Aehlig
              $ annotated_results
277 229da00f Petr Pudlak
278 6222b3a3 Klaus Aehlig
handleCall _ _ cfg (WaitForJobChange jid fields prev_job prev_log tmout) = do
279 9131274c Jose A. Lopes
  let compute_fn = computeJobUpdate cfg jid fields prev_log
280 6222b3a3 Klaus Aehlig
  qDir <- queueDir
281 6222b3a3 Klaus Aehlig
  -- verify if the job is finalized, and return immediately in this case
282 6222b3a3 Klaus Aehlig
  jobresult <- loadJobFromDisk qDir False jid
283 6222b3a3 Klaus Aehlig
  case jobresult of
284 6222b3a3 Klaus Aehlig
    Ok (job, _) | not (jobFinalized job) -> do
285 6222b3a3 Klaus Aehlig
      let jobfile = liveJobFile qDir jid
286 6222b3a3 Klaus Aehlig
      answer <- watchFile jobfile (min tmout C.luxiWfjcTimeout)
287 6222b3a3 Klaus Aehlig
                  (prev_job, JSArray []) compute_fn
288 6222b3a3 Klaus Aehlig
      return . Ok $ showJSON answer
289 6222b3a3 Klaus Aehlig
    _ -> liftM (Ok . showJSON) compute_fn
290 6222b3a3 Klaus Aehlig
291 946f1fb3 Klaus Aehlig
handleCall _ _ cfg (SetWatcherPause time) = do
292 946f1fb3 Klaus Aehlig
  let mcs = Config.getMasterCandidates cfg
293 946f1fb3 Klaus Aehlig
      masters = genericResult (const []) return
294 946f1fb3 Klaus Aehlig
                  . Config.getNode cfg . clusterMasterNode
295 946f1fb3 Klaus Aehlig
                  $ configCluster cfg
296 946f1fb3 Klaus Aehlig
  _ <- executeRpcCall (masters ++ mcs) $ RpcCallSetWatcherPause time
297 946f1fb3 Klaus Aehlig
  return . Ok . maybe JSNull showJSON $ time
298 946f1fb3 Klaus Aehlig
299 d5665e10 Klaus Aehlig
handleCall _ _ cfg (SetDrainFlag value) = do
300 d5665e10 Klaus Aehlig
  let mcs = Config.getMasterCandidates cfg
301 d5665e10 Klaus Aehlig
  fpath <- jobQueueDrainFile
302 d5665e10 Klaus Aehlig
  if value
303 d5665e10 Klaus Aehlig
     then writeFile fpath ""
304 d5665e10 Klaus Aehlig
     else removeFile fpath
305 d5665e10 Klaus Aehlig
  _ <- executeRpcCall mcs $ RpcCallSetDrainFlag value
306 d5665e10 Klaus Aehlig
  return . Ok . showJSON $ True
307 d5665e10 Klaus Aehlig
308 7711f32b Klaus Aehlig
handleCall _ qstat cfg (ChangeJobPriority jid prio) = do
309 7711f32b Klaus Aehlig
  maybeJob <- setJobPriority qstat jid prio
310 7711f32b Klaus Aehlig
  case maybeJob of
311 7711f32b Klaus Aehlig
    Bad s -> return . Ok $ showJSON (False, s)
312 7711f32b Klaus Aehlig
    Ok (Just job) -> runResultT $ do
313 7711f32b Klaus Aehlig
      let mcs = Config.getMasterCandidates cfg
314 7711f32b Klaus Aehlig
      qDir <- liftIO queueDir
315 7711f32b Klaus Aehlig
      liftIO $ replicateManyJobs qDir mcs [job]
316 7711f32b Klaus Aehlig
      return $ showJSON (True, "Priorities of pending opcodes for job "
317 7711f32b Klaus Aehlig
                               ++ show (fromJobId jid) ++ " have been changed"
318 7711f32b Klaus Aehlig
                               ++ " to " ++ show prio)
319 7711f32b Klaus Aehlig
    Ok Nothing -> runResultT $ do
320 7711f32b Klaus Aehlig
      -- Job has already started; so we have to forward the request
321 7711f32b Klaus Aehlig
      -- to the job, currently handled by masterd.
322 7711f32b Klaus Aehlig
      socketpath <- liftIO defaultMasterSocket
323 7711f32b Klaus Aehlig
      cl <- liftIO $ getLuxiClient socketpath
324 7711f32b Klaus Aehlig
      ResultT $ callMethod (ChangeJobPriority jid prio) cl
325 7711f32b Klaus Aehlig
326 36cb6837 Klaus Aehlig
handleCall _ qstat  cfg (CancelJob jid) = do
327 36cb6837 Klaus Aehlig
  let jName = (++) "job " . show $ fromJobId jid
328 36cb6837 Klaus Aehlig
  dequeueResult <- dequeueJob qstat jid
329 36cb6837 Klaus Aehlig
  case dequeueResult of
330 36cb6837 Klaus Aehlig
    Ok True -> do
331 36cb6837 Klaus Aehlig
      logDebug $ jName ++ " dequeued, marking as canceled"
332 36cb6837 Klaus Aehlig
      qDir <- queueDir
333 36cb6837 Klaus Aehlig
      readResult <- loadJobFromDisk qDir True jid
334 36cb6837 Klaus Aehlig
      let jobFileFailed = return . Ok . showJSON . (,) False
335 36cb6837 Klaus Aehlig
                            . (++) ("Dequeued " ++ jName
336 36cb6837 Klaus Aehlig
                                    ++ ", but failed to mark as cancelled: ")
337 36cb6837 Klaus Aehlig
                          :: String -> IO (ErrorResult JSValue)
338 36cb6837 Klaus Aehlig
      case readResult of
339 36cb6837 Klaus Aehlig
        Bad s -> jobFileFailed s
340 36cb6837 Klaus Aehlig
        Ok (job, _) -> do
341 36cb6837 Klaus Aehlig
          now <- currentTimestamp
342 36cb6837 Klaus Aehlig
          let job' = cancelQueuedJob now job
343 36cb6837 Klaus Aehlig
              mcs = Config.getMasterCandidates cfg
344 36cb6837 Klaus Aehlig
          write_result <- writeJobToDisk qDir job'
345 36cb6837 Klaus Aehlig
          case write_result of
346 36cb6837 Klaus Aehlig
            Bad s -> jobFileFailed s
347 36cb6837 Klaus Aehlig
            Ok () -> do
348 36cb6837 Klaus Aehlig
              replicateManyJobs qDir mcs [job']
349 36cb6837 Klaus Aehlig
              return . Ok . showJSON $ (True, "Dequeued " ++ jName)
350 36cb6837 Klaus Aehlig
    Ok False -> do
351 36cb6837 Klaus Aehlig
      logDebug $ jName ++ " not queued; trying to cancel directly"
352 36cb6837 Klaus Aehlig
      cancelJob jid
353 36cb6837 Klaus Aehlig
    Bad s -> return . Ok . showJSON $ (False, s)
354 36cb6837 Klaus Aehlig
355 6fdc84ab Klaus Aehlig
handleCall qlock _ cfg (ArchiveJob jid) = do
356 6fdc84ab Klaus Aehlig
  let archiveFailed = putMVar qlock  () >> (return . Ok $ showJSON False)
357 6fdc84ab Klaus Aehlig
                      :: IO (ErrorResult JSValue)
358 6fdc84ab Klaus Aehlig
  qDir <- queueDir
359 6fdc84ab Klaus Aehlig
  takeMVar qlock
360 6fdc84ab Klaus Aehlig
  result <- loadJobFromDisk qDir False jid
361 6fdc84ab Klaus Aehlig
  case result of
362 6fdc84ab Klaus Aehlig
    Bad _ -> archiveFailed
363 6fdc84ab Klaus Aehlig
    Ok (job, _) -> if jobFinalized job
364 6fdc84ab Klaus Aehlig
                     then do
365 6fdc84ab Klaus Aehlig
                       let mcs = Config.getMasterCandidates cfg
366 6fdc84ab Klaus Aehlig
                           live = liveJobFile qDir jid
367 6fdc84ab Klaus Aehlig
                           archive = archivedJobFile qDir jid
368 0c09ecc2 Klaus Aehlig
                       renameResult <- safeRenameFile queueDirPermissions
369 0c09ecc2 Klaus Aehlig
                                         live archive
370 6fdc84ab Klaus Aehlig
                       putMVar qlock ()
371 6fdc84ab Klaus Aehlig
                       case renameResult of
372 857cbfb1 Klaus Aehlig
                         Bad s -> return . Bad . JobQueueError
373 857cbfb1 Klaus Aehlig
                                    $ "Archiving failed in an unexpected way: "
374 857cbfb1 Klaus Aehlig
                                        ++ s
375 857cbfb1 Klaus Aehlig
                         Ok () -> do
376 6fdc84ab Klaus Aehlig
                           _ <- executeRpcCall mcs
377 6fdc84ab Klaus Aehlig
                                  $ RpcCallJobqueueRename [(live, archive)]
378 6fadcbab Klaus Aehlig
                           return . Ok $ showJSON True
379 6fdc84ab Klaus Aehlig
                     else archiveFailed
380 6fdc84ab Klaus Aehlig
381 658eb2dc Klaus Aehlig
handleCall qlock _ cfg (AutoArchiveJobs age timeout) = do
382 658eb2dc Klaus Aehlig
  qDir <- queueDir
383 658eb2dc Klaus Aehlig
  eitherJids <- getJobIDs [qDir]
384 658eb2dc Klaus Aehlig
  case eitherJids of
385 658eb2dc Klaus Aehlig
    Left s -> return . Bad . JobQueueError $ show s
386 658eb2dc Klaus Aehlig
    Right jids -> do
387 658eb2dc Klaus Aehlig
      result <- bracket_ (takeMVar qlock) (putMVar qlock ())
388 658eb2dc Klaus Aehlig
                  . archiveJobs cfg age timeout
389 658eb2dc Klaus Aehlig
                  $ sortJobIDs jids
390 658eb2dc Klaus Aehlig
      return . Ok $ showJSON result
391 658eb2dc Klaus Aehlig
392 b5fa2700 Klaus Aehlig
handleCall _ _ _ op =
393 5183e8be Iustin Pop
  return . Bad $
394 5183e8be Iustin Pop
    GenericError ("Luxi call '" ++ strOfOp op ++ "' not implemented")
395 25b54de0 Iustin Pop
396 edcad688 Petr Pudlak
{-# ANN handleCall "HLint: ignore Too strict if" #-}
397 edcad688 Petr Pudlak
398 6222b3a3 Klaus Aehlig
-- | Query the status of a job and return the requested fields
399 6222b3a3 Klaus Aehlig
-- and the logs newer than the given log number.
400 9131274c Jose A. Lopes
computeJobUpdate :: ConfigData -> JobId -> [String] -> JSValue
401 6222b3a3 Klaus Aehlig
                    -> IO (JSValue, JSValue)
402 6222b3a3 Klaus Aehlig
computeJobUpdate cfg jid fields prev_log = do
403 6222b3a3 Klaus Aehlig
  let sjid = show $ fromJobId jid
404 6222b3a3 Klaus Aehlig
  logDebug $ "Inspecting fields " ++ show fields ++ " of job " ++ sjid
405 6222b3a3 Klaus Aehlig
  let fromJSArray (JSArray xs) = xs
406 6222b3a3 Klaus Aehlig
      fromJSArray _ = []
407 6222b3a3 Klaus Aehlig
  let logFilter JSNull (JSArray _) = True
408 6222b3a3 Klaus Aehlig
      logFilter (JSRational _ n) (JSArray (JSRational _ m:_)) = n < m
409 6222b3a3 Klaus Aehlig
      logFilter _ _ = False
410 6222b3a3 Klaus Aehlig
  let filterLogs n logs = JSArray (filter (logFilter n) (logs >>= fromJSArray))
411 6222b3a3 Klaus Aehlig
  jobQuery <- handleClassicQuery cfg (Qlang.ItemTypeLuxi Qlang.QRJob)
412 6222b3a3 Klaus Aehlig
                [Right . fromIntegral $ fromJobId jid] ("oplog" : fields) False
413 6222b3a3 Klaus Aehlig
  let (rfields, rlogs) = case jobQuery of
414 6222b3a3 Klaus Aehlig
        Ok (JSArray [JSArray (JSArray logs : answer)]) ->
415 6222b3a3 Klaus Aehlig
          (answer, filterLogs prev_log logs)
416 6222b3a3 Klaus Aehlig
        _ -> (map (const JSNull) fields, JSArray [])
417 6222b3a3 Klaus Aehlig
  logDebug $ "Updates for job " ++ sjid ++ " are " ++ encode (rfields, rlogs)
418 6222b3a3 Klaus Aehlig
  return (JSArray rfields, rlogs)
419 6222b3a3 Klaus Aehlig
420 d79a6502 Petr Pudlak
421 d79a6502 Petr Pudlak
type LuxiConfig = (MVar (), JQStatus, ConfigReader)
422 d79a6502 Petr Pudlak
423 d79a6502 Petr Pudlak
luxiExec
424 d79a6502 Petr Pudlak
    :: LuxiConfig
425 d79a6502 Petr Pudlak
    -> LuxiOp
426 d79a6502 Petr Pudlak
    -> IO (Bool, GenericResult GanetiException JSValue)
427 d79a6502 Petr Pudlak
luxiExec (qlock, qstat, creader) args = do
428 25b54de0 Iustin Pop
  cfg <- creader
429 d79a6502 Petr Pudlak
  result <- handleCallWrapper qlock qstat cfg args
430 d79a6502 Petr Pudlak
  return (True, result)
431 d79a6502 Petr Pudlak
432 d79a6502 Petr Pudlak
luxiHandler :: LuxiConfig -> U.Handler LuxiOp JSValue
433 d79a6502 Petr Pudlak
luxiHandler cfg = U.Handler { U.hParse         = decodeLuxiCall
434 d79a6502 Petr Pudlak
                            , U.hInputLogShort = strOfOp
435 d79a6502 Petr Pudlak
                            , U.hInputLogLong  = show
436 d79a6502 Petr Pudlak
                            , U.hExec          = luxiExec cfg
437 d79a6502 Petr Pudlak
                            }
438 d79a6502 Petr Pudlak
439 670e954a Thomas Thrainer
-- | Type alias for prepMain results
440 5e671e0e Petr Pudlak
type PrepResult = (Server, IORef (Result ConfigData), JQStatus)
441 25b54de0 Iustin Pop
442 3695a4e0 Thomas Thrainer
-- | Check function for luxid.
443 670e954a Thomas Thrainer
checkMain :: CheckFn ()
444 670e954a Thomas Thrainer
checkMain _ = return $ Right ()
445 670e954a Thomas Thrainer
446 3695a4e0 Thomas Thrainer
-- | Prepare function for luxid.
447 670e954a Thomas Thrainer
prepMain :: PrepFn () PrepResult
448 670e954a Thomas Thrainer
prepMain _ _ = do
449 670e954a Thomas Thrainer
  socket_path <- Path.defaultQuerySocket
450 0d0ac025 Iustin Pop
  cleanupSocket socket_path
451 73b16ca1 Iustin Pop
  s <- describeError "binding to the Luxi socket"
452 d605e261 Petr Pudlak
         Nothing (Just socket_path) $ getLuxiServer True socket_path
453 670e954a Thomas Thrainer
  cref <- newIORef (Bad "Configuration not yet loaded")
454 6046dca9 Klaus Aehlig
  jq <- emptyJQStatus cref
455 5e671e0e Petr Pudlak
  return (s, cref, jq)
456 670e954a Thomas Thrainer
457 670e954a Thomas Thrainer
-- | Main function.
458 670e954a Thomas Thrainer
main :: MainFn () PrepResult
459 5e671e0e Petr Pudlak
main _ _ (server, cref, jq) = do
460 670e954a Thomas Thrainer
  initConfigReader id cref
461 670e954a Thomas Thrainer
  let creader = readIORef cref
462 b5fa2700 Klaus Aehlig
  initJQScheduler jq
463 9131274c Jose A. Lopes
464 e5fba493 Klaus Aehlig
  qlockFile <- jobQueueLockFile
465 e5fba493 Klaus Aehlig
  lockFile qlockFile >>= exitIfBad "Failed to obtain the job-queue lock"
466 e5fba493 Klaus Aehlig
  qlock <- newMVar ()
467 4c3f55b8 Iustin Pop
468 4c3f55b8 Iustin Pop
  finally
469 c7003a76 Petr Pudlak
    (forever $ U.listener (luxiHandler (qlock, jq, creader)) server)
470 5e671e0e Petr Pudlak
    (closeServer server)