Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Daemon.hs @ ef3ad027

History | View | Annotate | Download (10.5 kB)

1 6ec7a50e Iustin Pop
{-| Implementation of the generic daemon functionality.
2 6ec7a50e Iustin Pop
3 6ec7a50e Iustin Pop
-}
4 6ec7a50e Iustin Pop
5 6ec7a50e Iustin Pop
{-
6 6ec7a50e Iustin Pop
7 6ec7a50e Iustin Pop
Copyright (C) 2011, 2012 Google Inc.
8 6ec7a50e Iustin Pop
9 6ec7a50e Iustin Pop
This program is free software; you can redistribute it and/or modify
10 6ec7a50e Iustin Pop
it under the terms of the GNU General Public License as published by
11 6ec7a50e Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 6ec7a50e Iustin Pop
(at your option) any later version.
13 6ec7a50e Iustin Pop
14 6ec7a50e Iustin Pop
This program is distributed in the hope that it will be useful, but
15 6ec7a50e Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 6ec7a50e Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 6ec7a50e Iustin Pop
General Public License for more details.
18 6ec7a50e Iustin Pop
19 6ec7a50e Iustin Pop
You should have received a copy of the GNU General Public License
20 6ec7a50e Iustin Pop
along with this program; if not, write to the Free Software
21 6ec7a50e Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 6ec7a50e Iustin Pop
02110-1301, USA.
23 6ec7a50e Iustin Pop
24 6ec7a50e Iustin Pop
-}
25 6ec7a50e Iustin Pop
26 6ec7a50e Iustin Pop
module Ganeti.Daemon
27 6ec7a50e Iustin Pop
  ( DaemonOptions(..)
28 6ec7a50e Iustin Pop
  , OptType
29 6ec7a50e Iustin Pop
  , defaultOptions
30 6ec7a50e Iustin Pop
  , oShowHelp
31 6ec7a50e Iustin Pop
  , oShowVer
32 6ec7a50e Iustin Pop
  , oNoDaemonize
33 6ec7a50e Iustin Pop
  , oNoUserChecks
34 6ec7a50e Iustin Pop
  , oDebug
35 6ec7a50e Iustin Pop
  , oPort
36 152e05e1 Iustin Pop
  , oBindAddress
37 b714ff89 Iustin Pop
  , oSyslogUsage
38 6ec7a50e Iustin Pop
  , parseArgs
39 152e05e1 Iustin Pop
  , parseAddress
40 0d0ac025 Iustin Pop
  , cleanupSocket
41 6ec7a50e Iustin Pop
  , writePidFile
42 6ec7a50e Iustin Pop
  , genericMain
43 6ec7a50e Iustin Pop
  ) where
