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