{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-dodgy-imports #-}
module Ide.Arguments
( Arguments(..)
, LspArguments(..)
, PrintVersion(..)
, getArguments
, haskellLanguageServerVersion
, haskellLanguageServerNumericVersion
) where
import Data.Version
import Development.GitRev
import Options.Applicative
import Paths_haskell_language_server
import System.Environment
import HieDb.Run
data Arguments
= VersionMode PrintVersion
| ProbeToolsMode
| DbCmd Options Command
| LspMode LspArguments
data LspArguments = LspArguments
{LspArguments -> Bool
argLSP :: Bool
,LspArguments -> Maybe FilePath
argsCwd :: Maybe FilePath
,LspArguments -> [FilePath]
argFiles :: [FilePath]
,LspArguments -> Maybe FilePath
argsShakeProfiling :: Maybe FilePath
,LspArguments -> Bool
argsTesting :: Bool
,LspArguments -> Bool
argsExamplePlugin :: Bool
, LspArguments -> Bool
argsDebugOn :: Bool
, LspArguments -> Maybe FilePath
argsLogFile :: Maybe String
, LspArguments -> Int
argsThreads :: Int
, LspArguments -> Bool
argsProjectGhcVersion :: Bool
} deriving Int -> LspArguments -> ShowS
[LspArguments] -> ShowS
LspArguments -> FilePath
(Int -> LspArguments -> ShowS)
-> (LspArguments -> FilePath)
-> ([LspArguments] -> ShowS)
-> Show LspArguments
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [LspArguments] -> ShowS
$cshowList :: [LspArguments] -> ShowS
show :: LspArguments -> FilePath
$cshow :: LspArguments -> FilePath
showsPrec :: Int -> LspArguments -> ShowS
$cshowsPrec :: Int -> LspArguments -> ShowS
Show
data PrintVersion
= PrintVersion
| PrintNumericVersion
deriving (Int -> PrintVersion -> ShowS
[PrintVersion] -> ShowS
PrintVersion -> FilePath
(Int -> PrintVersion -> ShowS)
-> (PrintVersion -> FilePath)
-> ([PrintVersion] -> ShowS)
-> Show PrintVersion
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [PrintVersion] -> ShowS
$cshowList :: [PrintVersion] -> ShowS
show :: PrintVersion -> FilePath
$cshow :: PrintVersion -> FilePath
showsPrec :: Int -> PrintVersion -> ShowS
$cshowsPrec :: Int -> PrintVersion -> ShowS
Show, PrintVersion -> PrintVersion -> Bool
(PrintVersion -> PrintVersion -> Bool)
-> (PrintVersion -> PrintVersion -> Bool) -> Eq PrintVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrintVersion -> PrintVersion -> Bool
$c/= :: PrintVersion -> PrintVersion -> Bool
== :: PrintVersion -> PrintVersion -> Bool
$c== :: PrintVersion -> PrintVersion -> Bool
Eq, Eq PrintVersion
Eq PrintVersion
-> (PrintVersion -> PrintVersion -> Ordering)
-> (PrintVersion -> PrintVersion -> Bool)
-> (PrintVersion -> PrintVersion -> Bool)
-> (PrintVersion -> PrintVersion -> Bool)
-> (PrintVersion -> PrintVersion -> Bool)
-> (PrintVersion -> PrintVersion -> PrintVersion)
-> (PrintVersion -> PrintVersion -> PrintVersion)
-> Ord PrintVersion
PrintVersion -> PrintVersion -> Bool
PrintVersion -> PrintVersion -> Ordering
PrintVersion -> PrintVersion -> PrintVersion
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PrintVersion -> PrintVersion -> PrintVersion
$cmin :: PrintVersion -> PrintVersion -> PrintVersion
max :: PrintVersion -> PrintVersion -> PrintVersion
$cmax :: PrintVersion -> PrintVersion -> PrintVersion
>= :: PrintVersion -> PrintVersion -> Bool
$c>= :: PrintVersion -> PrintVersion -> Bool
> :: PrintVersion -> PrintVersion -> Bool
$c> :: PrintVersion -> PrintVersion -> Bool
<= :: PrintVersion -> PrintVersion -> Bool
$c<= :: PrintVersion -> PrintVersion -> Bool
< :: PrintVersion -> PrintVersion -> Bool
$c< :: PrintVersion -> PrintVersion -> Bool
compare :: PrintVersion -> PrintVersion -> Ordering
$ccompare :: PrintVersion -> PrintVersion -> Ordering
$cp1Ord :: Eq PrintVersion
Ord)
getArguments :: String -> IO Arguments
getArguments :: FilePath -> IO Arguments
getArguments FilePath
exeName = ParserInfo Arguments -> IO Arguments
forall a. ParserInfo a -> IO a
execParser ParserInfo Arguments
opts
where
hieInfo :: InfoMod a
hieInfo = InfoMod a
forall a. InfoMod a
fullDesc InfoMod a -> InfoMod a -> InfoMod a
forall a. Semigroup a => a -> a -> a
<> FilePath -> InfoMod a
forall a. FilePath -> InfoMod a
progDesc FilePath
"Query .hie files"
opts :: ParserInfo Arguments
opts = Parser Arguments -> InfoMod Arguments -> ParserInfo Arguments
forall a. Parser a -> InfoMod a -> ParserInfo a
info ((
PrintVersion -> Arguments
VersionMode (PrintVersion -> Arguments)
-> Parser PrintVersion -> Parser Arguments
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> Parser PrintVersion
printVersionParser FilePath
exeName
Parser Arguments -> Parser Arguments -> Parser Arguments
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> FilePath -> Parser Arguments
probeToolsParser FilePath
exeName
Parser Arguments -> Parser Arguments -> Parser Arguments
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Mod CommandFields Arguments -> Parser Arguments
forall a. Mod CommandFields a -> Parser a
hsubparser (FilePath -> ParserInfo Arguments -> Mod CommandFields Arguments
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
command FilePath
"hiedb" (Parser Arguments -> InfoMod Arguments -> ParserInfo Arguments
forall a. Parser a -> InfoMod a -> ParserInfo a
info (Options -> Command -> Arguments
DbCmd (Options -> Command -> Arguments)
-> Parser Options -> Parser (Command -> Arguments)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> Bool -> Parser Options
optParser FilePath
"" Bool
True Parser (Command -> Arguments) -> Parser Command -> Parser Arguments
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Command
cmdParser Parser Arguments
-> Parser (Arguments -> Arguments) -> Parser Arguments
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Arguments -> Arguments)
forall a. Parser (a -> a)
helper) InfoMod Arguments
forall a. InfoMod a
hieInfo))
Parser Arguments -> Parser Arguments -> Parser Arguments
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LspArguments -> Arguments
LspMode (LspArguments -> Arguments)
-> Parser LspArguments -> Parser Arguments
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser LspArguments
arguments)
Parser Arguments
-> Parser (Arguments -> Arguments) -> Parser Arguments
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Arguments -> Arguments)
forall a. Parser (a -> a)
helper)
( InfoMod Arguments
forall a. InfoMod a
fullDesc
InfoMod Arguments -> InfoMod Arguments -> InfoMod Arguments
forall a. Semigroup a => a -> a -> a
<> FilePath -> InfoMod Arguments
forall a. FilePath -> InfoMod a
progDesc FilePath
"Used as a test bed to check your IDE Client will work"
InfoMod Arguments -> InfoMod Arguments -> InfoMod Arguments
forall a. Semigroup a => a -> a -> a
<> FilePath -> InfoMod Arguments
forall a. FilePath -> InfoMod a
header (FilePath
exeName FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" - GHC Haskell LSP server"))
printVersionParser :: String -> Parser PrintVersion
printVersionParser :: FilePath -> Parser PrintVersion
printVersionParser FilePath
exeName =
PrintVersion -> Mod FlagFields PrintVersion -> Parser PrintVersion
forall a. a -> Mod FlagFields a -> Parser a
flag' PrintVersion
PrintVersion
(FilePath -> Mod FlagFields PrintVersion
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"version" Mod FlagFields PrintVersion
-> Mod FlagFields PrintVersion -> Mod FlagFields PrintVersion
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields PrintVersion
forall (f :: * -> *) a. FilePath -> Mod f a
help (FilePath
"Show " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
exeName FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" and GHC versions"))
Parser PrintVersion -> Parser PrintVersion -> Parser PrintVersion
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
PrintVersion -> Mod FlagFields PrintVersion -> Parser PrintVersion
forall a. a -> Mod FlagFields a -> Parser a
flag' PrintVersion
PrintNumericVersion
(FilePath -> Mod FlagFields PrintVersion
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"numeric-version" Mod FlagFields PrintVersion
-> Mod FlagFields PrintVersion -> Mod FlagFields PrintVersion
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields PrintVersion
forall (f :: * -> *) a. FilePath -> Mod f a
help (FilePath
"Show numeric version of " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
exeName))
probeToolsParser :: String -> Parser Arguments
probeToolsParser :: FilePath -> Parser Arguments
probeToolsParser FilePath
exeName =
Arguments -> Mod FlagFields Arguments -> Parser Arguments
forall a. a -> Mod FlagFields a -> Parser a
flag' Arguments
ProbeToolsMode
(FilePath -> Mod FlagFields Arguments
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"probe-tools" Mod FlagFields Arguments
-> Mod FlagFields Arguments -> Mod FlagFields Arguments
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Arguments
forall (f :: * -> *) a. FilePath -> Mod f a
help (FilePath
"Show " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
exeName FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" version and other tools of interest"))
arguments :: Parser LspArguments
arguments :: Parser LspArguments
arguments = Bool
-> Maybe FilePath
-> [FilePath]
-> Maybe FilePath
-> Bool
-> Bool
-> Bool
-> Maybe FilePath
-> Int
-> Bool
-> LspArguments
LspArguments
(Bool
-> Maybe FilePath
-> [FilePath]
-> Maybe FilePath
-> Bool
-> Bool
-> Bool
-> Maybe FilePath
-> Int
-> Bool
-> LspArguments)
-> Parser Bool
-> Parser
(Maybe FilePath
-> [FilePath]
-> Maybe FilePath
-> Bool
-> Bool
-> Bool
-> Maybe FilePath
-> Int
-> Bool
-> LspArguments)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mod FlagFields Bool -> Parser Bool
switch (FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"lsp" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Start talking to an LSP server")
Parser
(Maybe FilePath
-> [FilePath]
-> Maybe FilePath
-> Bool
-> Bool
-> Bool
-> Maybe FilePath
-> Int
-> Bool
-> LspArguments)
-> Parser (Maybe FilePath)
-> Parser
([FilePath]
-> Maybe FilePath
-> Bool
-> Bool
-> Bool
-> Maybe FilePath
-> Int
-> Bool
-> LspArguments)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FilePath -> Parser (Maybe FilePath)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (Mod OptionFields FilePath -> Parser FilePath)
-> Mod OptionFields FilePath -> Parser FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"cwd" Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"DIR"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Change to this directory")
Parser
([FilePath]
-> Maybe FilePath
-> Bool
-> Bool
-> Bool
-> Maybe FilePath
-> Int
-> Bool
-> LspArguments)
-> Parser [FilePath]
-> Parser
(Maybe FilePath
-> Bool
-> Bool
-> Bool
-> Maybe FilePath
-> Int
-> Bool
-> LspArguments)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FilePath -> Parser [FilePath]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ReadM FilePath -> Mod ArgumentFields FilePath -> Parser FilePath
forall a. ReadM a -> Mod ArgumentFields a -> Parser a
argument ReadM FilePath
forall s. IsString s => ReadM s
str (FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"FILES/DIRS..."))
Parser
(Maybe FilePath
-> Bool
-> Bool
-> Bool
-> Maybe FilePath
-> Int
-> Bool
-> LspArguments)
-> Parser (Maybe FilePath)
-> Parser
(Bool
-> Bool -> Bool -> Maybe FilePath -> Int -> Bool -> LspArguments)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FilePath -> Parser (Maybe FilePath)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (Mod OptionFields FilePath -> Parser FilePath)
-> Mod OptionFields FilePath -> Parser FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"shake-profiling" Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"DIR"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Dump profiling reports to this directory")
Parser
(Bool
-> Bool -> Bool -> Maybe FilePath -> Int -> Bool -> LspArguments)
-> Parser Bool
-> Parser
(Bool -> Bool -> Maybe FilePath -> Int -> Bool -> LspArguments)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
switch (FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"test"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Enable additional lsp messages used by the testsuite")
Parser
(Bool -> Bool -> Maybe FilePath -> Int -> Bool -> LspArguments)
-> Parser Bool
-> Parser (Bool -> Maybe FilePath -> Int -> Bool -> LspArguments)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
switch (FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"example"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Include the Example Plugin. For Plugin devs only")
Parser (Bool -> Maybe FilePath -> Int -> Bool -> LspArguments)
-> Parser Bool
-> Parser (Maybe FilePath -> Int -> Bool -> LspArguments)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
switch
( FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"debug"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'd'
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Generate debug output"
)
Parser (Maybe FilePath -> Int -> Bool -> LspArguments)
-> Parser (Maybe FilePath) -> Parser (Int -> Bool -> LspArguments)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FilePath -> Parser (Maybe FilePath)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption
( FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"logfile"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'l'
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"LOGFILE"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"File to log to, defaults to stdout"
))
Parser (Int -> Bool -> LspArguments)
-> Parser Int -> Parser (Bool -> LspArguments)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto
(Char -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'j'
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Number of threads (0: automatic)"
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"NUM"
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Int -> Mod OptionFields Int
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Int
0
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Int
forall a (f :: * -> *). Show a => Mod f a
showDefault
)
Parser (Bool -> LspArguments) -> Parser Bool -> Parser LspArguments
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
switch (FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"project-ghc-version"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Work out the project GHC version and print it")
haskellLanguageServerNumericVersion :: String
haskellLanguageServerNumericVersion :: FilePath
haskellLanguageServerNumericVersion = Version -> FilePath
showVersion Version
version
haskellLanguageServerVersion :: IO String
haskellLanguageServerVersion :: IO FilePath
haskellLanguageServerVersion = do
FilePath
path <- IO FilePath
getExecutablePath
let gitHashSection :: FilePath
gitHashSection = case $(FilePath
gitHash) of
FilePath
x | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"UNKNOWN" -> FilePath
""
FilePath
x -> FilePath
" (GIT hash: " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
x FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
")"
FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> IO FilePath) -> FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
"haskell-language-server version: " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
haskellLanguageServerNumericVersion
FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
" (GHC: " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> VERSION_ghc
FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
") (PATH: " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
path FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
")"
FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
gitHashSection