Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Server.hs @ d605e261

History | View | Annotate | Download (15.8 kB)

1 25b54de0 Iustin Pop
{-# LANGUAGE BangPatterns #-}
2 25b54de0 Iustin Pop
3 d120506c Agata Murawska
{-| Implementation of the Ganeti Query2 server.
4 25b54de0 Iustin Pop
5 25b54de0 Iustin Pop
-}
6 25b54de0 Iustin Pop
7 25b54de0 Iustin Pop
{-
8 25b54de0 Iustin Pop
9 72747d91 Iustin Pop
Copyright (C) 2012, 2013 Google Inc.
10 25b54de0 Iustin Pop
11 25b54de0 Iustin Pop
This program is free software; you can redistribute it and/or modify
12 25b54de0 Iustin Pop
it under the terms of the GNU General Public License as published by
13 25b54de0 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 25b54de0 Iustin Pop
(at your option) any later version.
15 25b54de0 Iustin Pop
16 25b54de0 Iustin Pop
This program is distributed in the hope that it will be useful, but
17 25b54de0 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 25b54de0 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 25b54de0 Iustin Pop
General Public License for more details.
20 25b54de0 Iustin Pop
21 25b54de0 Iustin Pop
You should have received a copy of the GNU General Public License
22 25b54de0 Iustin Pop
along with this program; if not, write to the Free Software
23 25b54de0 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 25b54de0 Iustin Pop
02110-1301, USA.
25 25b54de0 Iustin Pop
26 25b54de0 Iustin Pop
-}
27 25b54de0 Iustin Pop
28 4cab6703 Iustin Pop
module Ganeti.Query.Server
29 670e954a Thomas Thrainer
  ( main
30 670e954a Thomas Thrainer
  , checkMain
31 670e954a Thomas Thrainer
  , prepMain
32 0d0ac025 Iustin Pop
  ) where
33 25b54de0 Iustin Pop
34 f2374060 Iustin Pop
import Control.Applicative
35 25b54de0 Iustin Pop
import Control.Concurrent
36 25b54de0 Iustin Pop
import Control.Exception
37 c6013594 Klaus Aehlig
import Control.Monad (forever, when, zipWithM, liftM)
38 25b54de0 Iustin Pop
import Data.Bits (bitSize)
39 c87997d2 Jose A. Lopes
import qualified Data.Set as Set (toList)
40 670e954a Thomas Thrainer
import Data.IORef
41 25b54de0 Iustin Pop
import qualified Network.Socket as S
42 25b54de0 Iustin Pop
import qualified Text.JSON as J
43 6222b3a3 Klaus Aehlig
import Text.JSON (encode, showJSON, JSValue(..))
44 25b54de0 Iustin Pop
import System.Info (arch)
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 f5b765f0 Klaus Aehlig
import Ganeti.Path (queueDir, jobQueueLockFile)
62 4cbe9bda Iustin Pop
import Ganeti.Query.Query
63 c4e0d065 Klaus Aehlig
import Ganeti.Query.Filter (makeSimpleFilter)
64 6e94b75c Jose A. Lopes
import Ganeti.Types
65 6222b3a3 Klaus Aehlig
import Ganeti.Utils (lockFile, exitIfBad, watchFile)
66 3cb9bd38 Jose A. Lopes
import qualified Ganeti.Version as Version
67 25b54de0 Iustin Pop
68 cd67e337 Iustin Pop
-- | Helper for classic queries.
69 cd67e337 Iustin Pop
handleClassicQuery :: ConfigData      -- ^ Cluster config
70 cd67e337 Iustin Pop
                   -> Qlang.ItemType  -- ^ Query type
71 037762a9 Iustin Pop
                   -> [Either String Integer] -- ^ Requested names
72 037762a9 Iustin Pop
                                              -- (empty means all)
73 cd67e337 Iustin Pop
                   -> [String]        -- ^ Requested fields
74 cd67e337 Iustin Pop
                   -> Bool            -- ^ Whether to do sync queries or not
75 5183e8be Iustin Pop
                   -> IO (GenericResult GanetiException JSValue)
76 c4e0d065 Klaus Aehlig
handleClassicQuery _ _ _ _ True =
77 5183e8be Iustin Pop
  return . Bad $ OpPrereqError "Sync queries are not allowed" ECodeInval
78 c4e0d065 Klaus Aehlig
handleClassicQuery cfg qkind names fields _ = do
79 c4e0d065 Klaus Aehlig
  let flt = makeSimpleFilter (nameField qkind) names
80 cd67e337 Iustin Pop
  qr <- query cfg True (Qlang.Query qkind fields flt)
81 cd67e337 Iustin Pop
  return $ showJSON <$> (qr >>= queryCompat)
82 cd67e337 Iustin Pop
83 25b54de0 Iustin Pop
-- | Minimal wrapper to handle the missing config case.
84 b5fa2700 Klaus Aehlig
handleCallWrapper :: MVar () -> JQStatus ->  Result ConfigData 
85 e5fba493 Klaus Aehlig
                     -> LuxiOp -> IO (ErrorResult JSValue)
86 b5fa2700 Klaus Aehlig
handleCallWrapper _ _ (Bad msg) _ =
87 5183e8be Iustin Pop
  return . Bad . ConfigurationError $
88 5183e8be Iustin Pop
           "I do not have access to a valid configuration, cannot\
89 5183e8be Iustin Pop
           \ process queries: " ++ msg
90 b5fa2700 Klaus Aehlig
handleCallWrapper qlock qstat (Ok config) op = handleCall qlock qstat config op
91 25b54de0 Iustin Pop
92 25b54de0 Iustin Pop
-- | Actual luxi operation handler.
93 b5fa2700 Klaus Aehlig
handleCall :: MVar () -> JQStatus 
94 b5fa2700 Klaus Aehlig
              -> ConfigData -> LuxiOp -> IO (ErrorResult JSValue)
95 b5fa2700 Klaus Aehlig
handleCall _ _ cdata QueryClusterInfo =
96 25b54de0 Iustin Pop
  let cluster = configCluster cdata
97 1c3231aa Thomas Thrainer
      master = QCluster.clusterMasterNodeName cdata
98 25b54de0 Iustin Pop
      hypervisors = clusterEnabledHypervisors cluster
99 966e1580 Helga Velroyen
      diskTemplates = clusterEnabledDiskTemplates cluster
100 72747d91 Iustin Pop
      def_hv = case hypervisors of
101 72747d91 Iustin Pop
                 x:_ -> showJSON x
102 72747d91 Iustin Pop
                 [] -> JSNull
103 25b54de0 Iustin Pop
      bits = show (bitSize (0::Int)) ++ "bits"
104 25b54de0 Iustin Pop
      arch_tuple = [bits, arch]
105 5b11f8db Iustin Pop
      obj = [ ("software_version", showJSON C.releaseVersion)
106 5b11f8db Iustin Pop
            , ("protocol_version", showJSON C.protocolVersion)
107 5b11f8db Iustin Pop
            , ("config_version", showJSON C.configVersion)
108 c87997d2 Jose A. Lopes
            , ("os_api_version", showJSON . maximum .
109 c87997d2 Jose A. Lopes
                                 Set.toList . ConstantUtils.unFrozenSet $
110 c87997d2 Jose A. Lopes
                                 C.osApiVersions)
111 5b11f8db Iustin Pop
            , ("export_version", showJSON C.exportVersion)
112 3cb9bd38 Jose A. Lopes
            , ("vcs_version", showJSON Version.version)
113 5b11f8db Iustin Pop
            , ("architecture", showJSON arch_tuple)
114 25b54de0 Iustin Pop
            , ("name", showJSON $ clusterClusterName cluster)
115 1c3231aa Thomas Thrainer
            , ("master", showJSON (case master of
116 1c3231aa Thomas Thrainer
                                     Ok name -> name
117 1c3231aa Thomas Thrainer
                                     _ -> undefined))
118 72747d91 Iustin Pop
            , ("default_hypervisor", def_hv)
119 5b11f8db Iustin Pop
            , ("enabled_hypervisors", showJSON hypervisors)
120 a2160e57 Iustin Pop
            , ("hvparams", showJSON $ clusterHvparams cluster)
121 a2160e57 Iustin Pop
            , ("os_hvp", showJSON $ clusterOsHvp cluster)
122 25b54de0 Iustin Pop
            , ("beparams", showJSON $ clusterBeparams cluster)
123 25b54de0 Iustin Pop
            , ("osparams", showJSON $ clusterOsparams cluster)
124 25b54de0 Iustin Pop
            , ("ipolicy", showJSON $ clusterIpolicy cluster)
125 25b54de0 Iustin Pop
            , ("nicparams", showJSON $ clusterNicparams cluster)
126 25b54de0 Iustin Pop
            , ("ndparams", showJSON $ clusterNdparams cluster)
127 a2160e57 Iustin Pop
            , ("diskparams", showJSON $ clusterDiskparams cluster)
128 25b54de0 Iustin Pop
            , ("candidate_pool_size",
129 25b54de0 Iustin Pop
               showJSON $ clusterCandidatePoolSize cluster)
130 25b54de0 Iustin Pop
            , ("master_netdev",  showJSON $ clusterMasterNetdev cluster)
131 25b54de0 Iustin Pop
            , ("master_netmask", showJSON $ clusterMasterNetmask cluster)
132 25b54de0 Iustin Pop
            , ("use_external_mip_script",
133 25b54de0 Iustin Pop
               showJSON $ clusterUseExternalMipScript cluster)
134 64b0309a Dimitris Aragiorgis
            , ("volume_group_name",
135 64b0309a Dimitris Aragiorgis
               maybe JSNull showJSON (clusterVolumeGroupName cluster))
136 25b54de0 Iustin Pop
            , ("drbd_usermode_helper",
137 25b54de0 Iustin Pop
               maybe JSNull showJSON (clusterDrbdUsermodeHelper cluster))
138 25b54de0 Iustin Pop
            , ("file_storage_dir", showJSON $ clusterFileStorageDir cluster)
139 25b54de0 Iustin Pop
            , ("shared_file_storage_dir",
140 25b54de0 Iustin Pop
               showJSON $ clusterSharedFileStorageDir cluster)
141 25b54de0 Iustin Pop
            , ("maintain_node_health",
142 25b54de0 Iustin Pop
               showJSON $ clusterMaintainNodeHealth cluster)
143 25b54de0 Iustin Pop
            , ("ctime", showJSON $ clusterCtime cluster)
144 25b54de0 Iustin Pop
            , ("mtime", showJSON $ clusterMtime cluster)
145 25b54de0 Iustin Pop
            , ("uuid", showJSON $ clusterUuid cluster)
146 25b54de0 Iustin Pop
            , ("tags", showJSON $ clusterTags cluster)
147 25b54de0 Iustin Pop
            , ("uid_pool", showJSON $ clusterUidPool cluster)
148 25b54de0 Iustin Pop
            , ("default_iallocator",
149 25b54de0 Iustin Pop
               showJSON $ clusterDefaultIallocator cluster)
150 0359e5d0 Spyros Trigazis
            , ("default_iallocator_params",
151 0359e5d0 Spyros Trigazis
              showJSON $ clusterDefaultIallocatorParams cluster)
152 25b54de0 Iustin Pop
            , ("reserved_lvs", showJSON $ clusterReservedLvs cluster)
153 25b54de0 Iustin Pop
            , ("primary_ip_version",
154 25b54de0 Iustin Pop
               showJSON . ipFamilyToVersion $ clusterPrimaryIpFamily cluster)
155 7b9ceea7 Helga Velroyen
            , ("prealloc_wipe_disks",
156 7b9ceea7 Helga Velroyen
               showJSON $ clusterPreallocWipeDisks cluster)
157 7b9ceea7 Helga Velroyen
            , ("hidden_os", showJSON $ clusterHiddenOs cluster)
158 7b9ceea7 Helga Velroyen
            , ("blacklisted_os", showJSON $ clusterBlacklistedOs cluster)
159 966e1580 Helga Velroyen
            , ("enabled_disk_templates", showJSON diskTemplates)
160 25b54de0 Iustin Pop
            ]
161 25b54de0 Iustin Pop
162 1c3231aa Thomas Thrainer
  in case master of
163 1c3231aa Thomas Thrainer
    Ok _ -> return . Ok . J.makeObj $ obj
164 1c3231aa Thomas Thrainer
    Bad ex -> return $ Bad ex
165 25b54de0 Iustin Pop
166 b5fa2700 Klaus Aehlig
handleCall _ _ cfg (QueryTags kind name) = do
167 f2374060 Iustin Pop
  let tags = case kind of
168 6e94b75c Jose A. Lopes
               TagKindCluster  -> Ok . clusterTags $ configCluster cfg
169 6e94b75c Jose A. Lopes
               TagKindGroup    -> groupTags <$> Config.getGroup    cfg name
170 6e94b75c Jose A. Lopes
               TagKindNode     -> nodeTags  <$> Config.getNode     cfg name
171 6e94b75c Jose A. Lopes
               TagKindInstance -> instTags  <$> Config.getInstance cfg name
172 a8633d70 Jose A. Lopes
               TagKindNetwork  -> Bad $ OpPrereqError
173 a8633d70 Jose A. Lopes
                                        "Network tag is not allowed"
174 a8633d70 Jose A. Lopes
                                        ECodeInval
175 6e94b75c Jose A. Lopes
  return (J.showJSON <$> tags)
176 f2374060 Iustin Pop
177 b5fa2700 Klaus Aehlig
handleCall _ _ cfg (Query qkind qfields qfilter) = do
178 fa2c927c Agata Murawska
  result <- query cfg True (Qlang.Query qkind qfields qfilter)
179 4cbe9bda Iustin Pop
  return $ J.showJSON <$> result
180 4cbe9bda Iustin Pop
181 b5fa2700 Klaus Aehlig
handleCall _ _ _ (QueryFields qkind qfields) = do
182 518023a9 Iustin Pop
  let result = queryFields (Qlang.QueryFields qkind qfields)
183 518023a9 Iustin Pop
  return $ J.showJSON <$> result
184 518023a9 Iustin Pop
185 b5fa2700 Klaus Aehlig
handleCall _ _ cfg (QueryNodes names fields lock) =
186 037762a9 Iustin Pop
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRNode)
187 c4e0d065 Klaus Aehlig
    (map Left names) fields lock
