keter/Keter/Main.hs

197 lines
7.5 KiB
Haskell
Raw Normal View History

2013-07-26 12:17:05 +04:00
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
2012-10-24 18:31:18 +04:00
{-# LANGUAGE ScopedTypeVariables #-}
2013-07-26 12:17:05 +04:00
{-# LANGUAGE TemplateHaskell #-}
2012-05-11 12:29:25 +04:00
module Keter.Main
( keter
) where
2013-07-10 15:15:18 +04:00
import qualified Codec.Archive.TempTarball as TempFolder
2013-07-26 12:17:05 +04:00
import Control.Concurrent.Async (waitAny, withAsync)
import Control.Monad (unless)
2014-09-21 11:42:26 +04:00
import qualified Data.CaseInsensitive as CI
2013-07-26 12:17:05 +04:00
import qualified Data.Conduit.LogFile as LogFile
import Data.Monoid (mempty)
import qualified Data.Vector as V
import Keter.App (AppStartConfig (..))
import qualified Keter.AppManager as AppMan
import qualified Keter.HostManager as HostMan
import qualified Keter.PortPool as PortPool
import qualified Keter.Proxy as Proxy
import Keter.Types
import System.Posix.Files (getFileStatus, modificationTime)
import System.Posix.Signals (Handler (Catch), installHandler,
sigHUP)
import Control.Applicative ((<$>))
import Control.Exception (throwIO, try)
import Control.Monad (forM)
import Data.Conduit.Process.Unix (initProcessTracker)
import qualified Data.Map as Map
import qualified Data.Text as T
import Data.Text.Encoding (encodeUtf8)
2012-10-24 18:31:18 +04:00
import qualified Data.Text.Read
2013-07-26 12:17:05 +04:00
import Data.Time (getCurrentTime)
import Data.Yaml.FilePath
import qualified Filesystem as F
import qualified Filesystem.Path.CurrentOS as F
2013-07-28 14:41:42 +04:00
import Filesystem.Path.CurrentOS ((</>), hasExtension)
2013-11-10 19:04:26 +04:00
import qualified Network.HTTP.Conduit as HTTP (newManager, conduitManagerSettings)
2013-07-26 12:17:05 +04:00
import qualified System.FSNotify as FSN
import System.Posix.User (getUserEntryForID,
getUserEntryForName, userGroupID,
userID, userName)
2013-07-28 14:41:42 +04:00
import Control.Monad (void, when)
import Data.Default (def)
import Prelude hiding (FilePath, log)
import Filesystem (listDirectory, createTree)
keter :: FilePath -- ^ root directory or config file
-> [FilePath -> IO Plugin]
-> IO ()
2013-07-30 18:49:01 +04:00
keter input mkPlugins = withManagers input mkPlugins $ \kc hostman appMan log -> do
2013-07-26 12:17:05 +04:00
launchInitial kc appMan
2013-07-30 18:49:01 +04:00
startWatching kc appMan log
2013-07-26 12:17:05 +04:00
startListening kc hostman
-- | Load up Keter config.
withConfig :: FilePath
-> (KeterConfig -> IO a)
-> IO a
withConfig input f = do
2012-05-29 06:30:59 +04:00
exists <- F.isFile input
2013-07-26 12:17:05 +04:00
config <-
2012-05-29 06:30:59 +04:00
if exists
2013-07-26 12:17:05 +04:00
then do
eres <- decodeFileRelative input
case eres of
Left e -> throwIO $ InvalidKeterConfigFile input e
Right x -> return x
2013-07-14 16:30:55 +04:00
else return def { kconfigDir = input }
2013-07-26 12:17:05 +04:00
f config
2012-05-29 06:30:59 +04:00
2013-07-28 14:41:42 +04:00
withLogger :: FilePath
-> (KeterConfig -> (LogMessage -> IO ()) -> IO a)
-> IO a
withLogger fp f = withConfig fp $ \config -> do
2013-07-26 11:27:06 +04:00
mainlog <- LogFile.openRotatingLog
2013-07-26 12:17:05 +04:00
(F.encodeString $ (kconfigDir config) </> "log" </> "keter")
LogFile.defaultMaxTotal
2012-05-17 08:15:25 +04:00
2013-07-28 14:41:42 +04:00
f config $ \ml -> do
now <- getCurrentTime
let bs = encodeUtf8 $ T.pack $ concat
[ take 22 $ show now
, ": "
, show ml
, "\n"
]
LogFile.addChunk mainlog bs
2012-05-11 12:29:25 +04:00
2013-07-26 12:17:05 +04:00
withManagers :: FilePath
-> [FilePath -> IO Plugin]
2013-07-30 18:49:01 +04:00
-> (KeterConfig -> HostMan.HostManager -> AppMan.AppManager -> (LogMessage -> IO ()) -> IO a)
2013-07-26 12:17:05 +04:00
-> IO a
2013-07-28 14:41:42 +04:00
withManagers input mkPlugins f = withLogger input $ \kc@KeterConfig {..} log -> do
2013-07-26 11:27:06 +04:00
processTracker <- initProcessTracker
hostman <- HostMan.start
portpool <- PortPool.start kconfigPortPool
tf <- TempFolder.setup $ kconfigDir </> "temp"
2013-07-28 14:41:42 +04:00
plugins <- sequence $ map ($ kconfigDir) mkPlugins
2013-07-26 11:46:34 +04:00
muid <-
case kconfigSetuid of
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
2013-07-28 14:41:42 +04:00
Left (_ :: SomeException) -> error $ "Invalid user ID: " ++ T.unpack t
2013-07-26 11:46:34 +04:00
Right ue -> return $ Just (T.pack $ userName ue, (userID ue, userGroupID ue))
2013-07-26 11:09:11 +04:00
let appStartConfig = AppStartConfig
{ ascTempFolder = tf
, ascSetuid = muid
, ascProcessTracker = processTracker
, ascHostManager = hostman
, ascPortPool = portpool
, ascPlugins = plugins
2013-07-28 16:19:08 +04:00
, ascLog = log
, ascKeterConfig = kc
2013-07-26 11:09:11 +04:00
}
2013-07-28 14:41:42 +04:00
appMan <- AppMan.initialize log appStartConfig
2013-07-30 18:49:01 +04:00
f kc hostman appMan log
2013-07-26 11:09:11 +04:00
2013-07-26 12:17:05 +04:00
launchInitial :: KeterConfig -> AppMan.AppManager -> IO ()
launchInitial kc@KeterConfig {..} appMan = do
2012-05-17 12:47:54 +04:00
createTree incoming
2013-05-29 10:43:52 +04:00
bundles0 <- fmap (filter isKeter) $ listDirectory incoming
2013-07-26 12:17:05 +04:00
mapM_ (AppMan.addApp appMan) bundles0
2012-05-11 12:29:25 +04:00
2013-07-25 18:35:16 +04:00
unless (V.null kconfigBuiltinStanzas) $ AppMan.perform
appMan
2013-07-28 16:19:08 +04:00
AIBuiltin
(AppMan.Reload $ AIData $ BundleConfig kconfigBuiltinStanzas mempty)
2013-07-26 12:17:05 +04:00
where
incoming = getIncoming kc
getIncoming :: KeterConfig -> FilePath
getIncoming kc = kconfigDir kc </> "incoming"
2013-07-10 14:26:37 +04:00
2013-07-26 12:17:05 +04:00
isKeter :: FilePath -> Bool
isKeter fp = hasExtension fp "keter"
2013-07-30 18:49:01 +04:00
startWatching :: KeterConfig -> AppMan.AppManager -> (LogMessage -> IO ()) -> IO ()
startWatching kc@KeterConfig {..} appMan log = do
2013-06-03 14:34:47 +04:00
-- File system watching
wm <- FSN.startManager
2014-06-09 14:30:54 +04:00
_ <- FSN.watchDir wm incoming (const True) $ \e -> do
2013-07-30 18:49:01 +04:00
e' <-
case e of
FSN.Removed fp _ -> do
log $ WatchedFile "removed" fp
return $ Left fp
FSN.Added fp _ -> do
log $ WatchedFile "added" fp
return $ Right fp
FSN.Modified fp _ -> do
log $ WatchedFile "modified" fp
return $ Right fp
case e' of
2013-07-26 12:17:05 +04:00
Left fp -> when (isKeter fp) $ AppMan.terminateApp appMan $ getAppname fp
Right fp -> when (isKeter fp) $ AppMan.addApp appMan $ 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.
2013-07-26 12:17:05 +04:00
void $ flip (installHandler sigHUP) Nothing $ Catch $ do
2013-07-26 11:09:11 +04:00
bundles <- fmap (filter isKeter) $ F.listDirectory incoming
newMap <- fmap Map.fromList $ forM bundles $ \bundle -> do
time <- modificationTime <$> getFileStatus (F.encodeString bundle)
return (getAppname bundle, (bundle, time))
AppMan.reloadAppList appMan newMap
2013-07-26 12:17:05 +04:00
where
incoming = getIncoming kc
2013-05-29 10:43:52 +04:00
2013-07-26 12:17:05 +04:00
startListening :: KeterConfig -> HostMan.HostManager -> IO ()
startListening KeterConfig {..} hostman = do
2013-11-10 19:04:26 +04:00
manager <- HTTP.newManager HTTP.conduitManagerSettings
2013-07-26 11:27:06 +04:00
runAndBlock kconfigListeners $ Proxy.reverseProxy
kconfigIpFromHeader
manager
2014-09-21 11:42:26 +04:00
(HostMan.lookupAction hostman . CI.mk)
2013-07-26 11:27:06 +04:00
runAndBlock :: NonEmptyVector a
2013-07-28 14:41:42 +04:00
-> (a -> IO ())
-> IO ()
2013-07-26 11:27:06 +04:00
runAndBlock (NonEmptyVector x0 v) f =
loop l0 []
where
l0 = x0 : V.toList v
loop (x:xs) asyncs = withAsync (f x) $ \async -> loop xs $ async : asyncs
-- Once we have all of our asyncs, we wait for /any/ of them to exit. If
-- any listener thread exits, we kill the whole process.
loop [] asyncs = void $ waitAny asyncs