2014-04-10 21:22:32 +00:00
|
|
|
{-# LANGUAGE PackageImports #-}
|
|
|
|
|
2014-03-31 22:31:08 +00:00
|
|
|
module Propellor.Message where
|
|
|
|
|
|
|
|
import System.Console.ANSI
|
|
|
|
import System.IO
|
2014-04-01 15:59:48 +00:00
|
|
|
import System.Log.Logger
|
2014-11-18 22:44:24 +00:00
|
|
|
import System.Log.Formatter
|
|
|
|
import System.Log.Handler (setFormatter, LogHandler)
|
|
|
|
import System.Log.Handler.Simple
|
2014-04-10 21:22:32 +00:00
|
|
|
import "mtl" Control.Monad.Reader
|
2014-11-18 21:53:42 +00:00
|
|
|
import Data.Maybe
|
|
|
|
import Control.Applicative
|
2014-03-31 22:31:08 +00:00
|
|
|
|
|
|
|
import Propellor.Types
|
2014-11-18 04:19:11 +00:00
|
|
|
import Utility.Monad
|
2014-11-18 21:53:42 +00:00
|
|
|
import Utility.Env
|
2014-11-20 01:48:48 +00:00
|
|
|
import Utility.FileSystemEncoding
|
2014-11-18 04:19:11 +00:00
|
|
|
|
|
|
|
data MessageHandle
|
|
|
|
= ConsoleMessageHandle
|
|
|
|
| TextMessageHandle
|
|
|
|
|
|
|
|
mkMessageHandle :: IO MessageHandle
|
2014-11-20 01:48:48 +00:00
|
|
|
mkMessageHandle = do
|
|
|
|
fileEncoding stdout
|
|
|
|
ifM (hIsTerminalDevice stdout <||> (isJust <$> getEnv "PROPELLOR_CONSOLE"))
|
|
|
|
( return ConsoleMessageHandle
|
|
|
|
, return TextMessageHandle
|
|
|
|
)
|
2014-11-18 04:19:11 +00:00
|
|
|
|
2014-11-18 21:53:42 +00:00
|
|
|
forceConsole :: IO ()
|
|
|
|
forceConsole = void $ setEnv "PROPELLOR_CONSOLE" "1" True
|
|
|
|
|
|
|
|
isConsole :: MessageHandle -> Bool
|
|
|
|
isConsole ConsoleMessageHandle = True
|
|
|
|
isConsole _ = False
|
|
|
|
|
2014-11-18 04:19:11 +00:00
|
|
|
whenConsole :: MessageHandle -> IO () -> IO ()
|
|
|
|
whenConsole ConsoleMessageHandle a = a
|
|
|
|
whenConsole _ _ = return ()
|
2014-03-31 22:31:08 +00:00
|
|
|
|
|
|
|
-- | Shows a message while performing an action, with a colored status
|
|
|
|
-- display.
|
2014-04-10 21:22:32 +00:00
|
|
|
actionMessage :: (MonadIO m, ActionResult r) => Desc -> m r -> m r
|
2014-05-31 22:52:42 +00:00
|
|
|
actionMessage = actionMessage' Nothing
|
|
|
|
|
|
|
|
-- | Shows a message while performing an action on a specified host,
|
|
|
|
-- with a colored status display.
|
|
|
|
actionMessageOn :: (MonadIO m, ActionResult r) => HostName -> Desc -> m r -> m r
|
|
|
|
actionMessageOn = actionMessage' . Just
|
|
|
|
|
|
|
|
actionMessage' :: (MonadIO m, ActionResult r) => Maybe HostName -> Desc -> m r -> m r
|
|
|
|
actionMessage' mhn desc a = do
|
2014-11-18 04:19:11 +00:00
|
|
|
h <- liftIO mkMessageHandle
|
|
|
|
liftIO $ whenConsole h $ do
|
2014-04-10 21:22:32 +00:00
|
|
|
setTitle $ "propellor: " ++ desc
|
|
|
|
hFlush stdout
|
2014-03-31 22:31:08 +00:00
|
|
|
|
|
|
|
r <- a
|
|
|
|
|
2014-04-10 21:22:32 +00:00
|
|
|
liftIO $ do
|
2014-11-18 04:19:11 +00:00
|
|
|
whenConsole h $
|
|
|
|
setTitle "propellor: running"
|
2014-11-20 01:20:19 +00:00
|
|
|
putStr propellorSigel
|
2014-11-18 04:19:11 +00:00
|
|
|
showhn h mhn
|
2014-04-10 21:22:32 +00:00
|
|
|
putStr $ desc ++ " ... "
|
2014-05-31 22:52:42 +00:00
|
|
|
let (msg, intensity, color) = getActionResult r
|
2014-11-18 04:19:11 +00:00
|
|
|
colorLine h intensity color msg
|
2014-04-10 21:22:32 +00:00
|
|
|
hFlush stdout
|
2014-03-31 22:31:08 +00:00
|
|
|
|
|
|
|
return r
|
2014-05-31 22:52:42 +00:00
|
|
|
where
|
2014-11-18 04:19:11 +00:00
|
|
|
showhn _ Nothing = return ()
|
|
|
|
showhn h (Just hn) = do
|
|
|
|
whenConsole h $
|
|
|
|
setSGR [SetColor Foreground Dull Cyan]
|
2014-05-31 22:52:42 +00:00
|
|
|
putStr (hn ++ " ")
|
2014-11-18 04:19:11 +00:00
|
|
|
whenConsole h $
|
|
|
|
setSGR []
|
2014-03-31 22:31:08 +00:00
|
|
|
|
2014-04-10 21:22:32 +00:00
|
|
|
warningMessage :: MonadIO m => String -> m ()
|
2014-11-18 04:19:11 +00:00
|
|
|
warningMessage s = liftIO $ do
|
|
|
|
h <- mkMessageHandle
|
2014-11-20 01:20:19 +00:00
|
|
|
colorLine h Vivid Magenta $ propellorSigel ++ "** warning: " ++ s
|
2014-04-04 04:18:51 +00:00
|
|
|
|
2014-11-18 04:19:11 +00:00
|
|
|
errorMessage :: MonadIO m => String -> m a
|
|
|
|
errorMessage s = liftIO $ do
|
|
|
|
h <- mkMessageHandle
|
2014-11-20 01:20:19 +00:00
|
|
|
colorLine h Vivid Red $ propellorSigel ++ "** error: " ++ s
|
2014-11-18 04:19:11 +00:00
|
|
|
error "Cannot continue!"
|
|
|
|
|
|
|
|
colorLine :: MessageHandle -> ColorIntensity -> Color -> String -> IO ()
|
|
|
|
colorLine h intensity color msg = do
|
|
|
|
whenConsole h $
|
|
|
|
setSGR [SetColor Foreground intensity color]
|
2014-04-04 04:18:51 +00:00
|
|
|
putStr msg
|
2014-11-18 04:19:11 +00:00
|
|
|
whenConsole h $
|
|
|
|
setSGR []
|
2014-04-04 04:18:51 +00:00
|
|
|
-- Note this comes after the color is reset, so that
|
|
|
|
-- the color set and reset happen in the same line.
|
|
|
|
putStrLn ""
|
2014-03-31 22:31:08 +00:00
|
|
|
hFlush stdout
|
|
|
|
|
2014-04-01 15:59:48 +00:00
|
|
|
-- | Causes a debug message to be displayed when PROPELLOR_DEBUG=1
|
|
|
|
debug :: [String] -> IO ()
|
|
|
|
debug = debugM "propellor" . unwords
|
2014-11-18 22:44:24 +00:00
|
|
|
|
|
|
|
checkDebugMode :: IO ()
|
|
|
|
checkDebugMode = go =<< getEnv "PROPELLOR_DEBUG"
|
|
|
|
where
|
|
|
|
go (Just "1") = do
|
|
|
|
f <- setFormatter
|
|
|
|
<$> streamHandler stderr DEBUG
|
|
|
|
<*> pure (simpleLogFormatter "[$time] $msg")
|
|
|
|
updateGlobalLogger rootLoggerName $
|
|
|
|
setLevel DEBUG . setHandlers [f]
|
|
|
|
go _ = noop
|
2014-11-20 01:20:19 +00:00
|
|
|
|
|
|
|
-- Unicode propellor.
|
|
|
|
propellorSigel :: String
|
|
|
|
propellorSigel = "ꕤ "
|