Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (14 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 94d6d0a3 Klaus Aehlig
import Control.Monad (forever, when, zipWithM)
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 25b54de0 Iustin Pop
import Text.JSON (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 25b54de0 Iustin Pop
import Ganeti.Logging
57 25b54de0 Iustin Pop
import Ganeti.Luxi
58 4cab6703 Iustin Pop
import qualified Ganeti.Query.Language as Qlang
59 1c3231aa Thomas Thrainer
import qualified Ganeti.Query.Cluster as QCluster
60 e5fba493 Klaus Aehlig
import Ganeti.Path (queueDir, jobQueueLockFile, defaultLuxiSocket)
61 4cbe9bda Iustin Pop
import Ganeti.Query.Query
62 c4e0d065 Klaus Aehlig
import Ganeti.Query.Filter (makeSimpleFilter)
63 6e94b75c Jose A. Lopes
import Ganeti.Types
64 e5fba493 Klaus Aehlig
import Ganeti.Utils (lockFile, exitIfBad)
65 3cb9bd38 Jose A. Lopes
import qualified Ganeti.Version as Version
66 25b54de0 Iustin Pop
67 cd67e337 Iustin Pop
-- | Helper for classic queries.
68 cd67e337 Iustin Pop
handleClassicQuery :: ConfigData      -- ^ Cluster config
69 cd67e337 Iustin Pop
                   -> Qlang.ItemType  -- ^ Query type
70 037762a9 Iustin Pop
                   -> [Either String Integer] -- ^ Requested names
71 037762a9 Iustin Pop
                                              -- (empty means all)
72 cd67e337 Iustin Pop
                   -> [String]        -- ^ Requested fields
73 cd67e337 Iustin Pop
                   -> Bool            -- ^ Whether to do sync queries or not
74 5183e8be Iustin Pop
                   -> IO (GenericResult GanetiException JSValue)
75 c4e0d065 Klaus Aehlig
handleClassicQuery _ _ _ _ True =
76 5183e8be Iustin Pop
  return . Bad $ OpPrereqError "Sync queries are not allowed" ECodeInval
77 c4e0d065 Klaus Aehlig
handleClassicQuery cfg qkind names fields _ = do
78 c4e0d065 Klaus Aehlig
  let flt = makeSimpleFilter (nameField qkind) names
79 cd67e337 Iustin Pop
  qr <- query cfg True (Qlang.Query qkind fields flt)
80 cd67e337 Iustin Pop
  return $ showJSON <$> (qr >>= queryCompat)
81 cd67e337 Iustin Pop
82 25b54de0 Iustin Pop
-- | Minimal wrapper to handle the missing config case.
83 e5fba493 Klaus Aehlig
handleCallWrapper :: MVar () -> Result ConfigData 
84 e5fba493 Klaus Aehlig
                     -> LuxiOp -> IO (ErrorResult JSValue)
85 e5fba493 Klaus Aehlig
handleCallWrapper _ (Bad msg) _ =
86 5183e8be Iustin Pop
  return . Bad . ConfigurationError $
87 5183e8be Iustin Pop
           "I do not have access to a valid configuration, cannot\
88 5183e8be Iustin Pop
           \ process queries: " ++ msg
89 e5fba493 Klaus Aehlig
handleCallWrapper qlock (Ok config) op = handleCall qlock config op
90 25b54de0 Iustin Pop
91 25b54de0 Iustin Pop
-- | Actual luxi operation handler.
92 e5fba493 Klaus Aehlig
handleCall :: MVar () -> ConfigData -> LuxiOp -> IO (ErrorResult JSValue)
93 e5fba493 Klaus Aehlig
handleCall _ cdata QueryClusterInfo =
94 25b54de0 Iustin Pop
  let cluster = configCluster cdata
95 1c3231aa Thomas Thrainer
      master = QCluster.clusterMasterNodeName cdata
96 25b54de0 Iustin Pop
      hypervisors = clusterEnabledHypervisors cluster
97 966e1580 Helga Velroyen
      diskTemplates = clusterEnabledDiskTemplates cluster
98 72747d91 Iustin Pop
      def_hv = case hypervisors of
99 72747d91 Iustin Pop
                 x:_ -> showJSON x
100 72747d91 Iustin Pop
                 [] -> JSNull
101 25b54de0 Iustin Pop
      bits = show (bitSize (0::Int)) ++ "bits"
102 25b54de0 Iustin Pop
      arch_tuple = [bits, arch]
103 5b11f8db Iustin Pop
      obj = [ ("software_version", showJSON C.releaseVersion)
104 5b11f8db Iustin Pop
            , ("protocol_version", showJSON C.protocolVersion)
105 5b11f8db Iustin Pop
            , ("config_version", showJSON C.configVersion)
106 c87997d2 Jose A. Lopes
            , ("os_api_version", showJSON . maximum .
107 c87997d2 Jose A. Lopes
                                 Set.toList . ConstantUtils.unFrozenSet $
108 c87997d2 Jose A. Lopes
                                 C.osApiVersions)
109 5b11f8db Iustin Pop
            , ("export_version", showJSON C.exportVersion)
110 3cb9bd38 Jose A. Lopes
            , ("vcs_version", showJSON Version.version)
111 5b11f8db Iustin Pop
            , ("architecture", showJSON arch_tuple)
112 25b54de0 Iustin Pop
            , ("name", showJSON $ clusterClusterName cluster)
113 1c3231aa Thomas Thrainer
            , ("master", showJSON (case master of
114 1c3231aa Thomas Thrainer
                                     Ok name -> name
115 1c3231aa Thomas Thrainer
                                     _ -> undefined))
116 72747d91 Iustin Pop
            , ("default_hypervisor", def_hv)
117 5b11f8db Iustin Pop
            , ("enabled_hypervisors", showJSON hypervisors)
118 a2160e57 Iustin Pop
            , ("hvparams", showJSON $ clusterHvparams cluster)
119 a2160e57 Iustin Pop
            , ("os_hvp", showJSON $ clusterOsHvp cluster)
120 25b54de0 Iustin Pop
            , ("beparams", showJSON $ clusterBeparams cluster)
121 25b54de0 Iustin Pop
            , ("osparams", showJSON $ clusterOsparams cluster)
122 25b54de0 Iustin Pop
            , ("ipolicy", showJSON $ clusterIpolicy cluster)
123 25b54de0 Iustin Pop
            , ("nicparams", showJSON $ clusterNicparams cluster)
124 25b54de0 Iustin Pop
            , ("ndparams", showJSON $ clusterNdparams cluster)
125 a2160e57 Iustin Pop
            , ("diskparams", showJSON $ clusterDiskparams cluster)
126 25b54de0 Iustin Pop
            , ("candidate_pool_size",
127 25b54de0 Iustin Pop
               showJSON $ clusterCandidatePoolSize cluster)
128 25b54de0 Iustin Pop
            , ("master_netdev",  showJSON $ clusterMasterNetdev cluster)
129 25b54de0 Iustin Pop
            , ("master_netmask", showJSON $ clusterMasterNetmask cluster)
130 25b54de0 Iustin Pop
            , ("use_external_mip_script",
131 25b54de0 Iustin Pop
               showJSON $ clusterUseExternalMipScript cluster)
132 64b0309a Dimitris Aragiorgis
            , ("volume_group_name",
133 64b0309a Dimitris Aragiorgis
               maybe JSNull showJSON (clusterVolumeGroupName cluster))
134 25b54de0 Iustin Pop
            , ("drbd_usermode_helper",
135 25b54de0 Iustin Pop
               maybe JSNull showJSON (clusterDrbdUsermodeHelper cluster))
136 25b54de0 Iustin Pop
            , ("file_storage_dir", showJSON $ clusterFileStorageDir cluster)
137 25b54de0 Iustin Pop
            , ("shared_file_storage_dir",
138 25b54de0 Iustin Pop
               showJSON $ clusterSharedFileStorageDir cluster)
139 25b54de0 Iustin Pop
            , ("maintain_node_health",
140 25b54de0 Iustin Pop
               showJSON $ clusterMaintainNodeHealth cluster)
141 25b54de0 Iustin Pop
            , ("ctime", showJSON $ clusterCtime cluster)
142 25b54de0 Iustin Pop
            , ("mtime", showJSON $ clusterMtime cluster)
143 25b54de0 Iustin Pop
            , ("uuid", showJSON $ clusterUuid cluster)
144 25b54de0 Iustin Pop
            , ("tags", showJSON $ clusterTags cluster)
145 25b54de0 Iustin Pop
            , ("uid_pool", showJSON $ clusterUidPool cluster)
146 25b54de0 Iustin Pop
            , ("default_iallocator",
147 25b54de0 Iustin Pop
               showJSON $ clusterDefaultIallocator cluster)
148 25b54de0 Iustin Pop
            , ("reserved_lvs", showJSON $ clusterReservedLvs cluster)
149 25b54de0 Iustin Pop
            , ("primary_ip_version",
150 25b54de0 Iustin Pop
               showJSON . ipFamilyToVersion $ clusterPrimaryIpFamily cluster)
151 7b9ceea7 Helga Velroyen
            , ("prealloc_wipe_disks",
152 7b9ceea7 Helga Velroyen
               showJSON $ clusterPreallocWipeDisks cluster)
153 7b9ceea7 Helga Velroyen
            , ("hidden_os", showJSON $ clusterHiddenOs cluster)
154 7b9ceea7 Helga Velroyen
            , ("blacklisted_os", showJSON $ clusterBlacklistedOs cluster)
155 966e1580 Helga Velroyen
            , ("enabled_disk_templates", showJSON diskTemplates)
156 25b54de0 Iustin Pop
            ]
157 25b54de0 Iustin Pop
158 1c3231aa Thomas Thrainer
  in case master of
159 1c3231aa Thomas Thrainer
    Ok _ -> return . Ok . J.makeObj $ obj
160 1c3231aa Thomas Thrainer
    Bad ex -> return $ Bad ex
161 25b54de0 Iustin Pop
162 e5fba493 Klaus Aehlig
handleCall _ cfg (QueryTags kind name) = do
163 f2374060 Iustin Pop
  let tags = case kind of
164 6e94b75c Jose A. Lopes
               TagKindCluster  -> Ok . clusterTags $ configCluster cfg
165 6e94b75c Jose A. Lopes
               TagKindGroup    -> groupTags <$> Config.getGroup    cfg name
166 6e94b75c Jose A. Lopes
               TagKindNode     -> nodeTags  <$> Config.getNode     cfg name
167 6e94b75c Jose A. Lopes
               TagKindInstance -> instTags  <$> Config.getInstance cfg name
168 a8633d70 Jose A. Lopes
               TagKindNetwork  -> Bad $ OpPrereqError
169 a8633d70 Jose A. Lopes
                                        "Network tag is not allowed"
170 a8633d70 Jose A. Lopes
                                        ECodeInval
171 6e94b75c Jose A. Lopes
  return (J.showJSON <$> tags)
172 f2374060 Iustin Pop
173 e5fba493 Klaus Aehlig
handleCall _ cfg (Query qkind qfields qfilter) = do
174 fa2c927c Agata Murawska
  result <- query cfg True (Qlang.Query qkind qfields qfilter)
175 4cbe9bda Iustin Pop
  return $ J.showJSON <$> result
176 4cbe9bda Iustin Pop
177 e5fba493 Klaus Aehlig
handleCall _ _ (QueryFields qkind qfields) = do
178 518023a9 Iustin Pop
  let result = queryFields (Qlang.QueryFields qkind qfields)
179 518023a9 Iustin Pop
  return $ J.showJSON <$> result
180 518023a9 Iustin Pop
181 e5fba493 Klaus Aehlig
handleCall _ cfg (QueryNodes names fields lock) =
182 037762a9 Iustin Pop
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRNode)
183 c4e0d065 Klaus Aehlig
    (map Left names) fields lock
184 cd67e337 Iustin Pop
185 89352544 Helga Velroyen
handleCall _ cfg (QueryInstances names fields lock) =
186 89352544 Helga Velroyen
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRInstance)
187 89352544 Helga Velroyen
    (map Left names) fields lock
