keter/Keter/App.hs

202 lines
7.3 KiB
Haskell
Raw Normal View History

2012-05-11 08:38:05 +04:00
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
2012-05-15 12:19:03 +04:00
{-# LANGUAGE NoImplicitPrelude #-}
2012-05-11 08:38:05 +04:00
module Keter.App
( App
, start
, reload
, Keter.App.terminate
) where
2012-05-15 12:19:03 +04:00
import Keter.Prelude
2012-05-11 08:38:05 +04:00
import Keter.TempFolder
import Keter.Postgres
import Keter.Process
import Keter.Nginx hiding (start)
import qualified Codec.Archive.Tar as Tar
import Codec.Compression.GZip (decompress)
2012-05-14 11:15:50 +04:00
import qualified Filesystem.Path.CurrentOS as F
2012-05-11 08:38:05 +04:00
import Data.Yaml
import Control.Applicative ((<$>), (<*>))
import System.PosixCompat.Files
import qualified Network
import Data.Maybe (fromMaybe)
2012-05-15 12:19:03 +04:00
import Control.Exception (onException)
2012-05-11 08:38:05 +04:00
import System.IO (hClose)
data Config = Config
2012-05-14 11:15:50 +04:00
{ configExec :: F.FilePath
, configArgs :: [Text]
2012-05-11 08:38:05 +04:00
, configHost :: String
2012-05-11 12:42:56 +04:00
, configPostgres :: Bool
2012-05-11 08:38:05 +04:00
}
instance FromJSON Config where
parseJSON (Object o) = Config
2012-05-14 11:15:50 +04:00
<$> (F.fromText <$> o .: "exec")
2012-05-11 08:38:05 +04:00
<*> o .:? "args" .!= []
<*> o .: "host"
2012-05-11 12:42:56 +04:00
<*> o .:? "postgres" .!= False
2012-05-11 08:38:05 +04:00
parseJSON _ = fail "Wanted an object"
data Command = Reload | Terminate
2012-05-15 12:19:03 +04:00
newtype App = App (Command -> KIO ())
2012-05-11 08:38:05 +04:00
unpackBundle :: TempFolder
2012-05-14 11:15:50 +04:00
-> F.FilePath
2012-05-11 08:38:05 +04:00
-> Appname
2012-05-15 12:19:03 +04:00
-> KIO (Either SomeException (FilePath, Config))
unpackBundle tf bundle appname = do
elbs <- readFileLBS bundle
case elbs of
Left e -> return $ Left e
Right lbs -> do
edir <- getFolder tf appname
case edir of
Left e -> return $ Left e
Right dir -> do
log $ UnpackingBundle bundle dir
let rest = do
Tar.unpack (F.encodeString dir) $ Tar.read $ decompress lbs
let configFP = dir F.</> "config" F.</> "keter.yaml"
Just config <- decodeFile $ F.encodeString configFP
return (dir, config)
liftIO $ rest `onException` removeTree dir
2012-05-11 08:38:05 +04:00
start :: TempFolder
-> Nginx
2012-05-11 12:42:56 +04:00
-> Postgres
2012-05-11 12:29:25 +04:00
-> Appname
2012-05-14 11:15:50 +04:00
-> F.FilePath -- ^ app bundle
2012-05-15 12:19:03 +04:00
-> KIO () -- ^ action to perform to remove this App from list of actives
-> KIO (App, KIO ())
2012-05-11 12:42:56 +04:00
start tf nginx postgres appname bundle removeFromList = do
2012-05-15 12:19:03 +04:00
chan <- newChan
return (App $ writeChan chan, rest chan)
2012-05-11 08:38:05 +04:00
where
runApp port dir config = do
2012-05-15 12:19:03 +04:00
res1 <- liftIO $ setFileMode (toString $ dir </> "config" </> configExec config) ownerExecuteMode
case res1 of
Left e -> log $ ExceptionThrown e
Right () -> return ()
2012-05-14 13:26:20 +04:00
otherEnv <- do
mdbi <-
if configPostgres config
then do
2012-05-15 12:19:03 +04:00
edbi <- getInfo postgres appname
2012-05-14 13:26:20 +04:00
case edbi of
Left e -> do
2012-05-15 12:19:03 +04:00
log $ ExceptionThrown e
2012-05-14 13:26:20 +04:00
return Nothing
Right dbi -> return $ Just dbi
else return Nothing
return $ case mdbi of
Just dbi ->
[ ("PGHOST", "localhost")
, ("PGPORT", "5432")
, ("PGUSER", dbiUser dbi)
, ("PGPASS", dbiPass dbi)
, ("PGDATABASE", dbiName dbi)
]
Nothing -> []
2012-05-15 12:19:03 +04:00
run
("config" </> configExec config)
dir
2012-05-11 08:38:05 +04:00
(configArgs config)
2012-05-15 12:19:03 +04:00
$ ("PORT", show port)
: ("APPROOT", "http://" ++ configHost config)
2012-05-11 12:42:56 +04:00
: otherEnv
2012-05-11 08:38:05 +04:00
2012-05-15 12:19:03 +04:00
rest chan = forkKIO $ do
2012-05-11 08:38:05 +04:00
mres <- unpackBundle tf bundle appname
case mres of
2012-05-15 12:19:03 +04:00
Left e -> do
log $ ExceptionThrown e
removeFromList
Right (dir, config) -> do
eport <- getPort nginx
2012-05-15 11:49:20 +04:00
case eport of
Left e -> do
2012-05-15 12:19:03 +04:00
log $ ExceptionThrown e
2012-05-11 08:38:05 +04:00
removeFromList
2012-05-15 11:49:20 +04:00
Right port -> do
process <- runApp port dir config
b <- testApp port
if b
then do
2012-05-15 12:19:03 +04:00
addEntry nginx (configHost config) $ AppEntry port
2012-05-15 11:49:20 +04:00
loop chan dir process port config
else do
removeFromList
2012-05-15 12:19:03 +04:00
releasePort nginx port
Keter.Process.terminate process
2012-05-11 08:38:05 +04:00
loop chan dirOld processOld portOld configOld = do
2012-05-15 12:19:03 +04:00
command <- readChan chan
2012-05-11 08:38:05 +04:00
case command of
Terminate -> do
removeFromList
2012-05-15 12:19:03 +04:00
removeEntry nginx $ configHost configOld
log $ TerminatingApp appname
2012-05-11 08:38:05 +04:00
terminateOld
Reload -> do
mres <- unpackBundle tf bundle appname
case mres of
2012-05-15 12:19:03 +04:00
Left e -> do
log $ InvalidBundle bundle e
2012-05-11 08:38:05 +04:00
loop chan dirOld processOld portOld configOld
2012-05-15 12:19:03 +04:00
Right (dir, config) -> do
eport <- getPort nginx
2012-05-15 11:49:20 +04:00
case eport of
2012-05-15 12:19:03 +04:00
Left e -> log $ ExceptionThrown e
2012-05-15 11:49:20 +04:00
Right port -> do
process <- runApp port dir config
b <- testApp port
if b
then do
2012-05-15 12:19:03 +04:00
addEntry nginx (configHost config) $ AppEntry port
2012-05-15 11:49:20 +04:00
when (configHost config /= configHost configOld) $
2012-05-15 12:19:03 +04:00
removeEntry nginx $ configHost configOld
log $ FinishedReloading appname
2012-05-15 11:49:20 +04:00
terminateOld
loop chan dir process port config
else do
2012-05-15 12:19:03 +04:00
releasePort nginx port
Keter.Process.terminate process
log $ ProcessDidNotStart bundle
2012-05-15 11:49:20 +04:00
loop chan dirOld processOld portOld configOld
2012-05-11 08:38:05 +04:00
where
2012-05-15 12:19:03 +04:00
terminateOld = forkKIO $ do
2012-05-11 08:38:05 +04:00
threadDelay $ 20 * 1000 * 1000
2012-05-15 12:19:03 +04:00
log $ TerminatingOldProcess appname
Keter.Process.terminate processOld
2012-05-11 08:38:05 +04:00
threadDelay $ 60 * 1000 * 1000
2012-05-15 12:19:03 +04:00
log $ RemovingOldFolder dirOld
res <- liftIO $ removeTree dirOld
case res of
Left e -> log $ ExceptionThrown e
Right () -> return ()
2012-05-14 12:03:57 +04:00
2012-05-15 12:19:03 +04:00
testApp :: Port -> KIO Bool
2012-05-11 08:38:05 +04:00
testApp port = do
res <- timeout (90 * 1000 * 1000) testApp'
return $ fromMaybe False res
where
testApp' = do
threadDelay $ 2 * 1000 * 1000
2012-05-15 12:19:03 +04:00
eres <- liftIO $ Network.connectTo "127.0.0.1" $ Network.PortNumber $ fromIntegral port
2012-05-11 08:38:05 +04:00
case eres of
2012-05-15 12:19:03 +04:00
Left _ -> testApp'
2012-05-11 08:38:05 +04:00
Right handle -> do
2012-05-15 12:19:03 +04:00
res <- liftIO $ hClose handle
case res of
Left e -> log $ ExceptionThrown e
Right () -> return ()
2012-05-11 08:38:05 +04:00
return True
2012-05-15 12:19:03 +04:00
reload :: App -> KIO ()
2012-05-11 08:38:05 +04:00
reload (App f) = f Reload
2012-05-15 12:19:03 +04:00
terminate :: App -> KIO ()
2012-05-11 08:38:05 +04:00
terminate (App f) = f Terminate