188 cd67e337 Iustin Pop
189 b5fa2700 Klaus Aehlig
handleCall _ _ cfg (QueryInstances names fields lock) =
190 89352544 Helga Velroyen
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRInstance)
191 89352544 Helga Velroyen
    (map Left names) fields lock
192 89352544 Helga Velroyen
193 b5fa2700 Klaus Aehlig
handleCall _ _ cfg (QueryGroups names fields lock) =
194 037762a9 Iustin Pop
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRGroup)
195 c4e0d065 Klaus Aehlig
    (map Left names) fields lock
196 cd67e337 Iustin Pop
197 b5fa2700 Klaus Aehlig
handleCall _ _ cfg (QueryJobs names fields) =
198 a7e484c4 Iustin Pop
  handleClassicQuery cfg (Qlang.ItemTypeLuxi Qlang.QRJob)
199 c4e0d065 Klaus Aehlig
    (map (Right . fromIntegral . fromJobId) names)  fields False
200 a7e484c4 Iustin Pop
201 b5fa2700 Klaus Aehlig
handleCall _ _ cfg (QueryNetworks names fields lock) =
202 795d035d Klaus Aehlig
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRNetwork)
203 795d035d Klaus Aehlig
    (map Left names) fields lock
204 795d035d Klaus Aehlig
205 b5fa2700 Klaus Aehlig
handleCall qlock qstat cfg (SubmitJobToDrainedQueue ops) =
206 e5fba493 Klaus Aehlig
  do
