keter/Keter/HostManager.hs

183 lines
6.7 KiB
Haskell
Raw Normal View History

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
2013-07-30 18:49:01 +04:00
{-# LANGUAGE ViewPatterns #-}
2013-07-25 14:07:48 +04:00
module Keter.HostManager
( -- * Types
HostManager
, Reservations
-- * Actions
, reserveHosts
, forgetReservations
, activateApp
2013-07-28 21:16:01 +04:00
, deactivateApp
2013-07-28 21:47:22 +04:00
, reactivateApp
, lookupAction
-- * Initialize
, start
) where
import Control.Applicative
2013-07-30 18:49:01 +04:00
import Control.Exception (assert, throwIO)
2014-09-21 11:42:26 +04:00
import qualified Data.CaseInsensitive as CI
2013-07-30 18:49:01 +04:00
import Data.Either (partitionEithers)
2013-07-28 14:41:42 +04:00
import Data.IORef
2013-07-30 18:49:01 +04:00
import qualified Data.Map as Map
import qualified Data.Set as Set
import Data.Text.Encoding (encodeUtf8)
import Keter.Types
2013-08-28 20:37:53 +04:00
import Keter.LabelMap (LabelMap)
import qualified Keter.LabelMap as LabelMap
2014-06-09 14:30:54 +04:00
import Prelude hiding (log)
type HMState = LabelMap HostValue
2013-08-28 20:37:53 +04:00
data HostValue = HVActive !AppId !ProxyAction
2013-07-28 16:19:08 +04:00
| HVReserved !AppId
2013-07-28 14:41:42 +04:00
newtype HostManager = HostManager (IORef HMState)
type Reservations = Set.Set Host
start :: IO HostManager
start = HostManager <$> newIORef LabelMap.empty
-- | Reserve the given hosts so that no other application may use them. Does
-- not yet enable any action. The semantics are:
--
-- 1. If a requested host is currently actively used or by an app of the same name, it is
-- considered reserved.
--
-- 2. If a requested host is currently reserved by an app of the same name, it
-- is considered an error in calling this API. Only one app reservation can
-- happen at a time.
--
-- 3. If any requested host is currently used or reserved by an app with a
-- different name, then those values are returned as @Left@.
--
-- 4. Otherwise, the hosts which were reserved are returned as @Right@. This
-- does /not/ include previously active hosts.
2013-07-30 18:49:01 +04:00
reserveHosts :: (LogMessage -> IO ())
-> HostManager
2013-07-28 16:19:08 +04:00
-> AppId
-> Set.Set Host
2013-07-28 16:19:08 +04:00
-> IO Reservations
2013-07-30 18:49:01 +04:00
reserveHosts log (HostManager mstate) aid hosts = do
log $ ReservingHosts aid hosts
either (throwIO . CannotReserveHosts aid) return =<< atomicModifyIORef mstate (\entries0 ->
2013-07-28 14:41:42 +04:00
case partitionEithers $ map (checkHost entries0) $ Set.toList hosts of
2013-07-30 18:49:01 +04:00
([], Set.unions -> toReserve) ->
(Set.foldr reserve entries0 toReserve, Right toReserve)
2013-07-28 16:19:08 +04:00
(conflicts, _) -> (entries0, Left $ Map.fromList conflicts))
where
checkHost entries0 host =
case LabelMap.labelAssigned hostBS entries0 of
False -> Right $ Set.singleton host
True ->
case LabelMap.lookup hostBS entries0 of
Nothing -> Right $ Set.singleton host
Just (HVReserved aid') -> assert (aid /= aid')
$ Left (host, aid')
Just (HVActive aid' _)
| aid == aid' -> Right Set.empty
| otherwise -> Left (host, aid')
2014-09-21 11:42:26 +04:00
where hostBS = encodeUtf8 $ CI.original host
2013-07-28 16:19:08 +04:00
hvres = HVReserved aid
reserve host es =
assert (not $ LabelMap.labelAssigned hostBS es) $ LabelMap.insert hostBS hvres es
where
2014-09-21 11:42:26 +04:00
hostBS = encodeUtf8 $ CI.original host
-- | Forget previously made reservations.
2013-07-30 18:49:01 +04:00
forgetReservations :: (LogMessage -> IO ())
-> HostManager
2013-07-28 16:19:08 +04:00
-> AppId
-> Reservations
2013-07-28 14:41:42 +04:00
-> IO ()
2013-07-30 18:49:01 +04:00
forgetReservations log (HostManager mstate) app hosts = do
log $ ForgetingReservations app hosts
atomicModifyIORef mstate $ \state0 ->
(Set.foldr forget state0 hosts, ())
where
forget host state =
assert isReservedByMe $ LabelMap.delete hostBS state
where
2014-09-21 11:42:26 +04:00
hostBS = encodeUtf8 $ CI.original host
isReservedByMe = LabelMap.labelAssigned hostBS state &&
case LabelMap.lookup hostBS state of
Nothing -> False
Just (HVReserved app') -> app == app'
Just HVActive{} -> False
2012-10-21 09:07:26 +04:00
-- | Activate a new app. Note that you /must/ first reserve the hostnames you'll be using.
2013-07-30 18:49:01 +04:00
activateApp :: (LogMessage -> IO ())
-> HostManager
2013-07-28 16:19:08 +04:00
-> AppId
-> Map.Map Host ProxyAction
2013-07-28 14:41:42 +04:00
-> IO ()
2013-07-30 18:49:01 +04:00
activateApp log (HostManager mstate) app actions = do
log $ ActivatingApp app $ Map.keysSet actions
atomicModifyIORef mstate $ \state0 ->
(activateHelper app state0 actions, ())
2013-07-28 21:47:22 +04:00
activateHelper :: AppId -> HMState -> Map Host ProxyAction -> HMState
activateHelper app =
Map.foldrWithKey activate
where
activate host action state =
assert isOwnedByMe $ LabelMap.insert hostBS (HVActive app action) state
where
2014-09-21 11:42:26 +04:00
hostBS = encodeUtf8 $ CI.original host
isOwnedByMe = LabelMap.labelAssigned hostBS state &&
case LabelMap.lookup hostBS state of
Nothing -> False
Just (HVReserved app') -> app == app'
Just (HVActive app' _) -> app == app'
2013-07-30 18:49:01 +04:00
deactivateApp :: (LogMessage -> IO ())
-> HostManager
2013-07-28 21:16:01 +04:00
-> AppId
-> Set Host
-> IO ()
2013-07-30 18:49:01 +04:00
deactivateApp log (HostManager mstate) app hosts = do
log $ DeactivatingApp app hosts
atomicModifyIORef mstate $ \state0 ->
(deactivateHelper app state0 hosts, ())
2013-07-28 21:47:22 +04:00
deactivateHelper :: AppId -> HMState -> Set Host -> HMState
deactivateHelper app =
Set.foldr deactivate
2013-07-28 21:16:01 +04:00
where
deactivate host state =
assert isOwnedByMe $ LabelMap.delete hostBS state
2013-07-28 21:16:01 +04:00
where
2014-09-21 11:42:26 +04:00
hostBS = encodeUtf8 $ CI.original host
isOwnedByMe = LabelMap.labelAssigned hostBS state &&
case LabelMap.lookup hostBS state of
2013-07-28 21:16:01 +04:00
Nothing -> False
Just (HVActive app' _) -> app == app'
Just HVReserved {} -> False
2013-07-30 18:49:01 +04:00
reactivateApp :: (LogMessage -> IO ())
-> HostManager
2013-07-28 21:47:22 +04:00
-> AppId
-> Map Host ProxyAction
-> Set Host
-> IO ()
2013-07-30 18:49:01 +04:00
reactivateApp log (HostManager mstate) app actions hosts = do
log $ ReactivatingApp app hosts (Map.keysSet actions)
atomicModifyIORef mstate $ \state0 ->
(activateHelper app (deactivateHelper app state0 hosts) actions, ())
2013-07-28 21:47:22 +04:00
lookupAction :: HostManager
-> HostBS
2013-07-26 12:17:05 +04:00
-> IO (Maybe ProxyAction)
2013-07-28 14:41:42 +04:00
lookupAction (HostManager mstate) host = do
state <- readIORef mstate
2014-09-21 11:42:26 +04:00
return $ case LabelMap.lookup (CI.original host) state of
Nothing -> Nothing
Just (HVActive _ action) -> Just action
Just (HVReserved _) -> Nothing