keter/Keter/AppManager.hs

255 lines
10 KiB
Haskell
Raw Normal View History

2013-07-26 11:09:11 +04:00
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
2013-07-25 18:35:16 +04:00
-- | Used for management of applications.
module Keter.AppManager
( -- * Types
AppManager
, Action (..)
-- * Actions
, perform
2013-07-26 11:09:11 +04:00
, reloadAppList
2013-07-26 12:17:05 +04:00
, addApp
, terminateApp
2013-07-25 18:35:16 +04:00
-- * Initialize
, initialize
) where
import Control.Applicative
2013-07-28 14:41:42 +04:00
import Control.Concurrent (forkIO)
import Control.Concurrent.MVar (MVar, newMVar, withMVar)
2013-07-25 18:35:16 +04:00
import Control.Concurrent.STM
2013-07-28 14:41:42 +04:00
import qualified Control.Exception as E
import Control.Monad (void)
import qualified Data.Map as Map
import Data.Maybe (mapMaybe)
import Data.Maybe (catMaybes)
import qualified Data.Set as Set
2013-07-26 12:17:05 +04:00
import qualified Filesystem.Path.CurrentOS as F
2013-07-28 16:19:08 +04:00
import Keter.App (App, AppStartConfig)
2013-07-28 14:41:42 +04:00
import qualified Keter.App as App
import Keter.Types
import Prelude hiding (FilePath, log)
import System.Posix.Files (getFileStatus, modificationTime)
import System.Posix.Types (EpochTime)
2013-07-25 18:35:16 +04:00
data AppManager = AppManager
2013-07-26 11:09:11 +04:00
{ apps :: !(TVar (Map AppId (TVar AppState)))
, appStartConfig :: !AppStartConfig
, mutex :: !(MVar ())
2013-07-28 14:41:42 +04:00
, log :: !(LogMessage -> IO ())
2013-07-25 18:35:16 +04:00
}
2013-07-26 11:09:11 +04:00
data AppState = ASRunning App
| ASStarting
!(Maybe App)
!(TVar (Maybe EpochTime))
!(TVar (Maybe Action)) -- ^ the next one to try
2013-07-26 09:40:53 +04:00
| ASTerminated
2013-07-25 18:35:16 +04:00
data Action = Reload AppInput | Terminate
2013-07-28 14:41:42 +04:00
initialize :: (LogMessage -> IO ())
-> AppStartConfig
-> IO AppManager
initialize log' asc = AppManager
2013-07-25 18:35:16 +04:00
<$> newTVarIO Map.empty
2013-07-26 11:09:11 +04:00
<*> return asc
<*> newMVar ()
2013-07-28 14:41:42 +04:00
<*> return log'
2013-07-26 11:09:11 +04:00
-- | Reset which apps are running.
--
-- * Any app not listed here that is currently running will be terminated.
--
-- * Any app listed here that is currently running will be reloaded.
--
-- * Any app listed here that is not currently running will be started.
reloadAppList :: AppManager
2013-07-28 14:41:42 +04:00
-> Map Appname (FilePath, EpochTime)
2013-07-26 11:09:11 +04:00
-> IO ()
reloadAppList am@AppManager {..} newApps = withMVar mutex $ const $ do
actions <- atomically $ do
m <- readTVar apps
let currentApps = Set.fromList $ mapMaybe toAppName $ Map.keys m
allApps = Set.toList $ Map.keysSet newApps `Set.union` currentApps
fmap catMaybes $ mapM (getAction m) allApps
sequence_ actions
where
toAppName AIBuiltin = Nothing
toAppName (AINamed x) = Just x
getAction currentApps appname = do
case Map.lookup (AINamed appname) currentApps of
Nothing -> return freshLaunch
Just tstate -> do
state <- readTVar tstate
case state of
ASTerminated -> return freshLaunch
ASRunning app ->
case Map.lookup appname newApps of
Nothing -> return terminate
Just (fp, newTimestamp) -> do
moldTimestamp <- App.getTimestamp app
return $ if moldTimestamp == Just newTimestamp
then Nothing
else reload fp newTimestamp
ASStarting _ tmoldTimestamp tmaction ->
case Map.lookup appname newApps of
Nothing -> do
writeTVar tmaction $ Just Terminate
return Nothing
Just (fp, newTimestamp) -> do
moldTimestamp <- readTVar tmoldTimestamp
return $ if moldTimestamp == Just newTimestamp
then Nothing
else reload fp newTimestamp
where
freshLaunch =
case Map.lookup appname newApps of
Nothing -> E.assert False Nothing
Just (fp, timestamp) -> reload fp timestamp
terminate = Just $ performNoLock am (AINamed appname) Terminate
reload fp timestamp = Just $ performNoLock am (AINamed appname) (Reload $ AIBundle fp timestamp)
{-
case (Map.lookup appname currentApps, Map.lookup appname newApps) of
(Nothing, Nothing) -> E.assert False Nothing
(Just _, Nothing) -> Just $ perform am (AINamed appname) Terminate
(Nothing, Just _) -> Just $ perform am (AINamed appname) (Reload AIBundle)
-}
{- FIXME
actions <- do
current <- getAllApps appMan
let apps = Set.toList $ Set.fromList (Map.keys newMap) `Set.union` current
fmap catMaybes $ forM apps $ \appname -> return $
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
(Just (_, oldTime), Just (bundle, newTime))
| newTime /= oldTime -> Just $ runKIO' $ addApp bundle
| otherwise -> Nothing
P.sequence_ actions
2013-07-25 18:35:16 +04:00
getAllApps :: AppManager -> IO (Set Appname)
getAllApps AppManager {..} = atomically $ do
m <- readTVar apps
return $ Set.fromList $ mapMaybe toAppName $ Map.keys m
2013-07-26 11:09:11 +04:00
-}
2013-07-25 18:35:16 +04:00
perform :: AppManager -> AppId -> Action -> IO ()
2013-07-26 11:09:11 +04:00
perform am appid action = withMVar (mutex am) $ const $ performNoLock am appid action
performNoLock :: AppManager -> AppId -> Action -> IO ()
performNoLock am@AppManager {..} aid action = E.mask_ $ do
2013-07-25 20:58:54 +04:00
launchWorker' <- atomically $ do
2013-07-25 18:35:16 +04:00
m <- readTVar apps
2013-07-25 20:58:54 +04:00
case Map.lookup aid m of
2013-07-25 18:35:16 +04:00
Just tstate -> do
state <- readTVar tstate
case state of
2013-07-26 11:09:11 +04:00
ASStarting _mcurrent _tmtimestamp tmnext -> do
2013-07-25 20:58:54 +04:00
writeTVar tmnext $ Just action
2013-07-25 18:35:16 +04:00
-- use the previous worker, so nothing to do
2013-07-25 20:58:54 +04:00
return noWorker
2013-07-25 18:35:16 +04:00
ASRunning runningApp -> do
tmnext <- newTVar Nothing
2013-07-26 11:09:11 +04:00
tmtimestamp <- newTVar $
case action of
Reload (AIBundle _fp timestamp) -> Just timestamp
Reload (AIData _) -> Nothing
Terminate -> Nothing
writeTVar tstate $ ASStarting (Just runningApp) tmtimestamp tmnext
return $ launchWorker am aid tstate tmnext (Just runningApp) action
2013-07-26 09:40:53 +04:00
ASTerminated -> onNotRunning
Nothing -> onNotRunning
2013-07-25 18:35:16 +04:00
launchWorker'
where
2013-07-25 20:58:54 +04:00
noWorker = return ()
2013-07-26 09:40:53 +04:00
onNotRunning =
case action of
2013-07-26 11:09:11 +04:00
Reload input -> do
2013-07-26 09:40:53 +04:00
tmnext <- newTVar Nothing
2013-07-26 11:09:11 +04:00
tmtimestamp <- newTVar $
case input of
AIBundle _fp timestamp -> Just timestamp
AIData _ -> Nothing
tstate <- newTVar $ ASStarting Nothing tmtimestamp tmnext
2013-07-26 09:40:53 +04:00
modifyTVar apps $ Map.insert aid tstate
2013-07-26 11:09:11 +04:00
return $ launchWorker am aid tstate tmnext Nothing action
2013-07-26 09:40:53 +04:00
Terminate -> return noWorker
2013-07-25 20:58:54 +04:00
launchWorker :: AppManager
2013-07-26 11:09:11 +04:00
-> AppId
2013-07-25 20:58:54 +04:00
-> TVar AppState
2013-07-26 09:40:53 +04:00
-> TVar (Maybe Action)
2013-07-26 11:09:11 +04:00
-> Maybe App
2013-07-25 20:58:54 +04:00
-> Action
-> IO ()
2013-07-26 11:09:11 +04:00
launchWorker AppManager {..} appid tstate tmnext mcurrentApp0 action0 = void $ forkIO $ do
loop mcurrentApp0 action0
2013-07-26 09:40:53 +04:00
where
2013-07-26 11:09:11 +04:00
loop mcurrentApp action = do
mRunningApp <- processAction mcurrentApp action
2013-07-26 09:40:53 +04:00
mnext <- atomically $ do
mnext <- readTVar tmnext
writeTVar tmnext Nothing
case mnext of
Nothing ->
case mRunningApp of
Nothing -> writeTVar tstate ASTerminated
Just runningApp -> writeTVar tstate $ ASRunning runningApp
2013-07-28 16:19:08 +04:00
Just _next -> do
2013-07-26 11:09:11 +04:00
tmtimestamp <- newTVar $
case action of
Reload (AIBundle _fp timestamp) -> Just timestamp
Reload (AIData _) -> Nothing
Terminate -> Nothing
writeTVar tstate $ ASStarting mRunningApp tmtimestamp tmnext
2013-07-26 09:40:53 +04:00
return mnext
case mnext of
Nothing -> return ()
2013-07-28 14:41:42 +04:00
Just next -> loop mRunningApp next
2013-07-26 11:09:11 +04:00
processAction Nothing Terminate = return Nothing
processAction (Just app) Terminate = do
2013-07-28 14:41:42 +04:00
App.terminate app
2013-07-26 11:09:11 +04:00
return Nothing
2013-07-28 14:41:42 +04:00
processAction Nothing (Reload input) = do
eres <- E.try $ App.start appStartConfig appid input
2013-07-26 11:09:11 +04:00
case eres of
Left e -> do
2013-07-28 14:41:42 +04:00
log $ ErrorStartingBundle name e
2013-07-26 11:09:11 +04:00
return Nothing
Right app -> return $ Just app
2013-07-28 14:41:42 +04:00
processAction (Just app) (Reload input) = do
2014-12-18 09:06:58 +03:00
eres <- E.try $ App.reload app input
case eres of
Left e -> do
log $ ErrorStartingBundle name e
-- reloading will /always/ result in a valid app, either the old one
-- will continue running or the new one will replace it.
return (Just app)
Right () -> return $ Just app
name =
case appid of
AIBuiltin -> "<builtin>"
AINamed x -> x
2013-07-26 12:17:05 +04:00
2013-07-28 14:41:42 +04:00
addApp :: AppManager -> FilePath -> IO ()
2013-07-26 12:17:05 +04:00
addApp appMan bundle = do
(input, action) <- getInputForBundle bundle
perform appMan input action
2013-07-28 14:41:42 +04:00
getInputForBundle :: FilePath -> IO (AppId, Action)
2013-07-26 12:17:05 +04:00
getInputForBundle bundle = do
time <- modificationTime <$> getFileStatus (F.encodeString bundle)
return (AINamed $ getAppname bundle, Reload $ AIBundle bundle time)
2013-07-28 14:41:42 +04:00
terminateApp :: AppManager -> Appname -> IO ()
2013-07-26 12:17:05 +04:00
terminateApp appMan appname = perform appMan (AINamed appname) Terminate