207 f5b765f0 Klaus Aehlig
    let mcs = Config.getMasterCandidates cfg
208 f5b765f0 Klaus Aehlig
    jobid <- allocateJobId mcs qlock
209 e5fba493 Klaus Aehlig
    case jobid of
210 e5fba493 Klaus Aehlig
      Bad s -> return . Bad . GenericError $ s
211 e5fba493 Klaus Aehlig
      Ok jid -> do
212 c6013594 Klaus Aehlig
        ts <- currentTimestamp
213 c6013594 Klaus Aehlig
        job <- liftM (setReceivedTimestamp ts)
214 c6013594 Klaus Aehlig
                 $ queuedJobFromOpCodes jid ops
215 e5fba493 Klaus Aehlig
        qDir <- queueDir
216 e5fba493 Klaus Aehlig
        write_result <- writeJobToDisk qDir job
217 e5fba493 Klaus Aehlig
        case write_result of
218 e5fba493 Klaus Aehlig
          Bad s -> return . Bad . GenericError $ s
219 e5fba493 Klaus Aehlig
          Ok () -> do
220 f5b765f0 Klaus Aehlig
            _ <- replicateManyJobs qDir mcs [job]
221 b5fa2700 Klaus Aehlig
            _ <- forkIO $ enqueueNewJobs qstat [job]