44 6ec7a50e Iustin Pop
45 79ac58fa Iustin Pop
import Control.Exception
46 6ec7a50e Iustin Pop
import Control.Monad
47 0c28bee1 Iustin Pop
import Data.Maybe (fromMaybe)
48 6ec7a50e Iustin Pop
import Data.Word
49 0c28bee1 Iustin Pop
import GHC.IO.Handle (hDuplicateTo)
50 152e05e1 Iustin Pop
import qualified Network.Socket as Socket
51 79ac58fa Iustin Pop
import Prelude hiding (catch)
52 6ec7a50e Iustin Pop
import System.Console.GetOpt
53 6ec7a50e Iustin Pop
import System.Exit
54 6ec7a50e Iustin Pop
import System.Environment
55 6ec7a50e Iustin Pop
import System.IO
56 0d0ac025 Iustin Pop
import System.IO.Error (isDoesNotExistError)
57 6ec7a50e Iustin Pop
import System.Posix.Directory
58 6ec7a50e Iustin Pop
import System.Posix.Files
59 6ec7a50e Iustin Pop
import System.Posix.IO
60 6ec7a50e Iustin Pop
import System.Posix.Process
61 6ec7a50e Iustin Pop
import System.Posix.Types
62 36691f08 Iustin Pop
import System.Posix.Signals
63 6ec7a50e Iustin Pop
64 51000365 Iustin Pop
import Ganeti.Common as Common
65 6ec7a50e Iustin Pop
import Ganeti.Logging
66 6ec7a50e Iustin Pop
import Ganeti.Runtime
67 6ec7a50e Iustin Pop
import Ganeti.BasicTypes
68 26d62e4c Iustin Pop
import Ganeti.Utils
69 6ec7a50e Iustin Pop
import qualified Ganeti.Constants as C
70 152e05e1 Iustin Pop
import qualified Ganeti.Ssconf as Ssconf
71 6ec7a50e Iustin Pop
72 0c28bee1 Iustin Pop
-- * Constants
73 0c28bee1 Iustin Pop
74 0c28bee1 Iustin Pop
-- | \/dev\/null path.
75 0c28bee1 Iustin Pop
devNull :: FilePath
76 0c28bee1 Iustin Pop
devNull = "/dev/null"
77 0c28bee1 Iustin Pop
78 6ec7a50e Iustin Pop
-- * Data types
79 6ec7a50e Iustin Pop
80 6ec7a50e Iustin Pop
-- | Command line options structure.
81 6ec7a50e Iustin Pop
data DaemonOptions = DaemonOptions
82 6ec7a50e Iustin Pop
  { optShowHelp     :: Bool           -- ^ Just show the help
83 6ec7a50e Iustin Pop
  , optShowVer      :: Bool           -- ^ Just show the program version
84 097ad7ee Iustin Pop
  , optShowComp     :: Bool           -- ^ Just show the completion info
85 6ec7a50e Iustin Pop
  , optDaemonize    :: Bool           -- ^ Whether to daemonize or not
86 6ec7a50e Iustin Pop
  , optPort         :: Maybe Word16   -- ^ Override for the network port
87 6ec7a50e Iustin Pop
  , optDebug        :: Bool           -- ^ Enable debug messages
88 6ec7a50e Iustin Pop
  , optNoUserChecks :: Bool           -- ^ Ignore user checks
89 152e05e1 Iustin Pop
  , optBindAddress  :: Maybe String   -- ^ Override for the bind address
90 b714ff89 Iustin Pop
  , optSyslogUsage  :: Maybe SyslogUsage -- ^ Override for Syslog usage
91 6ec7a50e Iustin Pop
  }
92 6ec7a50e Iustin Pop
93 6ec7a50e Iustin Pop
-- | Default values for the command line options.
94 6ec7a50e Iustin Pop
defaultOptions :: DaemonOptions
95 6ec7a50e Iustin Pop
defaultOptions  = DaemonOptions
96 6ec7a50e Iustin Pop
  { optShowHelp     = False
97 6ec7a50e Iustin Pop
  , optShowVer      = False
98 097ad7ee Iustin Pop
  , optShowComp     = False
99 6ec7a50e Iustin Pop
  , optDaemonize    = True
100 6ec7a50e Iustin Pop
  , optPort         = Nothing
101 6ec7a50e Iustin Pop
  , optDebug        = False
102 6ec7a50e Iustin Pop
  , optNoUserChecks = False
103 152e05e1 Iustin Pop
  , optBindAddress  = Nothing
104 b714ff89 Iustin Pop
  , optSyslogUsage  = Nothing
105 6ec7a50e Iustin Pop
  }
106 6ec7a50e Iustin Pop
107 51000365 Iustin Pop
instance StandardOptions DaemonOptions where
108 51000365 Iustin Pop
  helpRequested = optShowHelp
109 51000365 Iustin Pop
  verRequested  = optShowVer
110 097ad7ee Iustin Pop
  compRequested = optShowComp
111 5b11f8db Iustin Pop
  requestHelp o = o { optShowHelp = True }
112 5b11f8db Iustin Pop
  requestVer  o = o { optShowVer  = True }
113 097ad7ee Iustin Pop
  requestComp o = o { optShowComp = True }
114 51000365 Iustin Pop
115 6ec7a50e Iustin Pop
-- | Abrreviation for the option type.
116 51000365 Iustin Pop
type OptType = GenericOptType DaemonOptions
117 6ec7a50e Iustin Pop
118 6ec7a50e Iustin Pop
-- * Command line options
119 6ec7a50e Iustin Pop
120 6ec7a50e Iustin Pop
oNoDaemonize :: OptType
121 ce207617 Iustin Pop
oNoDaemonize =
122 ce207617 Iustin Pop
  (Option "f" ["foreground"]
123 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optDaemonize = False}))
124 ce207617 Iustin Pop
   "Don't detach from the current terminal",