188 89352544 Helga Velroyen
189 e5fba493 Klaus Aehlig
handleCall _ cfg (QueryGroups names fields lock) =
190 037762a9 Iustin Pop
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRGroup)
191 c4e0d065 Klaus Aehlig
    (map Left names) fields lock
192 cd67e337 Iustin Pop
193 e5fba493 Klaus Aehlig
handleCall _ cfg (QueryJobs names fields) =
194 a7e484c4 Iustin Pop
  handleClassicQuery cfg (Qlang.ItemTypeLuxi Qlang.QRJob)
195 c4e0d065 Klaus Aehlig
    (map (Right . fromIntegral . fromJobId) names)  fields False
196 a7e484c4 Iustin Pop
197 e5fba493 Klaus Aehlig
handleCall _ cfg (QueryNetworks names fields lock) =
198 795d035d Klaus Aehlig
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRNetwork)
199 795d035d Klaus Aehlig
    (map Left names) fields lock
200 795d035d Klaus Aehlig
201 e5fba493 Klaus Aehlig
handleCall qlock cfg (SubmitJobToDrainedQueue ops) =
202 e5fba493 Klaus Aehlig
  do
203 e5fba493 Klaus Aehlig
    jobid <- allocateJobId (Config.getMasterCandidates cfg) qlock