222 e5fba493 Klaus Aehlig
            return . Ok . showJSON . fromJobId $ jid
223 e5fba493 Klaus Aehlig
224 b5fa2700 Klaus Aehlig
handleCall qlock qstat cfg (SubmitJob ops) =
225 e5fba493 Klaus Aehlig
  do
226 e5fba493 Klaus Aehlig
    open <- isQueueOpen
227 e5fba493 Klaus Aehlig
    if not open
228 e5fba493 Klaus Aehlig
       then return . Bad . GenericError $ "Queue drained"
229 b5fa2700 Klaus Aehlig
       else handleCall qlock qstat cfg (SubmitJobToDrainedQueue ops)
230 e5fba493 Klaus Aehlig
231 b5fa2700 Klaus Aehlig
handleCall qlock qstat cfg (SubmitManyJobs lops) =
232 94d6d0a3 Klaus Aehlig
  do
233 94d6d0a3 Klaus Aehlig
    open <- isQueueOpen
234 94d6d0a3 Klaus Aehlig
    if not open
235 94d6d0a3 Klaus Aehlig
      then return . Bad . GenericError $ "Queue drained"
236 94d6d0a3 Klaus Aehlig
      else do
237 f5b765f0 Klaus Aehlig
        let mcs = Config.getMasterCandidates cfg
