Skip to content

Commit 6cfb608

Browse files
committed
Probe tools: Print version with padded spaces
Addressing <#3093 (comment)>
1 parent 13b0e15 commit 6cfb608

File tree

2 files changed

+16
-8
lines changed

2 files changed

+16
-8
lines changed

exe/Wrapper.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@ module Main where
1414
import Control.Monad.Extra
1515
import Data.Char (isSpace)
1616
import Data.Default
17-
import Data.Either (fromRight)
17+
import Data.Either.Extra (eitherToMaybe)
1818
import Data.Foldable
1919
import Data.List
2020
import Data.Void
@@ -83,7 +83,7 @@ main = do
8383
putStrLn "Tool versions in your project"
8484
cradle <- findProjectCradle' False
8585
ghcVersion <- runExceptT $ getRuntimeGhcVersion' cradle
86-
putStrLn $ "ghc:\t\t" ++ fromRight "Not found" ghcVersion
86+
putStrLn $ showProgramVersion "ghc" $ mkVersion =<< eitherToMaybe ghcVersion
8787

8888
VersionMode PrintVersion ->
8989
putStrLn hlsVer

src/Ide/Version.hs

Lines changed: 14 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -46,13 +46,17 @@ data ProgramsOfInterest = ProgramsOfInterest
4646
showProgramVersionOfInterest :: ProgramsOfInterest -> String
4747
showProgramVersionOfInterest ProgramsOfInterest {..} =
4848
unlines
49-
[ "cabal:\t\t" ++ showVersionWithDefault cabalVersion
50-
, "stack:\t\t" ++ showVersionWithDefault stackVersion
51-
, "ghc:\t\t" ++ showVersionWithDefault ghcVersion
49+
[ showProgramVersion "cabal" cabalVersion
50+
, showProgramVersion "stack" stackVersion
51+
, showProgramVersion "ghc" ghcVersion
5252
]
53+
54+
showProgramVersion :: String -> Maybe Version -> String
55+
showProgramVersion name version =
56+
pad 16 (name ++ ":") ++ showVersionWithDefault version
5357
where
54-
showVersionWithDefault :: Maybe Version -> String
5558
showVersionWithDefault = maybe "Not found" showVersion
59+
pad n s = s ++ replicate (n - length s) ' '
5660

5761
findProgramVersions :: IO ProgramsOfInterest
5862
findProgramVersions = ProgramsOfInterest
@@ -69,8 +73,11 @@ findVersionOf tool =
6973
Nothing -> pure Nothing
7074
Just path ->
7175
readProcessWithExitCode path ["--numeric-version"] "" >>= \case
72-
(ExitSuccess, sout, _) -> pure $ consumeParser myVersionParser sout
76+
(ExitSuccess, sout, _) -> pure $ mkVersion sout
7377
_ -> pure Nothing
78+
79+
mkVersion :: String -> Maybe Version
80+
mkVersion = consumeParser myVersionParser
7481
where
7582
myVersionParser = do
7683
skipSpaces
@@ -79,4 +86,5 @@ findVersionOf tool =
7986
pure version
8087

8188
consumeParser :: ReadP a -> String -> Maybe a
82-
consumeParser p input = listToMaybe $ map fst . filter (null . snd) $ readP_to_S p input
89+
consumeParser p input =
90+
listToMaybe $ map fst . filter (null . snd) $ readP_to_S p input

0 commit comments

Comments
 (0)