204 e5fba493 Klaus Aehlig
    case jobid of
205 e5fba493 Klaus Aehlig
      Bad s -> return . Bad . GenericError $ s
206 e5fba493 Klaus Aehlig
      Ok jid -> do
207 e5fba493 Klaus Aehlig
        qDir <- queueDir
208 e5fba493 Klaus Aehlig
        job <- queuedJobFromOpCodes jid ops
209 e5fba493 Klaus Aehlig
        write_result <- writeJobToDisk qDir job
210 e5fba493 Klaus Aehlig
        case write_result of
211 e5fba493 Klaus Aehlig
          Bad s -> return . Bad . GenericError $ s
212 e5fba493 Klaus Aehlig
          Ok () -> do
213 e5fba493 Klaus Aehlig
            socketpath <- defaultLuxiSocket
214 e5fba493 Klaus Aehlig
            client <- getClient socketpath
215 e5fba493 Klaus Aehlig
            pickupResult <- callMethod (PickupJob jid) client
216 e5fba493 Klaus Aehlig
            closeClient client
217 e5fba493 Klaus Aehlig
            case pickupResult of
218 e5fba493 Klaus Aehlig
              Ok _ -> return ()
219 e5fba493 Klaus Aehlig
              Bad e -> logWarning $ "Failded to notify masterd: " ++ show e
