gitit.hs 5.7 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172
  1. {-# LANGUAGE CPP #-}
  2. {-
  3. Copyright (C) 2008 John MacFarlane <jgm@berkeley.edu>
  4. This program is free software; you can redistribute it and/or modify
  5. it under the terms of the GNU General Public License as published by
  6. the Free Software Foundation; either version 2 of the License, or
  7. (at your option) any later version.
  8. This program is distributed in the hope that it will be useful,
  9. but WITHOUT ANY WARRANTY; without even the implied warranty of
  10. MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
  11. GNU General Public License for more details.
  12. You should have received a copy of the GNU General Public License
  13. along with this program; if not, write to the Free Software
  14. Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
  15. -}
  16. module Main where
  17. import Network.Gitit
  18. import Network.Gitit.Server
  19. import Network.Gitit.Util (readFileUTF8)
  20. import System.Directory
  21. import Data.Maybe (isNothing)
  22. import Data.Text.Encoding (encodeUtf8)
  23. import Network.Gitit.Compat.Except()
  24. import Control.Monad.Reader
  25. import System.Log.Logger (Priority(..), setLevel, setHandlers,
  26. getLogger, saveGlobalLogger)
  27. import System.Log.Handler.Simple (fileHandler)
  28. import System.Environment
  29. import System.Exit
  30. import System.IO (stderr)
  31. import System.Console.GetOpt
  32. import Network.Socket hiding (Debug)
  33. import Data.Version (showVersion)
  34. import qualified Data.ByteString.Char8 as B
  35. import Data.ByteString.UTF8 (fromString)
  36. import Paths_gitit (version, getDataFileName)
  37. main :: IO ()
  38. main = do
  39. -- parse options to get config file
  40. args <- getArgs >>= parseArgs
  41. -- sequence in Either monad gets first Left or all Rights
  42. opts <- case sequence args of
  43. Left Help -> putErr ExitSuccess =<< usageMessage
  44. Left Version -> do
  45. progname <- getProgName
  46. putErr ExitSuccess (progname ++ " version " ++
  47. showVersion version ++ compileInfo ++ copyrightMessage)
  48. Left PrintDefaultConfig -> getDataFileName "data/default.conf" >>=
  49. readFileUTF8 >>= B.putStrLn . encodeUtf8 >> exitSuccess
  50. Right xs -> return xs
  51. conf' <- case [f | ConfigFile f <- opts] of
  52. fs -> getConfigFromFiles fs
  53. let conf = foldl handleFlag conf' opts
  54. -- check for external programs that are needed
  55. let repoProg = case repositoryType conf of
  56. Mercurial -> "hg"
  57. Darcs -> "darcs"
  58. Git -> "git"
  59. let prereqs = ["grep", repoProg]
  60. forM_ prereqs $ \prog ->
  61. findExecutable prog >>= \mbFind ->
  62. when (isNothing mbFind) $ error $
  63. "Required program '" ++ prog ++ "' not found in system path."
  64. -- set up logging
  65. let level = if debugMode conf then DEBUG else logLevel conf
  66. logFileHandler <- fileHandler (logFile conf) level
  67. serverLogger <- getLogger "Happstack.Server.AccessLog.Combined"
  68. gititLogger <- getLogger "gitit"
  69. saveGlobalLogger $ setLevel level $ setHandlers [logFileHandler] serverLogger
  70. saveGlobalLogger $ setLevel level $ setHandlers [logFileHandler] gititLogger
  71. -- setup the page repository, template, and static files, if they don't exist
  72. createRepoIfMissing conf
  73. createStaticIfMissing conf
  74. createTemplateIfMissing conf
  75. -- initialize state
  76. initializeGititState conf
  77. let serverConf = nullConf { validator = Nothing, port = portNumber conf,
  78. timeout = 20, logAccess = Nothing }
  79. -- open the requested interface
  80. sock <- socket AF_INET Stream defaultProtocol
  81. setSocketOption sock ReuseAddr 1
  82. device <- inet_addr (address conf)
  83. bind sock (SockAddrInet (toEnum (portNumber conf)) device)
  84. listen sock 10
  85. -- start the server
  86. simpleHTTPWithSocket sock serverConf $ msum [ wiki conf
  87. , dir "_reloadTemplates" reloadTemplates
  88. ]
  89. data ExitOpt
  90. = Help
  91. | Version
  92. | PrintDefaultConfig
  93. data ConfigOpt
  94. = ConfigFile FilePath
  95. | Port Int
  96. | Listen String
  97. | Debug
  98. deriving (Eq)
  99. type Opt = Either ExitOpt ConfigOpt
  100. flags :: [OptDescr Opt]
  101. flags =
  102. [ Option ['h'] ["help"] (NoArg (Left Help))
  103. "Print this help message"
  104. , Option ['v'] ["version"] (NoArg (Left Version))
  105. "Print version information"
  106. , Option ['p'] ["port"] (ReqArg (Right . Port . read) "PORT")
  107. "Specify port"
  108. , Option ['l'] ["listen"] (ReqArg (Right . Listen) "INTERFACE")
  109. "Specify IP address to listen on"
  110. , Option [] ["print-default-config"] (NoArg (Left PrintDefaultConfig))
  111. "Print default configuration"
  112. , Option [] ["debug"] (NoArg (Right Debug))
  113. "Print debugging information on each request"
  114. , Option ['f'] ["config-file"] (ReqArg (Right . ConfigFile) "FILE")
  115. "Specify configuration file"
  116. ]
  117. parseArgs :: [String] -> IO [Opt]
  118. parseArgs argv =
  119. case getOpt Permute flags argv of
  120. (opts,_,[]) -> return opts
  121. (_,_,errs) -> putErr (ExitFailure 1) . (concat errs ++) =<< usageMessage
  122. usageMessage :: IO String
  123. usageMessage = do
  124. progname <- getProgName
  125. return $ usageInfo ("Usage: " ++ progname ++ " [opts...]") flags
  126. copyrightMessage :: String
  127. copyrightMessage = "\nCopyright (C) 2008 John MacFarlane\n" ++
  128. "This is free software; see the source for copying conditions. There is no\n" ++
  129. "warranty, not even for merchantability or fitness for a particular purpose."
  130. compileInfo :: String
  131. compileInfo =
  132. #ifdef _PLUGINS
  133. " +plugins"
  134. #else
  135. " -plugins"
  136. #endif
  137. handleFlag :: Config -> ConfigOpt -> Config
  138. handleFlag conf Debug = conf{ debugMode = True, logLevel = DEBUG }
  139. handleFlag conf (Port p) = conf { portNumber = p }
  140. handleFlag conf (Listen l) = conf { address = l }
  141. handleFlag conf _ = conf
  142. putErr :: ExitCode -> String -> IO a
  143. putErr c s = B.hPutStrLn stderr (fromString s) >> exitWith c