mirror of
https://github.com/nmattia/niv.git
synced 2024-11-07 22:36:53 +03:00
Add flag for --no-colors
This commit is contained in:
parent
ba57d5a29b
commit
d91c8b8051
@ -221,10 +221,11 @@ niv - dependency manager for Nix projects
|
||||
|
||||
version: 0.2.18
|
||||
|
||||
Usage: niv [-s|--sources-file FILE] COMMAND
|
||||
Usage: niv [-s|--sources-file FILE] [--no-colors] COMMAND
|
||||
|
||||
Available options:
|
||||
-s,--sources-file FILE Use FILE instead of nix/sources.json
|
||||
--no-colors Don't use colors in output
|
||||
-h,--help Show this help text
|
||||
--version Print version
|
||||
|
||||
|
@ -54,16 +54,17 @@ li = liftIO
|
||||
cli :: IO ()
|
||||
cli = do
|
||||
warnGitHubEnvVars
|
||||
(fsj, nio) <-
|
||||
((fsj, colors), nio) <-
|
||||
execParserPure' Opts.defaultPrefs opts <$> getArgs
|
||||
>>= Opts.handleParseResult
|
||||
setColors colors
|
||||
runReaderT (runNIO nio) fsj
|
||||
where
|
||||
execParserPure' pprefs pinfo [] =
|
||||
Opts.Failure $
|
||||
Opts.parserFailure pprefs pinfo Opts.ShowHelpText mempty
|
||||
execParserPure' pprefs pinfo args = Opts.execParserPure pprefs pinfo args
|
||||
opts = Opts.info ((,) <$> parseFindSourcesJson <*> (parseCommand <**> Opts.helper <**> versionflag)) $ mconcat desc
|
||||
opts = Opts.info ((,) <$> ((,) <$> parseFindSourcesJson <*> parseColors) <*> (parseCommand <**> Opts.helper <**> versionflag)) $ mconcat desc
|
||||
desc =
|
||||
[ Opts.fullDesc,
|
||||
Opts.headerDoc $ Just $
|
||||
@ -80,6 +81,12 @@ cli = do
|
||||
<> Opts.help "Use FILE instead of nix/sources.json"
|
||||
)
|
||||
<|> pure Auto
|
||||
parseColors =
|
||||
(\case True -> Never; False -> Always)
|
||||
<$> Opts.switch
|
||||
( Opts.long "no-colors"
|
||||
<> Opts.help "Don't use colors in output"
|
||||
)
|
||||
versionflag :: Opts.Parser (a -> a)
|
||||
versionflag =
|
||||
Opts.abortOption (Opts.InfoMsg (showVersion version)) $
|
||||
|
@ -4,7 +4,9 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Niv.Logger
|
||||
( job,
|
||||
( Colors (Always, Never),
|
||||
job,
|
||||
setColors,
|
||||
bug,
|
||||
tsay,
|
||||
say,
|
||||
@ -35,6 +37,27 @@ import System.Exit (exitFailure)
|
||||
import System.IO.Unsafe (unsafePerformIO)
|
||||
import UnliftIO
|
||||
|
||||
-- A somewhat hacky way of deciding whether or not to use SGR codes, by writing
|
||||
-- and reading a global variable unsafely.
|
||||
-- This should be fine as long as the IORef is written right after argument
|
||||
-- parsing, and as long as the value is never changed.
|
||||
-- NOTE: this won't work in GHCi.
|
||||
|
||||
data Colors
|
||||
= Always
|
||||
| Never
|
||||
deriving (Eq)
|
||||
|
||||
colors :: IORef Colors
|
||||
colors = unsafePerformIO $ newIORef Always
|
||||
{-# NOINLINE colors #-}
|
||||
|
||||
setColors :: Colors -> IO ()
|
||||
setColors = writeIORef colors
|
||||
|
||||
useColors :: Bool
|
||||
useColors = unsafePerformIO $ (\c -> c == Always) <$> readIORef colors
|
||||
|
||||
type S = String -> String
|
||||
|
||||
type T = T.Text -> T.Text
|
||||
@ -85,61 +108,58 @@ twarn = tsay . mkWarn
|
||||
mkNote :: T.Text -> T.Text
|
||||
mkNote w = tbold (tblue "NOTE") <> ": " <> w
|
||||
|
||||
color :: ANSI.Color -> String -> String
|
||||
color c str =
|
||||
if useColors
|
||||
then
|
||||
ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.BoldIntensity]
|
||||
<> ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid c]
|
||||
<> str
|
||||
<> ANSI.setSGRCode [ANSI.Reset]
|
||||
else str
|
||||
|
||||
colorFaint :: ANSI.Color -> String -> String
|
||||
colorFaint c str =
|
||||
if useColors
|
||||
then
|
||||
ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.FaintIntensity]
|
||||
<> ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid c]
|
||||
<> str
|
||||
<> ANSI.setSGRCode [ANSI.Reset]
|
||||
else str
|
||||
|
||||
green :: S
|
||||
green str =
|
||||
ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.BoldIntensity]
|
||||
<> ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Green]
|
||||
<> str
|
||||
<> ANSI.setSGRCode [ANSI.Reset]
|
||||
green = color ANSI.Green
|
||||
|
||||
tgreen :: T
|
||||
tgreen = t green
|
||||
|
||||
yellow :: S
|
||||
yellow str =
|
||||
ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.BoldIntensity]
|
||||
<> ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Yellow]
|
||||
<> str
|
||||
<> ANSI.setSGRCode [ANSI.Reset]
|
||||
yellow = color ANSI.Yellow
|
||||
|
||||
tyellow :: T
|
||||
tyellow = t yellow
|
||||
|
||||
blue :: S
|
||||
blue str =
|
||||
ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.BoldIntensity]
|
||||
<> ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Blue]
|
||||
<> str
|
||||
<> ANSI.setSGRCode [ANSI.Reset]
|
||||
blue = color ANSI.Blue
|
||||
|
||||
tblue :: T
|
||||
tblue = t blue
|
||||
|
||||
red :: S
|
||||
red str =
|
||||
ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Red]
|
||||
<> str
|
||||
<> ANSI.setSGRCode [ANSI.Reset]
|
||||
red = color ANSI.Red
|
||||
|
||||
tred :: T
|
||||
tred = t red
|
||||
|
||||
bold :: S
|
||||
bold str =
|
||||
ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.BoldIntensity]
|
||||
<> ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.White]
|
||||
<> str
|
||||
<> ANSI.setSGRCode [ANSI.Reset]
|
||||
bold = color ANSI.White
|
||||
|
||||
tbold :: T
|
||||
tbold = t bold
|
||||
|
||||
faint :: String -> String
|
||||
faint str =
|
||||
ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.FaintIntensity]
|
||||
<> ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.White]
|
||||
<> str
|
||||
<> ANSI.setSGRCode [ANSI.Reset]
|
||||
faint = colorFaint ANSI.White
|
||||
|
||||
tfaint :: T
|
||||
tfaint = t faint
|
||||
|
Loading…
Reference in New Issue
Block a user