220 e5fba493 Klaus Aehlig
            return . Ok . showJSON . fromJobId $ jid
221 e5fba493 Klaus Aehlig
222 e5fba493 Klaus Aehlig
handleCall qlock cfg (SubmitJob ops) =
223 e5fba493 Klaus Aehlig
  do
224 e5fba493 Klaus Aehlig
    open <- isQueueOpen
225 e5fba493 Klaus Aehlig
    if not open
226 e5fba493 Klaus Aehlig
       then return . Bad . GenericError $ "Queue drained"
227 e5fba493 Klaus Aehlig
       else handleCall qlock cfg (SubmitJobToDrainedQueue ops)
228 e5fba493 Klaus Aehlig
229 94d6d0a3 Klaus Aehlig
handleCall qlock cfg (SubmitManyJobs lops) =
230 94d6d0a3 Klaus Aehlig
  do
231 94d6d0a3 Klaus Aehlig
    open <- isQueueOpen
232 94d6d0a3 Klaus Aehlig
    if not open
233 94d6d0a3 Klaus Aehlig
      then return . Bad . GenericError $ "Queue drained"
234 94d6d0a3 Klaus Aehlig
      else do
235 94d6d0a3 Klaus Aehlig
        result_jobids <- allocateJobIds (Config.getMasterCandidates cfg)
236 94d6d0a3 Klaus Aehlig
                           qlock (length lops)
237 94d6d0a3 Klaus Aehlig
        case result_jobids of
238 94d6d0a3 Klaus Aehlig
          Bad s -> return . Bad . GenericError $ s
239 94d6d0a3 Klaus Aehlig
          Ok jids -> do
240 94d6d0a3 Klaus Aehlig
            jobs <- zipWithM queuedJobFromOpCodes jids lops
241 94d6d0a3 Klaus Aehlig
            qDir <- queueDir
242 94d6d0a3 Klaus Aehlig
            write_results <- mapM (writeJobToDisk qDir) jobs
243 94d6d0a3 Klaus Aehlig
            let annotated_results = zip write_results jids
244 94d6d0a3 Klaus Aehlig
                succeeded = map snd $ filter (isOk . fst) annotated_results
245 94d6d0a3 Klaus Aehlig
            when (any isBad write_results) . logWarning
246 94d6d0a3 Klaus Aehlig
              $ "Writing some jobs failed " ++ show annotated_results