238 f5b765f0 Klaus Aehlig
        result_jobids <- allocateJobIds mcs qlock (length lops)
239 94d6d0a3 Klaus Aehlig
        case result_jobids of
240 94d6d0a3 Klaus Aehlig
          Bad s -> return . Bad . GenericError $ s
241 94d6d0a3 Klaus Aehlig
          Ok jids -> do
242 c6013594 Klaus Aehlig
            ts <- currentTimestamp
243 c6013594 Klaus Aehlig
            jobs <- liftM (map $ setReceivedTimestamp ts)
244 c6013594 Klaus Aehlig
                      $ zipWithM queuedJobFromOpCodes jids lops
245 94d6d0a3 Klaus Aehlig
            qDir <- queueDir
246 94d6d0a3 Klaus Aehlig
            write_results <- mapM (writeJobToDisk qDir) jobs
247 f5b765f0 Klaus Aehlig
            let annotated_results = zip write_results jobs
248 94d6d0a3 Klaus Aehlig
                succeeded = map snd $ filter (isOk . fst) annotated_results
249 94d6d0a3 Klaus Aehlig
            when (any isBad write_results) . logWarning
250 94d6d0a3 Klaus Aehlig
              $ "Writing some jobs failed " ++ show annotated_results
251 f5b765f0 Klaus Aehlig
            replicateManyJobs qDir mcs succeeded
252 b5fa2700 Klaus Aehlig
            _ <- forkIO $ enqueueNewJobs qstat succeeded