125 ce207617 Iustin Pop
   OptComplNone)
126 6ec7a50e Iustin Pop
127 6ec7a50e Iustin Pop
oDebug :: OptType
128 ce207617 Iustin Pop
oDebug =
129 ce207617 Iustin Pop
  (Option "d" ["debug"]
130 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optDebug = True }))
131 ce207617 Iustin Pop
   "Enable debug messages",
132 ce207617 Iustin Pop
   OptComplNone)
133 6ec7a50e Iustin Pop
134 6ec7a50e Iustin Pop
oNoUserChecks :: OptType
135 ce207617 Iustin Pop
oNoUserChecks =
136 ce207617 Iustin Pop
  (Option "" ["no-user-checks"]
137 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optNoUserChecks = True }))
138 ce207617 Iustin Pop
   "Ignore user checks",
139 ce207617 Iustin Pop
   OptComplNone)
140 6ec7a50e Iustin Pop
141 6ec7a50e Iustin Pop
oPort :: Int -> OptType
142 ce207617 Iustin Pop
oPort def =
143 ce207617 Iustin Pop
  (Option "p" ["port"]
144 ce207617 Iustin Pop
   (reqWithConversion (tryRead "reading port")
145 ce207617 Iustin Pop
    (\port opts -> Ok opts { optPort = Just port }) "PORT")
146 ce207617 Iustin Pop
   ("Network port (default: " ++ show def ++ ")"),
147 ecebe9f6 Iustin Pop
   OptComplInteger)
148 6ec7a50e Iustin Pop
149 152e05e1 Iustin Pop
oBindAddress :: OptType
150 ce207617 Iustin Pop
oBindAddress =
151 ce207617 Iustin Pop
  (Option "b" ["bind"]
152 ce207617 Iustin Pop
   (ReqArg (\addr opts -> Ok opts { optBindAddress = Just addr })
153 ce207617 Iustin Pop
    "ADDR")
154 ce207617 Iustin Pop
   "Bind address (default depends on cluster configuration)",
155 ce207617 Iustin Pop
   OptComplInetAddr)
156 152e05e1 Iustin Pop
157 b714ff89 Iustin Pop
oSyslogUsage :: OptType
158 ce207617 Iustin Pop
oSyslogUsage =
159 ce207617 Iustin Pop
  (Option "" ["syslog"]
160 ce207617 Iustin Pop
   (reqWithConversion syslogUsageFromRaw
161 ce207617 Iustin Pop
    (\su opts -> Ok opts { optSyslogUsage = Just su })
162 ce207617 Iustin Pop
    "SYSLOG")
163 ce207617 Iustin Pop
   ("Enable logging to syslog (except debug \
164 ce207617 Iustin Pop
    \messages); one of 'no', 'yes' or 'only' [" ++ C.syslogUsage ++
165 ce207617 Iustin Pop
    "]"),
166 ce207617 Iustin Pop
   OptComplChoices ["yes", "no", "only"])
167 b714ff89 Iustin Pop
168 42834645 Iustin Pop
-- | Generic options.
169 42834645 Iustin Pop
genericOpts :: [OptType]
170 42834645 Iustin Pop
genericOpts = [ oShowHelp
171 42834645 Iustin Pop
              , oShowVer
172 097ad7ee Iustin Pop
              , oShowComp
173 42834645 Iustin Pop
              ]
174 42834645 Iustin Pop
175 6ec7a50e Iustin Pop
-- | Small wrapper over getArgs and 'parseOpts'.
176 6ec7a50e Iustin Pop
parseArgs :: String -> [OptType] -> IO (DaemonOptions, [String])
177 6ec7a50e Iustin Pop
parseArgs cmd options = do
178 6ec7a50e Iustin Pop
  cmd_args <- getArgs
179 22278fa7 Iustin Pop
  parseOpts defaultOptions cmd_args cmd (options ++ genericOpts) []