247 94d6d0a3 Klaus Aehlig
            socketpath <- defaultLuxiSocket
248 94d6d0a3 Klaus Aehlig
            client <- getClient socketpath
249 94d6d0a3 Klaus Aehlig
            pickupResults <- mapM (flip callMethod client . PickupJob)
250 94d6d0a3 Klaus Aehlig
                               succeeded
251 94d6d0a3 Klaus Aehlig
            closeClient client
252 94d6d0a3 Klaus Aehlig
            when (any isBad pickupResults)
253 94d6d0a3 Klaus Aehlig
              . logWarning . (++)  "Failed to notify maserd: " . show
254 94d6d0a3 Klaus Aehlig
              $ zip succeeded pickupResults
255 94d6d0a3 Klaus Aehlig
            return . Ok . JSArray
256 94d6d0a3 Klaus Aehlig
              . map (\(res, jid) ->
257 94d6d0a3 Klaus Aehlig
                      if isOk res
258 94d6d0a3 Klaus Aehlig
                        then showJSON (True, fromJobId jid)
259 94d6d0a3 Klaus Aehlig
                        else showJSON (False, genericResult id (const "") res))
260 94d6d0a3 Klaus Aehlig
              $ annotated_results
261 229da00f Petr Pudlak
262 e5fba493 Klaus Aehlig
handleCall _ _ op =
263 5183e8be Iustin Pop
  return . Bad $
264 5183e8be Iustin Pop
    GenericError ("Luxi call '" ++ strOfOp op ++ "' not implemented")
