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
|
2013-07-25 16:44:23 +04:00
|
|
|
import qualified Keter.PortPool as PortPool
|
2012-08-06 18:44:41 +04:00
|
|
|
import qualified Keter.Proxy as Proxy
|
2013-07-25 15:18:32 +04:00
|
|
|
import qualified Network.HTTP.ReverseProxy.Rewrite as Rewrite
|
2013-05-29 10:43:52 +04:00
|
|
|
import System.Posix.Files (modificationTime, getFileStatus)
|
|
|
|
import System.Posix.Signals (sigHUP, installHandler, Handler (Catch))
|
2013-07-10 13:48:46 +04:00
|
|
|
import qualified Data.Conduit.LogFile as LogFile
|
2013-07-25 18:35:16 +04:00
|
|
|
import qualified Keter.AppManager as AppMan
|
|
|
|
import Data.Monoid (mempty)
|
|
|
|
import Control.Monad (unless)
|
|
|
|
import qualified Data.Vector as V
|
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
|
2012-08-06 18:44:41 +04:00
|
|
|
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
|
2013-03-17 01:36:57 +04:00
|
|
|
import qualified Data.Set as Set
|
2013-03-20 09:01:43 +04:00
|
|
|
import qualified Network.HTTP.Conduit as HTTP (newManager)
|
2013-06-03 15:15:13 +04:00
|
|
|
import qualified Network.Wai.Handler.Warp as Warp
|
2013-07-10 10:03:03 +04:00
|
|
|
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))
|
|
|
|
|
2013-07-10 10:03:03 +04:00
|
|
|
processTracker <- initProcessTracker
|
2013-07-25 16:44:23 +04:00
|
|
|
hostman <- HostMan.start
|
|
|
|
portpool <- PortPool.start kconfigPortPool
|
2013-07-14 16:30:55 +04:00
|
|
|
tf <- runThrow $ liftIO $ TempFolder.setup $ kconfigDir </> "temp"
|
|
|
|
plugins <- runThrow $ loadPlugins $ map ($ kconfigDir) mkPlugins
|
2013-07-10 13:48:46 +04:00
|
|
|
mainlog <- runThrow $ liftIO $ LogFile.openRotatingLog
|
2013-07-14 16:30:55 +04:00
|
|
|
(F.encodeString $ kconfigDir </> "log" </> "keter")
|
2013-07-10 13:48:46 +04:00
|
|
|
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"
|
|
|
|
]
|
2013-07-10 13:48:46 +04:00
|
|
|
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
|
2013-07-25 18:55:45 +04:00
|
|
|
V.mapM_ (forkIO . Proxy.reverseProxy
|
2013-07-14 16:30:55 +04:00
|
|
|
kconfigIpFromHeader
|
2013-06-03 15:15:13 +04:00
|
|
|
manager
|
2013-07-25 18:55:45 +04:00
|
|
|
(runKIOPrint . HostMan.lookupAction hostman)) kconfigListeners
|
2012-08-06 18:44:41 +04:00
|
|
|
|
2013-07-25 18:35:16 +04:00
|
|
|
appMan <- AppMan.initialize
|
|
|
|
let addApp bundle = AppMan.perform
|
|
|
|
appMan
|
|
|
|
(AppMan.AINamed $ getAppname bundle)
|
|
|
|
(AppMan.Reload AppMan.AIBundle)
|
|
|
|
terminateApp appname = AppMan.perform appMan (AppMan.AINamed appname) AppMan.Terminate
|
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
|
2013-07-25 18:35:16 +04:00
|
|
|
mapM_ addApp bundles0
|
2012-05-11 12:29:25 +04:00
|
|
|
|
2013-07-25 18:35:16 +04:00
|
|
|
unless (V.null kconfigBuiltinStanzas) $ AppMan.perform
|
|
|
|
appMan
|
|
|
|
AppMan.AIBuiltin
|
|
|
|
(AppMan.Reload $ AppMan.AIData $ BundleConfig kconfigBuiltinStanzas mempty)
|
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
|
2013-07-25 18:35:16 +04:00
|
|
|
Right fp -> when (isKeter fp) $ 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.
|
2013-07-25 18:35:16 +04:00
|
|
|
{- FIXME
|
2013-05-29 10:43:52 +04:00
|
|
|
_ <- flip (installHandler sigHUP) Nothing $ Catch $ do
|
2013-07-25 18:35:16 +04:00
|
|
|
actions <- do
|
2013-05-29 10:43:52 +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' $ F.encodeString bundle, (bundle, time))
|
|
|
|
|
2013-07-25 18:35:16 +04:00
|
|
|
current <- getAllApps appMan
|
|
|
|
let apps = Set.toList $ Set.fromList (Map.keys newMap) `Set.union` current
|
2013-05-29 10:43:52 +04:00
|
|
|
fmap catMaybes $ forM apps $ \appname -> return $
|
2013-07-25 18:35:16 +04:00
|
|
|
case (Set.member appname current, Map.lookup appname newMap) of
|
|
|
|
(False, Nothing) -> Nothing -- should never happen
|
|
|
|
(True, Nothing) -> Just $ terminateApp appname
|
|
|
|
(False, Just (bundle, _)) -> Just $ runKIO' $ addApp bundle
|
2013-05-29 10:43:52 +04:00
|
|
|
(Just (_, oldTime), Just (bundle, newTime))
|
|
|
|
| newTime /= oldTime -> Just $ runKIO' $ addApp bundle
|
|
|
|
| otherwise -> Nothing
|
|
|
|
P.sequence_ actions
|
2013-07-25 18:35:16 +04:00
|
|
|
-}
|
2013-05-29 10:43:52 +04:00
|
|
|
|
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
|