180 6ec7a50e Iustin Pop
181 6ec7a50e Iustin Pop
-- * Daemon-related functions
182 6ec7a50e Iustin Pop
-- | PID file mode.
183 6ec7a50e Iustin Pop
pidFileMode :: FileMode
184 6ec7a50e Iustin Pop
pidFileMode = unionFileModes ownerReadMode ownerWriteMode
185 6ec7a50e Iustin Pop
186 6ec7a50e Iustin Pop
-- | Writes a PID file and locks it.
187 6ec7a50e Iustin Pop
_writePidFile :: FilePath -> IO Fd
188 6ec7a50e Iustin Pop
_writePidFile path = do
189 6ec7a50e Iustin Pop
  fd <- createFile path pidFileMode
190 6ec7a50e Iustin Pop
  setLock fd (WriteLock, AbsoluteSeek, 0, 0)
191 6ec7a50e Iustin Pop
  my_pid <- getProcessID
192 6ec7a50e Iustin Pop
  _ <- fdWrite fd (show my_pid ++ "\n")
193 6ec7a50e Iustin Pop
  return fd
194 6ec7a50e Iustin Pop
195 79ac58fa Iustin Pop
-- | Helper to format an IOError.
196 79ac58fa Iustin Pop
formatIOError :: String -> IOError -> String
197 79ac58fa Iustin Pop
formatIOError msg err = msg ++ ": " ++  show err
198 79ac58fa Iustin Pop
199 6ec7a50e Iustin Pop
-- | Wrapper over '_writePidFile' that transforms IO exceptions into a
200 6ec7a50e Iustin Pop
-- 'Bad' value.
201 6ec7a50e Iustin Pop
writePidFile :: FilePath -> IO (Result Fd)
202 5b11f8db Iustin Pop
writePidFile path =
203 79ac58fa Iustin Pop
  catch (fmap Ok $ _writePidFile path)
204 79ac58fa Iustin Pop
    (return . Bad . formatIOError "Failure during writing of the pid file")
205 6ec7a50e Iustin Pop
206 0d0ac025 Iustin Pop
-- | Helper function to ensure a socket doesn't exist. Should only be
207 0d0ac025 Iustin Pop
-- called once we have locked the pid file successfully.
208 0d0ac025 Iustin Pop
cleanupSocket :: FilePath -> IO ()
209 5b11f8db Iustin Pop
cleanupSocket socketPath =
210 0d0ac025 Iustin Pop
  catchJust (guard . isDoesNotExistError) (removeLink socketPath)
211 0d0ac025 Iustin Pop
            (const $ return ())
212 0d0ac025 Iustin Pop
213 6ec7a50e Iustin Pop
-- | Sets up a daemon's environment.
214 6ec7a50e Iustin Pop
setupDaemonEnv :: FilePath -> FileMode -> IO ()
215 6ec7a50e Iustin Pop
setupDaemonEnv cwd umask = do
216 6ec7a50e Iustin Pop
  changeWorkingDirectory cwd
217 6ec7a50e Iustin Pop
  _ <- setFileCreationMask umask
218 6ec7a50e Iustin Pop
  _ <- createSession
219 6ec7a50e Iustin Pop
  return ()
220 6ec7a50e Iustin Pop
221 36691f08 Iustin Pop
-- | Signal handler for reopening log files.
222 36691f08 Iustin Pop
handleSigHup :: FilePath -> IO ()
223 36691f08 Iustin Pop
handleSigHup path = do
224 36691f08 Iustin Pop
  setupDaemonFDs (Just path)
225 36691f08 Iustin Pop
  logInfo "Reopening log files after receiving SIGHUP"
226 36691f08 Iustin Pop
227 0c28bee1 Iustin Pop
-- | Sets up a daemon's standard file descriptors.
228 0c28bee1 Iustin Pop
setupDaemonFDs :: Maybe FilePath -> IO ()
229 0c28bee1 Iustin Pop
setupDaemonFDs logfile = do
230 0c28bee1 Iustin Pop
  null_in_handle <- openFile devNull ReadMode
231 0c28bee1 Iustin Pop
  null_out_handle <- openFile (fromMaybe devNull logfile) AppendMode
232 0c28bee1 Iustin Pop
  hDuplicateTo null_in_handle stdin
233 0c28bee1 Iustin Pop
  hDuplicateTo null_out_handle stdout