253 94d6d0a3 Klaus Aehlig
            return . Ok . JSArray
254 f5b765f0 Klaus Aehlig
              . map (\(res, job) ->
255 94d6d0a3 Klaus Aehlig
                      if isOk res
256 f5b765f0 Klaus Aehlig
                        then showJSON (True, fromJobId $ qjId job)
257 94d6d0a3 Klaus Aehlig
                        else showJSON (False, genericResult id (const "") res))
258 94d6d0a3 Klaus Aehlig
              $ annotated_results
259 229da00f Petr Pudlak
260 6222b3a3 Klaus Aehlig
handleCall _ _ cfg (WaitForJobChange jid fields prev_job prev_log tmout) = do
261 6222b3a3 Klaus Aehlig
  let compute_fn = computeJobUpdate cfg jid fields prev_log 
262 6222b3a3 Klaus Aehlig
  qDir <- queueDir
263 6222b3a3 Klaus Aehlig
  -- verify if the job is finalized, and return immediately in this case
264 6222b3a3 Klaus Aehlig
  jobresult <- loadJobFromDisk qDir False jid
265 6222b3a3 Klaus Aehlig
  case jobresult of
266 6222b3a3 Klaus Aehlig
    Ok (job, _) | not (jobFinalized job) -> do
267 6222b3a3 Klaus Aehlig
      let jobfile = liveJobFile qDir jid
268 6222b3a3 Klaus Aehlig
      answer <- watchFile jobfile (min tmout C.luxiWfjcTimeout)
269 6222b3a3 Klaus Aehlig
                  (prev_job, JSArray []) compute_fn
270 6222b3a3 Klaus Aehlig
      return . Ok $ showJSON answer
271 6222b3a3 Klaus Aehlig
    _ -> liftM (Ok . showJSON) compute_fn
272 6222b3a3 Klaus Aehlig
273 b5fa2700 Klaus Aehlig
handleCall _ _ _ op =
274 5183e8be Iustin Pop
  return . Bad $
275 5183e8be Iustin Pop
    GenericError ("Luxi call '" ++ strOfOp op ++ "' not implemented")