265 25b54de0 Iustin Pop
266 edcad688 Petr Pudlak
{-# ANN handleCall "HLint: ignore Too strict if" #-}
267 edcad688 Petr Pudlak
268 25b54de0 Iustin Pop
-- | Given a decoded luxi request, executes it and sends the luxi
269 25b54de0 Iustin Pop
-- response back to the client.
270 e5fba493 Klaus Aehlig
handleClientMsg :: MVar () -> Client -> ConfigReader -> LuxiOp -> IO Bool
271 e5fba493 Klaus Aehlig
handleClientMsg qlock client creader args = do
272 25b54de0 Iustin Pop
  cfg <- creader
273 25b54de0 Iustin Pop
  logDebug $ "Request: " ++ show args
274 e5fba493 Klaus Aehlig
  call_result <- handleCallWrapper qlock cfg args
275 25b54de0 Iustin Pop
  (!status, !rval) <-
276 25b54de0 Iustin Pop
    case call_result of
277 9abbb084 Iustin Pop
      Bad err -> do
278 3e0c2a24 Klaus Aehlig
        logWarning $ "Failed to execute request " ++ show args ++ ": "
279 3e0c2a24 Klaus Aehlig
                     ++ show err
280 5183e8be Iustin Pop
        return (False, showJSON err)
281 25b54de0 Iustin Pop
      Ok result -> do
282 f74b88fa Iustin Pop
        -- only log the first 2,000 chars of the result
283 f74b88fa Iustin Pop
        logDebug $ "Result (truncated): " ++ take 2000 (J.encode result)
284 3e0c2a24 Klaus Aehlig
        logInfo $ "Successfully handled " ++ strOfOp args
285 25b54de0 Iustin Pop
        return (True, result)
286 25b54de0 Iustin Pop
  sendMsg client $ buildResponse status rval
287 25b54de0 Iustin Pop
  return True
288 25b54de0 Iustin Pop
289 25b54de0 Iustin Pop
-- | Handles one iteration of the client protocol: receives message,
290 3e02cd3c Michele Tartara
-- checks it for validity and decodes it, returns response.
291 e5fba493 Klaus Aehlig
handleClient :: MVar () -> Client -> ConfigReader -> IO Bool
292 e5fba493 Klaus Aehlig
handleClient qlock client creader = do
293 25b54de0 Iustin Pop
  !msg <- recvMsgExt client
294 385d4574 Klaus Aehlig
  logDebug $ "Received message: " ++ show msg
295 25b54de0 Iustin Pop
  case msg of
296 25b54de0 Iustin Pop
    RecvConnClosed -> logDebug "Connection closed" >> return False
297 25b54de0 Iustin Pop
    RecvError err -> logWarning ("Error during message receiving: " ++ err) >>
298 25b54de0 Iustin Pop
                     return False
299 25b54de0 Iustin Pop
    RecvOk payload ->
300 25b54de0 Iustin Pop
      case validateCall payload >>= decodeCall of
301 9abbb084 Iustin Pop
        Bad err -> do
302 9abbb084 Iustin Pop
             let errmsg = "Failed to parse request: " ++ err
303 9abbb084 Iustin Pop
             logWarning errmsg
304 9abbb084 Iustin Pop
             sendMsg client $ buildResponse False (showJSON errmsg)
305 9abbb084 Iustin Pop
             return False
306 e5fba493 Klaus Aehlig
        Ok args -> handleClientMsg qlock client creader args
307 25b54de0 Iustin Pop
308 25b54de0 Iustin Pop
-- | Main client loop: runs one loop of 'handleClient', and if that
309 cb44e3db Helga Velroyen
-- doesn't report a finished (closed) connection, restarts itself.
310 e5fba493 Klaus Aehlig
clientLoop :: MVar () -> Client -> ConfigReader -> IO ()
311 e5fba493 Klaus Aehlig
clientLoop qlock client creader = do
312 e5fba493 Klaus Aehlig
  result <- handleClient qlock client creader
313 25b54de0 Iustin Pop
  if result
314 e5fba493 Klaus Aehlig
    then clientLoop qlock client creader
315 25b54de0 Iustin Pop
    else closeClient client
316 25b54de0 Iustin Pop
317 670e954a Thomas Thrainer
-- | Main listener loop: accepts clients, forks an I/O thread to handle
318 670e954a Thomas Thrainer
-- that client.
319 e5fba493 Klaus Aehlig
listener :: MVar () -> ConfigReader -> S.Socket -> IO ()
320 e5fba493 Klaus Aehlig
listener qlock creader socket = do
321 25b54de0 Iustin Pop
  client <- acceptClient socket
322 e5fba493 Klaus Aehlig
  _ <- forkIO $ clientLoop qlock client creader
323 670e954a Thomas Thrainer
  return ()
324 25b54de0 Iustin Pop
325 670e954a Thomas Thrainer
-- | Type alias for prepMain results
326 670e954a Thomas Thrainer
type PrepResult = (FilePath, S.Socket, IORef (Result ConfigData))
327 25b54de0 Iustin Pop
328 3695a4e0 Thomas Thrainer
-- | Check function for luxid.
329 670e954a Thomas Thrainer
checkMain :: CheckFn ()
330 670e954a Thomas Thrainer
checkMain _ = return $ Right ()
331 670e954a Thomas Thrainer
332 3695a4e0 Thomas Thrainer
-- | Prepare function for luxid.
333 670e954a Thomas Thrainer
prepMain :: PrepFn () PrepResult
334 670e954a Thomas Thrainer
prepMain _ _ = do
335 670e954a Thomas Thrainer
  socket_path <- Path.defaultQuerySocket
336 0d0ac025 Iustin Pop
  cleanupSocket socket_path
337 73b16ca1 Iustin Pop
  s <- describeError "binding to the Luxi socket"
338 e455a3e8 Michele Tartara
         Nothing (Just socket_path) $ getServer True socket_path
339 670e954a Thomas Thrainer
  cref <- newIORef (Bad "Configuration not yet loaded")
340 670e954a Thomas Thrainer
  return (socket_path, s, cref)
341 670e954a Thomas Thrainer
342 670e954a Thomas Thrainer
-- | Main function.
343 670e954a Thomas Thrainer
main :: MainFn () PrepResult
344 670e954a Thomas Thrainer
main _ _ (socket_path, server, cref) = do
345 670e954a Thomas Thrainer
  initConfigReader id cref
346 670e954a Thomas Thrainer
  let creader = readIORef cref
347 e5fba493 Klaus Aehlig
  
348 e5fba493 Klaus Aehlig
  qlockFile <- jobQueueLockFile
349 e5fba493 Klaus Aehlig
  lockFile qlockFile >>= exitIfBad "Failed to obtain the job-queue lock"
350 e5fba493 Klaus Aehlig
  qlock <- newMVar ()
351 4c3f55b8 Iustin Pop
352 4c3f55b8 Iustin Pop
  finally
353 e5fba493 Klaus Aehlig
    (forever $ listener qlock creader server)
354 4c3f55b8 Iustin Pop
    (closeServer socket_path server)