234 0c28bee1 Iustin Pop
  hDuplicateTo null_out_handle stderr
235 0c28bee1 Iustin Pop
  hClose null_in_handle
236 0c28bee1 Iustin Pop
  hClose null_out_handle
237 0c28bee1 Iustin Pop
238 152e05e1 Iustin Pop
-- | Computes the default bind address for a given family.
239 152e05e1 Iustin Pop
defaultBindAddr :: Int                  -- ^ The port we want
240 152e05e1 Iustin Pop
                -> Socket.Family        -- ^ The cluster IP family
241 152e05e1 Iustin Pop
                -> Result (Socket.Family, Socket.SockAddr)
242 152e05e1 Iustin Pop
defaultBindAddr port Socket.AF_INET =
243 5b11f8db Iustin Pop
  Ok (Socket.AF_INET,
244 5b11f8db Iustin Pop
      Socket.SockAddrInet (fromIntegral port) Socket.iNADDR_ANY)
245 152e05e1 Iustin Pop
defaultBindAddr port Socket.AF_INET6 =
246 5b11f8db Iustin Pop
  Ok (Socket.AF_INET6,
247 5b11f8db Iustin Pop
      Socket.SockAddrInet6 (fromIntegral port) 0 Socket.iN6ADDR_ANY 0)
248 152e05e1 Iustin Pop
defaultBindAddr _ fam = Bad $ "Unsupported address family: " ++ show fam
249 152e05e1 Iustin Pop
250 152e05e1 Iustin Pop
-- | Default hints for the resolver
251 152e05e1 Iustin Pop
resolveAddrHints :: Maybe Socket.AddrInfo
252 152e05e1 Iustin Pop
resolveAddrHints =
253 152e05e1 Iustin Pop
  Just Socket.defaultHints { Socket.addrFlags = [Socket.AI_NUMERICHOST,
254 152e05e1 Iustin Pop
                                                 Socket.AI_NUMERICSERV] }
255 152e05e1 Iustin Pop
256 152e05e1 Iustin Pop
-- | Resolves a numeric address.
257 152e05e1 Iustin Pop
resolveAddr :: Int -> String -> IO (Result (Socket.Family, Socket.SockAddr))
258 152e05e1 Iustin Pop
resolveAddr port str = do
259 152e05e1 Iustin Pop
  resolved <- Socket.getAddrInfo resolveAddrHints (Just str) (Just (show port))
260 152e05e1 Iustin Pop
  return $ case resolved of
261 152e05e1 Iustin Pop
             [] -> Bad "Invalid results from lookup?"
262 5b11f8db Iustin Pop
             best:_ -> Ok (Socket.addrFamily best, Socket.addrAddress best)
263 152e05e1 Iustin Pop
264 152e05e1 Iustin Pop
-- | Based on the options, compute the socket address to use for the
265 152e05e1 Iustin Pop
-- daemon.
266 152e05e1 Iustin Pop
parseAddress :: DaemonOptions      -- ^ Command line options
267 152e05e1 Iustin Pop
             -> Int                -- ^ Default port for this daemon
268 152e05e1 Iustin Pop
             -> IO (Result (Socket.Family, Socket.SockAddr))
269 152e05e1 Iustin Pop
parseAddress opts defport = do
270 152e05e1 Iustin Pop
  let port = maybe defport fromIntegral $ optPort opts
271 152e05e1 Iustin Pop
  def_family <- Ssconf.getPrimaryIPFamily Nothing
272 5b11f8db Iustin Pop
  case optBindAddress opts of
273 5b11f8db Iustin Pop
    Nothing -> return (def_family >>= defaultBindAddr port)
274 5b11f8db Iustin Pop
    Just saddr -> catch (resolveAddr port saddr)
275 5b11f8db Iustin Pop
                  (annotateIOError $ "Invalid address " ++ saddr)