276 25b54de0 Iustin Pop
277 edcad688 Petr Pudlak
{-# ANN handleCall "HLint: ignore Too strict if" #-}
278 edcad688 Petr Pudlak
279 6222b3a3 Klaus Aehlig
-- | Query the status of a job and return the requested fields
280 6222b3a3 Klaus Aehlig
-- and the logs newer than the given log number.
281 6222b3a3 Klaus Aehlig
computeJobUpdate :: ConfigData -> JobId -> [String] -> JSValue 
282 6222b3a3 Klaus Aehlig
                    -> IO (JSValue, JSValue)
283 6222b3a3 Klaus Aehlig
computeJobUpdate cfg jid fields prev_log = do
284 6222b3a3 Klaus Aehlig
  let sjid = show $ fromJobId jid
285 6222b3a3 Klaus Aehlig
  logDebug $ "Inspecting fields " ++ show fields ++ " of job " ++ sjid
286 6222b3a3 Klaus Aehlig
  let fromJSArray (JSArray xs) = xs
287 6222b3a3 Klaus Aehlig
      fromJSArray _ = []
288 6222b3a3 Klaus Aehlig
  let logFilter JSNull (JSArray _) = True
289 6222b3a3 Klaus Aehlig
      logFilter (JSRational _ n) (JSArray (JSRational _ m:_)) = n < m
290 6222b3a3 Klaus Aehlig
      logFilter _ _ = False
291 6222b3a3 Klaus Aehlig
  let filterLogs n logs = JSArray (filter (logFilter n) (logs >>= fromJSArray))
292 6222b3a3 Klaus Aehlig
  jobQuery <- handleClassicQuery cfg (Qlang.ItemTypeLuxi Qlang.QRJob)
293 6222b3a3 Klaus Aehlig
                [Right . fromIntegral $ fromJobId jid] ("oplog" : fields) False
294 6222b3a3 Klaus Aehlig
  let (rfields, rlogs) = case jobQuery of
295 6222b3a3 Klaus Aehlig
        Ok (JSArray [JSArray (JSArray logs : answer)]) ->
296 6222b3a3 Klaus Aehlig
          (answer, filterLogs prev_log logs)
297 6222b3a3 Klaus Aehlig
        _ -> (map (const JSNull) fields, JSArray [])
298 6222b3a3 Klaus Aehlig
  logDebug $ "Updates for job " ++ sjid ++ " are " ++ encode (rfields, rlogs)
299 6222b3a3 Klaus Aehlig
  return (JSArray rfields, rlogs)
300 6222b3a3 Klaus Aehlig
301 25b54de0 Iustin Pop
-- | Given a decoded luxi request, executes it and sends the luxi
302 25b54de0 Iustin Pop
-- response back to the client.
303 b5fa2700 Klaus Aehlig
handleClientMsg :: MVar () -> JQStatus -> Client -> ConfigReader
304 b5fa2700 Klaus Aehlig
                   -> LuxiOp -> IO Bool
305 b5fa2700 Klaus Aehlig
handleClientMsg qlock qstat client creader args = do
306 25b54de0 Iustin Pop
  cfg <- creader
307 25b54de0 Iustin Pop
  logDebug $ "Request: " ++ show args
308 b5fa2700 Klaus Aehlig
  call_result <- handleCallWrapper qlock qstat cfg args
309 25b54de0 Iustin Pop
  (!status, !rval) <-
310 25b54de0 Iustin Pop
    case call_result of
311 9abbb084 Iustin Pop
      Bad err -> do
312 3e0c2a24 Klaus Aehlig
        logWarning $ "Failed to execute request " ++ show args ++ ": "
313 3e0c2a24 Klaus Aehlig
                     ++ show err
314 5183e8be Iustin Pop
        return (False, showJSON err)
315 25b54de0 Iustin Pop
      Ok result -> do
316 f74b88fa Iustin Pop
        -- only log the first 2,000 chars of the result
317 f74b88fa Iustin Pop
        logDebug $ "Result (truncated): " ++ take 2000 (J.encode result)
318 3e0c2a24 Klaus Aehlig
        logInfo $ "Successfully handled " ++ strOfOp args
319 25b54de0 Iustin Pop
        return (True, result)
320 25b54de0 Iustin Pop
  sendMsg client $ buildResponse status rval
321 25b54de0 Iustin Pop
  return True
322 25b54de0 Iustin Pop
323 25b54de0 Iustin Pop
-- | Handles one iteration of the client protocol: receives message,
324 3e02cd3c Michele Tartara
-- checks it for validity and decodes it, returns response.
325 b5fa2700 Klaus Aehlig
handleClient :: MVar () -> JQStatus -> Client -> ConfigReader -> IO Bool
326 b5fa2700 Klaus Aehlig
handleClient qlock qstat client creader = do
327 25b54de0 Iustin Pop
  !msg <- recvMsgExt client
328 385d4574 Klaus Aehlig
  logDebug $ "Received message: " ++ show msg
329 25b54de0 Iustin Pop
  case msg of
330 25b54de0 Iustin Pop
    RecvConnClosed -> logDebug "Connection closed" >> return False
331 25b54de0 Iustin Pop
    RecvError err -> logWarning ("Error during message receiving: " ++ err) >>
332 25b54de0 Iustin Pop
                     return False
333 25b54de0 Iustin Pop
    RecvOk payload ->
334 25b54de0 Iustin Pop
      case validateCall payload >>= decodeCall of
335 9abbb084 Iustin Pop
        Bad err -> do
336 9abbb084 Iustin Pop
             let errmsg = "Failed to parse request: " ++ err
337 9abbb084 Iustin Pop
             logWarning errmsg
338 9abbb084 Iustin Pop
             sendMsg client $ buildResponse False (showJSON errmsg)
339 9abbb084 Iustin Pop
             return False
340 b5fa2700 Klaus Aehlig
        Ok args -> handleClientMsg qlock qstat client creader args
341 25b54de0 Iustin Pop
342 25b54de0 Iustin Pop
-- | Main client loop: runs one loop of 'handleClient', and if that
343 cb44e3db Helga Velroyen
-- doesn't report a finished (closed) connection, restarts itself.
344 b5fa2700 Klaus Aehlig
clientLoop :: MVar () -> JQStatus -> Client -> ConfigReader -> IO ()
345 b5fa2700 Klaus Aehlig
clientLoop qlock qstat client creader = do
346 b5fa2700 Klaus Aehlig
  result <- handleClient qlock qstat client creader
347 25b54de0 Iustin Pop
  if result
348 b5fa2700 Klaus Aehlig
    then clientLoop qlock qstat client creader
349 25b54de0 Iustin Pop
    else closeClient client
350 25b54de0 Iustin Pop
351 670e954a Thomas Thrainer
-- | Main listener loop: accepts clients, forks an I/O thread to handle
352 670e954a Thomas Thrainer
-- that client.
353 b5fa2700 Klaus Aehlig
listener :: MVar () -> JQStatus -> ConfigReader -> S.Socket -> IO ()
354 b5fa2700 Klaus Aehlig
listener qlock qstat creader socket = do
355 25b54de0 Iustin Pop
  client <- acceptClient socket
356 b5fa2700 Klaus Aehlig
  _ <- forkIO $ clientLoop qlock qstat client creader
357 670e954a Thomas Thrainer
  return ()
358 25b54de0 Iustin Pop
359 670e954a Thomas Thrainer
-- | Type alias for prepMain results
360 b5fa2700 Klaus Aehlig
type PrepResult = (FilePath, S.Socket, IORef (Result ConfigData), JQStatus)
361 25b54de0 Iustin Pop
362 3695a4e0 Thomas Thrainer
-- | Check function for luxid.
363 670e954a Thomas Thrainer
checkMain :: CheckFn ()
364 670e954a Thomas Thrainer
checkMain _ = return $ Right ()
365 670e954a Thomas Thrainer
366 3695a4e0 Thomas Thrainer
-- | Prepare function for luxid.
367 670e954a Thomas Thrainer
prepMain :: PrepFn () PrepResult
368 670e954a Thomas Thrainer
prepMain _ _ = do
369 670e954a Thomas Thrainer
  socket_path <- Path.defaultQuerySocket
370 0d0ac025 Iustin Pop
  cleanupSocket socket_path
371 73b16ca1 Iustin Pop
  s <- describeError "binding to the Luxi socket"
372 d605e261 Petr Pudlak
         Nothing (Just socket_path) $ getLuxiServer True socket_path
373 670e954a Thomas Thrainer
  cref <- newIORef (Bad "Configuration not yet loaded")
374 b5fa2700 Klaus Aehlig
  jq <- emptyJQStatus 
375 b5fa2700 Klaus Aehlig
  return (socket_path, s, cref, jq)
376 670e954a Thomas Thrainer
377 670e954a Thomas Thrainer
-- | Main function.
378 670e954a Thomas Thrainer
main :: MainFn () PrepResult
379 b5fa2700 Klaus Aehlig
main _ _ (socket_path, server, cref, jq) = do
380 670e954a Thomas Thrainer
  initConfigReader id cref
381 670e954a Thomas Thrainer
  let creader = readIORef cref
382 b5fa2700 Klaus Aehlig
  initJQScheduler jq
383 e5fba493 Klaus Aehlig
  
384 e5fba493 Klaus Aehlig
  qlockFile <- jobQueueLockFile
385 e5fba493 Klaus Aehlig
  lockFile qlockFile >>= exitIfBad "Failed to obtain the job-queue lock"
386 e5fba493 Klaus Aehlig
  qlock <- newMVar ()
387 4c3f55b8 Iustin Pop
388 4c3f55b8 Iustin Pop
  finally
389 b5fa2700 Klaus Aehlig
    (forever $ listener qlock jq creader server)
390 4c3f55b8 Iustin Pop
    (closeServer socket_path server)