Skip to content

Commit aac2c81

Browse files
committed
Clean up -v output, use ansi codes
1 parent 55b9ff6 commit aac2c81

File tree

1 file changed

+71
-46
lines changed

1 file changed

+71
-46
lines changed

src/Stack/Types/StackT.hs

Lines changed: 71 additions & 46 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@
88
{-# LANGUAGE OverloadedStrings #-}
99
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
1010
{-# LANGUAGE RecordWildCards #-}
11+
{-# LANGUAGE TemplateHaskell #-}
1112
{-# OPTIONS_GHC -fno-warn-orphans #-}
1213

1314
-- | The monad used for the command-line executable @stack@.
@@ -33,10 +34,11 @@ import Control.Monad.Base
3334
import Control.Monad.Catch
3435
import Control.Monad.IO.Class
3536
import Control.Monad.Logger
36-
import Control.Monad.Reader
37+
import Control.Monad.Reader hiding (lift)
3738
import Control.Monad.Trans.Control
3839
import qualified Data.ByteString.Char8 as S8
3940
import Data.Char
41+
import Data.List (stripPrefix)
4042
import Data.Maybe
4143
import Data.Monoid
4244
import Data.Text (Text)
@@ -47,14 +49,15 @@ import qualified Data.Text.IO as T
4749
import Data.Time
4850
import GHC.Foreign (withCString, peekCString)
4951
import Language.Haskell.TH
52+
import Language.Haskell.TH.Syntax (lift)
5053
import Network.HTTP.Client.Conduit (HasHttpManager(..))
5154
import Network.HTTP.Conduit
5255
import Prelude -- Fix AMP warning
53-
import Stack.Types.Internal
5456
import Stack.Types.Config (GlobalOpts (..))
57+
import Stack.Types.Internal
58+
import System.Console.ANSI
5559
import System.IO
5660
import System.Log.FastLogger
57-
import System.Console.ANSI (hSupportsANSI)
5861

5962
#ifndef MIN_VERSION_time
6063
#define MIN_VERSION_time(x, y, z) 0
@@ -226,29 +229,31 @@ newTLSManager = liftIO $ newManager tlsManagerSettings
226229
--------------------------------------------------------------------------------
227230
-- Logging functionality
228231
stickyLoggerFunc
229-
:: (HasSticky r, HasLogLevel r, HasSupportsUnicode r, ToLogStr msg, MonadReader r m, MonadIO m)
232+
:: (HasSticky r, HasLogLevel r, HasSupportsUnicode r, HasTerminal r, ToLogStr msg, MonadReader r m, MonadIO m)
230233
=> Loc -> LogSource -> LogLevel -> msg -> m ()
231234
stickyLoggerFunc loc src level msg = do
232235
func <- getStickyLoggerFunc
233236
liftIO $ func loc src level msg
234237

235238
getStickyLoggerFunc
236-
:: (HasSticky r, HasLogLevel r, HasSupportsUnicode r, ToLogStr msg, MonadReader r m)
239+
:: (HasSticky r, HasLogLevel r, HasSupportsUnicode r, HasTerminal r, ToLogStr msg, MonadReader r m)
237240
=> m (Loc -> LogSource -> LogLevel -> msg -> IO ())
238241
getStickyLoggerFunc = do
239242
sticky <- asks getSticky
240243
logLevel <- asks getLogLevel
241244
supportsUnicode <- asks getSupportsUnicode
242-
return $ stickyLoggerFuncImpl sticky logLevel supportsUnicode
245+
supportsAnsi <- asks getAnsiTerminal
246+
return $ stickyLoggerFuncImpl sticky logLevel supportsUnicode supportsAnsi
243247

244248
stickyLoggerFuncImpl
245249
:: ToLogStr msg
246-
=> Sticky -> LogLevel -> Bool
250+
=> Sticky -> LogLevel -> Bool -> Bool
247251
-> (Loc -> LogSource -> LogLevel -> msg -> IO ())
248-
stickyLoggerFuncImpl (Sticky mref) maxLogLevel supportsUnicode loc src level msg =
252+
stickyLoggerFuncImpl (Sticky mref) maxLogLevel supportsUnicode supportsAnsi loc src level msg =
249253
case mref of
250254
Nothing ->
251255
loggerFunc
256+
supportsAnsi
252257
maxLogLevel
253258
out
254259
loc
@@ -287,7 +292,7 @@ stickyLoggerFuncImpl (Sticky mref) maxLogLevel supportsUnicode loc src level msg
287292
_
288293
| level >= maxLogLevel -> do
289294
clear
290-
loggerFunc maxLogLevel out loc src level $ toLogStr msgText
295+
loggerFunc supportsAnsi maxLogLevel out loc src level $ toLogStr msgText
291296
case sticky of
292297
Nothing ->
293298
return Nothing
@@ -310,46 +315,66 @@ replaceUnicode c = c
310315

311316
-- | Logging function takes the log level into account.
312317
loggerFunc :: ToLogStr msg
313-
=> LogLevel -> Handle -> Loc -> Text -> LogLevel -> msg -> IO ()
314-
loggerFunc maxLogLevel outputChannel loc _src level msg =
318+
=> Bool -> LogLevel -> Handle -> Loc -> Text -> LogLevel -> msg -> IO ()
319+
loggerFunc supportsAnsi maxLogLevel outputChannel loc _src level msg =
315320
when (level >= maxLogLevel)
316321
(liftIO (do out <- getOutput
317322
T.hPutStrLn outputChannel out))
318-
where getOutput =
319-
do timestamp <- getTimestamp
320-
l <- getLevel
321-
lc <- getLoc
322-
return (T.pack timestamp <> T.pack l <> T.decodeUtf8 (fromLogStr (toLogStr msg)) <> T.pack lc)
323-
where getTimestamp
324-
| maxLogLevel <= LevelDebug =
325-
do now <- getZonedTime
326-
return (formatTime' now ++ ": ")
327-
| otherwise = return ""
328-
where
329-
formatTime' =
330-
take timestampLength . formatTime defaultTimeLocale "%F %T.%q"
331-
getLevel
332-
| maxLogLevel <= LevelDebug =
333-
return ("[" ++
334-
map toLower (drop 5 (show level)) ++
335-
"] ")
336-
| otherwise = return ""
337-
getLoc
338-
| maxLogLevel <= LevelDebug =
339-
return (" @(" ++ fileLocStr ++ ")")
340-
| otherwise = return ""
341-
fileLocStr =
342-
loc_package loc ++
343-
':' :
344-
loc_module loc ++
345-
' ' :
346-
loc_filename loc ++
347-
':' :
348-
line loc ++
349-
':' :
350-
char loc
351-
where line = show . fst . loc_start
352-
char = show . snd . loc_start
323+
where
324+
getOutput = do
325+
timestamp <- getTimestamp
326+
l <- getLevel
327+
lc <- getLoc
328+
return $ T.concat
329+
[ T.pack timestamp
330+
, T.pack l
331+
, T.pack (ansi [Reset])
332+
, T.decodeUtf8 (fromLogStr (toLogStr msg))
333+
, T.pack lc
334+
, T.pack (ansi [Reset])
335+
]
336+
where
337+
ansi xs | supportsAnsi = setSGRCode xs
338+
| otherwise = ""
339+
getTimestamp
340+
| maxLogLevel <= LevelDebug =
341+
do now <- getZonedTime
342+
return $
343+
ansi [SetColor Foreground Vivid Black]
344+
++ formatTime' now ++ ": "
345+
| otherwise = return ""
346+
where
347+
formatTime' =
348+
take timestampLength . formatTime defaultTimeLocale "%F %T.%q"
349+
getLevel
350+
| maxLogLevel <= LevelDebug =
351+
return ((case level of
352+
LevelDebug -> ansi [SetColor Foreground Dull Green]
353+
LevelInfo -> ansi [SetColor Foreground Dull Blue]
354+
LevelWarn -> ansi [SetColor Foreground Dull Yellow]
355+
LevelError -> ansi [SetColor Foreground Dull Red]
356+
LevelOther _ -> ansi [SetColor Foreground Dull Magenta]) ++
357+
"[" ++
358+
map toLower (drop 5 (show level)) ++
359+
"] ")
360+
| otherwise = return ""
361+
getLoc
362+
| maxLogLevel <= LevelDebug =
363+
return $
364+
ansi [SetColor Foreground Vivid Black] ++
365+
"\n@(" ++ fileLocStr ++ ")"
366+
| otherwise = return ""
367+
fileLocStr =
368+
fromMaybe file (stripPrefix dirRoot file) ++
369+
':' :
370+
line loc ++
371+
':' :
372+
char loc
373+
where
374+
file = loc_filename loc
375+
line = show . fst . loc_start
376+
char = show . snd . loc_start
377+
dirRoot = $(lift . T.unpack . fromJust . T.stripSuffix "src/Stack/Types/StackT.hs" . T.pack . loc_filename =<< location)
353378

354379
-- | The length of a timestamp in the format "YYYY-MM-DD hh:mm:ss.μμμμμμ".
355380
-- This definition is top-level in order to avoid multiple reevaluation at runtime.

0 commit comments

Comments
 (0)