276 152e05e1 Iustin Pop
277 6ec7a50e Iustin Pop
-- | Run an I/O action as a daemon.
278 6ec7a50e Iustin Pop
--
279 6ec7a50e Iustin Pop
-- WARNING: this only works in single-threaded mode (either using the
280 6ec7a50e Iustin Pop
-- single-threaded runtime, or using the multi-threaded one but with
281 6ec7a50e Iustin Pop
-- only one OS thread, i.e. -N1).
282 6ec7a50e Iustin Pop
--
283 6ec7a50e Iustin Pop
-- FIXME: this doesn't support error reporting and the prepfn
284 6ec7a50e Iustin Pop
-- functionality.
285 0c28bee1 Iustin Pop
daemonize :: FilePath -> IO () -> IO ()
286 0c28bee1 Iustin Pop
daemonize logfile action = do
287 6ec7a50e Iustin Pop
  -- first fork
288 6ec7a50e Iustin Pop
  _ <- forkProcess $ do
289 6ec7a50e Iustin Pop
    -- in the child
290 6ec7a50e Iustin Pop
    setupDaemonEnv "/" (unionFileModes groupModes otherModes)
291 0c28bee1 Iustin Pop
    setupDaemonFDs $ Just logfile
292 36691f08 Iustin Pop
    _ <- installHandler lostConnection (Catch (handleSigHup logfile)) Nothing
293 6ec7a50e Iustin Pop
    _ <- forkProcess action
294 6ec7a50e Iustin Pop
    exitImmediately ExitSuccess
295 6ec7a50e Iustin Pop
  exitImmediately ExitSuccess
296 6ec7a50e Iustin Pop
297 6ec7a50e Iustin Pop
-- | Generic daemon startup.
298 6ec7a50e Iustin Pop
genericMain :: GanetiDaemon -> [OptType] -> (DaemonOptions -> IO ()) -> IO ()
299 6ec7a50e Iustin Pop
genericMain daemon options main = do
300 6ec7a50e Iustin Pop
  let progname = daemonName daemon
301 6ec7a50e Iustin Pop
  (opts, args) <- parseArgs progname options
302 6ec7a50e Iustin Pop
303 88a10df5 Iustin Pop
  exitUnless (null args) "This program doesn't take any arguments"
304 6ec7a50e Iustin Pop
305 6ec7a50e Iustin Pop
  unless (optNoUserChecks opts) $ do
306 6ec7a50e Iustin Pop
    runtimeEnts <- getEnts
307 88a10df5 Iustin Pop
    ents <- exitIfBad "Can't find required user/groups" runtimeEnts
308 88a10df5 Iustin Pop
    verifyDaemonUser daemon ents
309 6ec7a50e Iustin Pop
310 b714ff89 Iustin Pop
  syslog <- case optSyslogUsage opts of
311 88a10df5 Iustin Pop
              Nothing -> exitIfBad "Invalid cluster syslog setting" $
312 b714ff89 Iustin Pop
                         syslogUsageFromRaw C.syslogUsage
313 b714ff89 Iustin Pop
              Just v -> return v
314 0c28bee1 Iustin Pop
  let processFn = if optDaemonize opts
315 0c28bee1 Iustin Pop
                    then daemonize (daemonLogFile daemon)
316 0c28bee1 Iustin Pop
                    else id
317 b714ff89 Iustin Pop
  processFn $ innerMain daemon opts syslog (main opts)
318 6ec7a50e Iustin Pop
319 6ec7a50e Iustin Pop
-- | Inner daemon function.
320 6ec7a50e Iustin Pop
--
321 6ec7a50e Iustin Pop
-- This is executed after daemonization.
322 b714ff89 Iustin Pop
innerMain :: GanetiDaemon -> DaemonOptions -> SyslogUsage -> IO () -> IO ()
323 b714ff89 Iustin Pop
innerMain daemon opts syslog main = do
324 0c28bee1 Iustin Pop
  let logfile = if optDaemonize opts
325 0c28bee1 Iustin Pop
                  then Nothing
326 0c28bee1 Iustin Pop
                  else Just $ daemonLogFile daemon
327 0c28bee1 Iustin Pop
  setupLogging logfile (daemonName daemon) (optDebug opts) True False syslog
328 6ec7a50e Iustin Pop
  pid_fd <- writePidFile (daemonPidFile daemon)
329 88a10df5 Iustin Pop
  _ <- exitIfBad "Cannot write PID file; already locked? Error" pid_fd
330 6ec7a50e Iustin Pop
  logNotice "starting"
331 6ec7a50e Iustin Pop
  main