keter/Keter/Main.hs

216 lines
8.8 KiB
Haskell
Raw Normal View History

2012-05-14 12:18:09 +04:00
{-# LANGUAGE OverloadedStrings #-}
2013-06-03 15:15:13 +04:00
{-# LANGUAGE ViewPatterns #-}
2012-05-15 12:38:54 +04:00
{-# LANGUAGE NoImplicitPrelude #-}
2012-05-17 10:32:11 +04:00
{-# LANGUAGE TemplateHaskell #-}
2012-05-29 06:30:59 +04:00
{-# LANGUAGE RecordWildCards #-}
2012-10-24 18:31:18 +04:00
{-# LANGUAGE ScopedTypeVariables #-}
2012-05-11 12:29:25 +04:00
module Keter.Main
( keter
) where
2012-05-17 11:59:17 +04:00
import Keter.Prelude hiding (getCurrentTime)
2013-07-10 15:15:18 +04:00
import qualified Codec.Archive.TempTarball as TempFolder
2012-05-11 12:29:25 +04:00
import qualified Keter.App as App
2013-07-10 14:26:37 +04:00
import Keter.Types
2013-07-25 14:07:48 +04:00
import qualified Keter.HostManager as HostMan
import qualified Keter.Proxy as Proxy
import qualified Keter.ReverseProxy as ReverseProxy
2013-05-29 10:43:52 +04:00
import System.Posix.Files (modificationTime, getFileStatus)
import System.Posix.Signals (sigHUP, installHandler, Handler (Catch))
import qualified Data.Conduit.LogFile as LogFile
2012-05-11 12:29:25 +04:00
2013-07-10 10:57:38 +04:00
import Data.Yaml.FilePath
2012-05-11 12:29:25 +04:00
import qualified Control.Concurrent.MVar as M
import Control.Concurrent (forkIO)
2012-05-11 12:29:25 +04:00
import qualified Data.Map as Map
2013-06-03 14:34:47 +04:00
import qualified System.FSNotify as FSN
2013-07-10 10:57:38 +04:00
import Control.Monad (forever, forM)
2012-05-14 11:15:50 +04:00
import qualified Filesystem.Path.CurrentOS as F
2012-05-29 06:30:59 +04:00
import qualified Filesystem as F
2012-10-24 18:31:18 +04:00
import Control.Exception (throwIO, try)
2012-05-15 12:38:54 +04:00
import qualified Prelude as P
2012-05-17 08:15:25 +04:00
import Data.Text.Encoding (encodeUtf8)
import Data.Time (getCurrentTime)
import qualified Data.Text as T
2013-05-29 10:43:52 +04:00
import Data.Maybe (fromMaybe, catMaybes)
2013-07-14 16:55:05 +04:00
import Control.Applicative ((<$>))
2012-10-24 18:31:18 +04:00
import System.Posix.User (userID, userGroupID, getUserEntryForName, getUserEntryForID, userName)
import qualified Data.Text.Read
import qualified Data.Set as Set
import qualified Network.HTTP.Conduit as HTTP (newManager)
2013-06-03 15:15:13 +04:00
import qualified Network.Wai.Handler.Warp as Warp
import Data.Conduit.Process.Unix (initProcessTracker)
2012-05-11 12:29:25 +04:00
2012-05-29 06:30:59 +04:00
keter :: P.FilePath -- ^ root directory or config file
2013-07-10 14:26:37 +04:00
-> [F.FilePath -> KIO (Either SomeException Plugin)]
2012-05-15 12:38:54 +04:00
-> P.IO ()
2013-07-10 14:26:37 +04:00
keter (F.decodeString -> input) mkPlugins = do
2012-05-29 06:30:59 +04:00
exists <- F.isFile input
2013-07-14 16:30:55 +04:00
KeterConfig{..} <-
2012-05-29 06:30:59 +04:00
if exists
2013-07-10 10:57:38 +04:00
then decodeFileRelative input >>= either
(\e -> P.error $ "Invalid config file: " ++ P.show e)
return
2013-07-14 16:30:55 +04:00
else return def { kconfigDir = input }
2012-05-29 06:30:59 +04:00
2012-10-24 18:31:18 +04:00
muid <-
2013-07-14 16:30:55 +04:00
case kconfigSetuid of
2012-10-24 18:31:18 +04:00
Nothing -> return Nothing
Just t -> do
x <- try $
case Data.Text.Read.decimal t of
Right (i, "") -> getUserEntryForID i
_ -> getUserEntryForName $ T.unpack t
case x of
Left (_ :: SomeException) -> P.error $ T.unpack $ "Invalid user ID: " ++ t
Right ue -> return $ Just (T.pack $ userName ue, (userID ue, userGroupID ue))
processTracker <- initProcessTracker
2013-07-25 14:07:48 +04:00
portman <- runThrow $ HostMan.start kconfigHostMan
2013-07-14 16:30:55 +04:00
tf <- runThrow $ liftIO $ TempFolder.setup $ kconfigDir </> "temp"
plugins <- runThrow $ loadPlugins $ map ($ kconfigDir) mkPlugins
mainlog <- runThrow $ liftIO $ LogFile.openRotatingLog
2013-07-14 16:30:55 +04:00
(F.encodeString $ kconfigDir </> "log" </> "keter")
LogFile.defaultMaxTotal
2012-05-17 08:15:25 +04:00
let runKIO' = runKIO $ \ml -> do
now <- getCurrentTime
let bs = encodeUtf8 $ T.concat
2012-05-17 10:32:11 +04:00
[ T.take 22 $ show now
2012-05-17 08:15:25 +04:00
, ": "
, show ml
, "\n"
]
LogFile.addChunk mainlog bs
2012-05-17 08:15:25 +04:00
runKIOPrint = runKIO P.print
2012-05-11 12:29:25 +04:00
2013-06-03 15:15:13 +04:00
manager <- HTTP.newManager def
_ <- forkIO $ Proxy.reverseProxy
2013-07-14 16:30:55 +04:00
kconfigIpFromHeader
2013-06-03 15:15:13 +04:00
manager
Warp.defaultSettings
2013-07-14 16:30:55 +04:00
{ Warp.settingsPort = kconfigPort
, Warp.settingsHost = kconfigHost
2013-06-03 15:15:13 +04:00
}
2013-07-25 14:07:48 +04:00
(runKIOPrint . HostMan.lookupPort portman)
2013-07-14 16:30:55 +04:00
case kconfigSsl of
2012-08-09 19:12:32 +04:00
Nothing -> return ()
2013-07-10 10:57:38 +04:00
Just (Proxy.TLSConfig s ts) -> do
2012-08-09 19:12:32 +04:00
_ <- forkIO $ Proxy.reverseProxySsl
2013-07-14 16:30:55 +04:00
kconfigIpFromHeader
2013-06-03 15:15:13 +04:00
manager
ts
s
2013-07-25 14:07:48 +04:00
(runKIOPrint . HostMan.lookupPort portman)
2012-08-09 19:12:32 +04:00
return ()
2012-05-11 12:29:25 +04:00
mappMap <- M.newMVar Map.empty
2012-05-15 12:19:03 +04:00
let removeApp appname = Keter.Prelude.modifyMVar_ mappMap $ return . Map.delete appname
2012-05-11 12:29:25 +04:00
addApp bundle = do
let appname = getAppname bundle
2012-05-15 12:38:54 +04:00
rest <- modifyMVar mappMap $ \appMap ->
2012-05-11 12:29:25 +04:00
case Map.lookup appname appMap of
2013-05-29 10:43:52 +04:00
Just (app, _time) -> do
2012-05-15 12:38:54 +04:00
App.reload app
2013-05-29 10:43:52 +04:00
etime <- liftIO $ modificationTime <$> getFileStatus (F.encodeString bundle)
let time = either (P.const 0) id etime
return (Map.insert appname (app, time) appMap, return ())
2012-05-11 12:29:25 +04:00
Nothing -> do
2012-05-17 10:32:11 +04:00
mlogger <- do
2013-07-14 16:30:55 +04:00
let dirout = kconfigDir </> "log" </> fromText ("app-" ++ appname)
2012-05-17 10:32:11 +04:00
direrr = dirout </> "err"
erlog <- liftIO $ LogFile.openRotatingLog
(F.encodeString dirout)
LogFile.defaultMaxTotal
case erlog of
2012-05-17 10:32:11 +04:00
Left e -> do
$logEx e
return Nothing
Right rlog -> return (Just rlog)
let logger = fromMaybe LogFile.dummy mlogger
2012-05-15 12:38:54 +04:00
(app, rest) <- App.start
2012-05-14 11:15:50 +04:00
tf
2012-10-24 18:31:18 +04:00
muid
processTracker
portman
2013-07-10 14:26:37 +04:00
plugins
2012-05-17 10:32:11 +04:00
logger
2012-05-14 11:15:50 +04:00
appname
2012-05-15 12:38:54 +04:00
bundle
2012-05-14 11:15:50 +04:00
(removeApp appname)
2013-05-29 10:43:52 +04:00
etime <- liftIO $ modificationTime <$> getFileStatus (F.encodeString bundle)
let time = either (P.const 0) id etime
let appMap' = Map.insert appname (app, time) appMap
2012-05-11 12:29:25 +04:00
return (appMap', rest)
2012-05-15 12:38:54 +04:00
rest
2012-05-11 12:29:25 +04:00
terminateApp appname = do
2013-05-29 10:43:52 +04:00
-- FIXME why not remove it from the map?
2012-05-11 12:29:25 +04:00
appMap <- M.readMVar mappMap
case Map.lookup appname appMap of
Nothing -> return ()
2013-05-29 10:43:52 +04:00
Just (app, _) -> runKIO' $ App.terminate app
2012-05-11 12:29:25 +04:00
2013-07-14 16:30:55 +04:00
let incoming = kconfigDir </> "incoming"
2012-05-15 12:38:54 +04:00
isKeter fp = hasExtension fp "keter"
2012-05-17 12:47:54 +04:00
createTree incoming
2013-05-29 10:43:52 +04:00
bundles0 <- fmap (filter isKeter) $ listDirectory incoming
runKIO' $ mapM_ addApp bundles0
2012-05-11 12:29:25 +04:00
2013-07-25 15:10:09 +04:00
{- FIXME handle static stanzas
let staticReverse r = do
2013-07-25 14:07:48 +04:00
HostMan.addEntry portman (ReverseProxy.reversingHost r)
$ HostMan.PEReverseProxy
2013-06-03 15:15:13 +04:00
$ ReverseProxy.RPEntry r manager
2013-07-14 16:30:55 +04:00
runKIO' $ mapM_ staticReverse (Set.toList kconfigReverseProxy)
2013-07-25 15:10:09 +04:00
-}
2013-07-10 14:26:37 +04:00
2013-06-03 14:34:47 +04:00
-- File system watching
wm <- FSN.startManager
FSN.watchDir wm incoming (P.const True) $ \e ->
let e' =
case e of
FSN.Removed fp _ -> Left fp
FSN.Added fp _ -> Right fp
FSN.Modified fp _ -> Right fp
in case e' of
Left fp -> when (isKeter fp) $ terminateApp $ getAppname fp
Right fp -> when (isKeter fp) $ runKIO' $ addApp $ incoming </> fp
2012-05-11 12:29:25 +04:00
2013-05-29 10:43:52 +04:00
-- Install HUP handler for cases when inotify cannot be used.
_ <- flip (installHandler sigHUP) Nothing $ Catch $ do
actions <- M.withMVar mappMap $ \appMap -> do
bundles <- fmap (filter isKeter) $ F.listDirectory incoming
newMap <- fmap Map.fromList $ forM bundles $ \bundle -> do
time <- modificationTime <$> getFileStatus (F.encodeString bundle)
return (getAppname' $ F.encodeString bundle, (bundle, time))
let apps = Set.toList $ Set.fromList (Map.keys newMap)
`Set.union` Set.fromList (Map.keys appMap)
fmap catMaybes $ forM apps $ \appname -> return $
case (Map.lookup appname appMap, Map.lookup appname newMap) of
(Nothing, Nothing) -> Nothing -- should never happen
(Just _, Nothing) -> Just $ terminateApp appname
(Nothing, Just (bundle, _)) -> Just $ runKIO' $ addApp bundle
(Just (_, oldTime), Just (bundle, newTime))
| newTime /= oldTime -> Just $ runKIO' $ addApp bundle
| otherwise -> Nothing
P.sequence_ actions
2012-05-15 12:38:54 +04:00
runKIO' $ forever $ threadDelay $ 60 * 1000 * 1000
2012-05-11 12:29:25 +04:00
where
2012-05-15 12:38:54 +04:00
getAppname = either id id . toText . basename
getAppname' = getAppname . F.decodeString
2012-05-17 08:15:25 +04:00
runThrow f = runKIO P.print f >>= either throwIO return
2013-07-10 14:26:37 +04:00
loadPlugins :: [KIO (Either SomeException Plugin)]
-> KIO (Either SomeException Plugins)
loadPlugins =
loop id
where
loop front [] = return $ Right $ front []
loop front (x:xs) = do
eres <- x
case eres of
Left e -> return $ Left e
Right p -> loop (front . (p:)) xs