{-# OPTIONS_GHC -Wno-orphans #-}
module Development.IDE.Main
(Arguments(..)
,Command(..)
,IdeCommand(..)
,isLSP
,commandP
,defaultMain
) where
import           Control.Concurrent.Extra              (newLock, readVar,
                                                        withLock)
import           Control.Exception.Safe                (Exception (displayException),
                                                        catchAny)
import           Control.Monad.Extra                   (concatMapM, unless,
                                                        when)
import qualified Data.Aeson.Encode.Pretty              as A
import           Data.Default                          (Default (def))
import           Data.Foldable                         (traverse_)
import qualified Data.HashMap.Strict                   as HashMap
import           Data.Hashable                         (hashed)
import           Data.List.Extra                       (intercalate, isPrefixOf,
                                                        nub, nubOrd, partition)
import           Data.Maybe                            (catMaybes, isJust)
import qualified Data.Text                             as T
import qualified Data.Text.IO                          as T
import           Data.Text.Lazy.Encoding               (decodeUtf8)
import qualified Data.Text.Lazy.IO                     as LT
import           Development.IDE                       (Action, GhcVersion (..),
                                                        Rules, ghcVersion,
                                                        hDuplicateTo')
import           Development.IDE.Core.Debouncer        (Debouncer,
                                                        newAsyncDebouncer)
import           Development.IDE.Core.FileStore        (isWatchSupported,
                                                        makeVFSHandle)
import           Development.IDE.Core.IdeConfiguration (IdeConfiguration (..),
                                                        registerIdeConfiguration)
import           Development.IDE.Core.OfInterest       (FileOfInterestStatus (OnDisk),
                                                        kick,
                                                        setFilesOfInterest)
import           Development.IDE.Core.RuleTypes        (GenerateCore (GenerateCore),
                                                        GetHieAst (GetHieAst),
                                                        GhcSession (GhcSession),
                                                        GhcSessionDeps (GhcSessionDeps),
                                                        TypeCheck (TypeCheck))
import           Development.IDE.Core.Rules            (GhcSessionIO (GhcSessionIO),
                                                        mainRule)
import           Development.IDE.Core.Service          (initialise, runAction)
import           Development.IDE.Core.Shake            (IdeState (shakeExtras),
                                                        ShakeExtras (state),
                                                        shakeSessionInit, uses)
import           Development.IDE.Core.Tracing          (measureMemory)
import           Development.IDE.Graph                 (action)
import           Development.IDE.LSP.LanguageServer    (runLanguageServer)
import           Development.IDE.Plugin                (Plugin (pluginHandlers, pluginModifyDynflags, pluginRules))
import           Development.IDE.Plugin.HLS            (asGhcIdePlugin)
import qualified Development.IDE.Plugin.HLS.GhcIde     as Ghcide
import           Development.IDE.Session               (SessionLoadingOptions,
                                                        getHieDbLoc,
                                                        loadSessionWithOptions,
                                                        runWithDb,
                                                        setInitialDynFlags)
import           Development.IDE.Types.Location        (NormalizedUri,
                                                        toNormalizedFilePath')
import           Development.IDE.Types.Logger          (Logger (Logger))
import           Development.IDE.Types.Options         (IdeGhcSession,
                                                        IdeOptions (optCheckParents, optCheckProject, optReportProgress, optRunSubset),
                                                        clientSupportsProgress,
                                                        defaultIdeOptions,
                                                        optModifyDynFlags)
import           Development.IDE.Types.Shake           (Key (Key))
import           GHC.IO.Encoding                       (setLocaleEncoding)
import           GHC.IO.Handle                         (hDuplicate)
import           HIE.Bios.Cradle                       (findCradle)
import qualified HieDb.Run                             as HieDb
import           Ide.Plugin.Config                     (CheckParents (NeverCheck),
                                                        Config,
                                                        getConfigFromNotification)
import           Ide.Plugin.ConfigUtils                (pluginsToDefaultConfig,
                                                        pluginsToVSCodeExtensionSchema)
import           Ide.PluginUtils                       (allLspCmdIds',
                                                        getProcessID,
                                                        pluginDescToIdePlugins)
import           Ide.Types                             (IdeCommand (IdeCommand),
                                                        IdePlugins,
                                                        PluginDescriptor (PluginDescriptor, pluginCli),
                                                        PluginId (PluginId),
                                                        ipMap)
import qualified Language.LSP.Server                   as LSP
import           Options.Applicative                   hiding (action)
import qualified System.Directory.Extra                as IO
import           System.Exit                           (ExitCode (ExitFailure),
                                                        exitWith)
import           System.FilePath                       (takeExtension,
                                                        takeFileName)
import           System.IO                             (BufferMode (LineBuffering, NoBuffering),
                                                        Handle, hFlush,
                                                        hPutStrLn,
                                                        hSetBuffering,
                                                        hSetEncoding, stderr,
                                                        stdin, stdout, utf8)
import           System.Time.Extra                     (offsetTime,
                                                        showDuration)
import           Text.Printf                           (printf)

data Command
    = Check [FilePath]  -- ^ Typecheck some paths and print diagnostics. Exit code is the number of failures
    | Db {Command -> FilePath
projectRoot :: FilePath, Command -> Options
hieOptions ::  HieDb.Options, Command -> Command
hieCommand :: HieDb.Command}
     -- ^ Run a command in the hiedb
    | LSP   -- ^ Run the LSP server
    | PrintExtensionSchema
    | PrintDefaultConfig
    | Custom {projectRoot :: FilePath, Command -> IdeCommand IdeState
ideCommand :: IdeCommand IdeState} -- ^ User defined
    deriving Int -> Command -> ShowS
[Command] -> ShowS
Command -> FilePath
(Int -> Command -> ShowS)
-> (Command -> FilePath) -> ([Command] -> ShowS) -> Show Command
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Command] -> ShowS
$cshowList :: [Command] -> ShowS
show :: Command -> FilePath
$cshow :: Command -> FilePath
showsPrec :: Int -> Command -> ShowS
$cshowsPrec :: Int -> Command -> ShowS
Show


-- TODO move these to hiedb
deriving instance Show HieDb.Command
deriving instance Show HieDb.Options

isLSP :: Command -> Bool
isLSP :: Command -> Bool
isLSP Command
LSP = Bool
True
isLSP Command
_   = Bool
False

commandP :: IdePlugins IdeState -> Parser Command
commandP :: IdePlugins IdeState -> Parser Command
commandP IdePlugins IdeState
plugins =
    Mod CommandFields Command -> Parser Command
forall a. Mod CommandFields a -> Parser a
hsubparser(FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
command FilePath
"typecheck" (Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
info ([FilePath] -> Command
Check ([FilePath] -> Command) -> Parser [FilePath] -> Parser Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser [FilePath]
fileCmd) InfoMod Command
forall a. InfoMod a
fileInfo)
            Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
command FilePath
"hiedb" (Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
info (FilePath -> Options -> Command -> Command
Db FilePath
"." (Options -> Command -> Command)
-> Parser Options -> Parser (Command -> Command)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> Bool -> Parser Options
HieDb.optParser FilePath
"" Bool
True Parser (Command -> Command) -> Parser Command -> Parser Command
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Command
HieDb.cmdParser Parser Command -> Parser (Command -> Command) -> Parser Command
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Command -> Command)
forall a. Parser (a -> a)
helper) InfoMod Command
forall a. InfoMod a
hieInfo)
            Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
command FilePath
"lsp" (Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
info (Command -> Parser Command
forall (f :: * -> *) a. Applicative f => a -> f a
pure Command
LSP Parser Command -> Parser (Command -> Command) -> Parser Command
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Command -> Command)
forall a. Parser (a -> a)
helper) InfoMod Command
forall a. InfoMod a
lspInfo)
            Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
command FilePath
"vscode-extension-schema" ParserInfo Command
extensionSchemaCommand
            Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
command FilePath
"generate-default-config" ParserInfo Command
generateDefaultConfigCommand
            Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> Mod CommandFields Command
pluginCommands
            )
  where
    fileCmd :: Parser [FilePath]
fileCmd = 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..."))
    lspInfo :: InfoMod a
lspInfo = 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
"Start talking to an LSP client"
    fileInfo :: InfoMod a
fileInfo = 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
"Used as a test bed to check your IDE will work"
    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"
    extensionSchemaCommand :: ParserInfo Command
extensionSchemaCommand =
        Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
info (Command -> Parser Command
forall (f :: * -> *) a. Applicative f => a -> f a
pure Command
PrintExtensionSchema)
             (InfoMod Command
forall a. InfoMod a
fullDesc InfoMod Command -> InfoMod Command -> InfoMod Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
progDesc FilePath
"Print generic config schema for plugins (used in the package.json of haskell vscode extension)")
    generateDefaultConfigCommand :: ParserInfo Command
generateDefaultConfigCommand =
        Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
info (Command -> Parser Command
forall (f :: * -> *) a. Applicative f => a -> f a
pure Command
PrintDefaultConfig)
             (InfoMod Command
forall a. InfoMod a
fullDesc InfoMod Command -> InfoMod Command -> InfoMod Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
progDesc FilePath
"Print config supported by the server with default values")

    pluginCommands :: Mod CommandFields Command
pluginCommands = [Mod CommandFields Command] -> Mod CommandFields Command
forall a. Monoid a => [a] -> a
mconcat
        [ FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
command (Text -> FilePath
T.unpack Text
pId) (FilePath -> IdeCommand IdeState -> Command
Custom FilePath
"." (IdeCommand IdeState -> Command)
-> ParserInfo (IdeCommand IdeState) -> ParserInfo Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserInfo (IdeCommand IdeState)
p)
        | (PluginId Text
pId, PluginDescriptor{pluginCli :: forall ideState.
PluginDescriptor ideState
-> Maybe (ParserInfo (IdeCommand ideState))
pluginCli = Just ParserInfo (IdeCommand IdeState)
p}) <- IdePlugins IdeState -> [(PluginId, PluginDescriptor IdeState)]
forall ideState.
IdePlugins ideState -> [(PluginId, PluginDescriptor ideState)]
ipMap IdePlugins IdeState
plugins
        ]


data Arguments = Arguments
    { Arguments -> Bool
argsOTMemoryProfiling     :: Bool
    , Arguments -> Command
argCommand                :: Command
    , Arguments -> IO Logger
argsLogger                :: IO Logger
    , Arguments -> Rules ()
argsRules                 :: Rules ()
    , Arguments -> IdePlugins IdeState
argsHlsPlugins            :: IdePlugins IdeState
    , Arguments -> Plugin Config
argsGhcidePlugin          :: Plugin Config  -- ^ Deprecated
    , Arguments -> SessionLoadingOptions
argsSessionLoadingOptions :: SessionLoadingOptions
    , Arguments -> Config -> Action IdeGhcSession -> IdeOptions
argsIdeOptions            :: Config -> Action IdeGhcSession -> IdeOptions
    , Arguments -> Options
argsLspOptions            :: LSP.Options
    , Arguments -> Config
argsDefaultHlsConfig      :: Config
    , Arguments -> FilePath -> IO FilePath
argsGetHieDbLoc           :: FilePath -> IO FilePath -- ^ Map project roots to the location of the hiedb for the project
    , Arguments -> IO (Debouncer NormalizedUri)
argsDebouncer             :: IO (Debouncer NormalizedUri) -- ^ Debouncer used for diagnostics
    , Arguments -> IO Handle
argsHandleIn              :: IO Handle
    , Arguments -> IO Handle
argsHandleOut             :: IO Handle
    }

instance Default Arguments where
    def :: Arguments
def = Arguments :: Bool
-> Command
-> IO Logger
-> Rules ()
-> IdePlugins IdeState
-> Plugin Config
-> SessionLoadingOptions
-> (Config -> Action IdeGhcSession -> IdeOptions)
-> Options
-> Config
-> (FilePath -> IO FilePath)
-> IO (Debouncer NormalizedUri)
-> IO Handle
-> IO Handle
-> Arguments
Arguments
        { argsOTMemoryProfiling :: Bool
argsOTMemoryProfiling = Bool
False
        , argCommand :: Command
argCommand = Command
LSP
        , argsLogger :: IO Logger
argsLogger = IO Logger
stderrLogger
        , argsRules :: Rules ()
argsRules = Rules ()
mainRule Rules () -> Rules () -> Rules ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Action () -> Rules ()
forall a. Action a -> Rules ()
action Action ()
kick
        , argsGhcidePlugin :: Plugin Config
argsGhcidePlugin = Plugin Config
forall a. Monoid a => a
mempty
        , argsHlsPlugins :: IdePlugins IdeState
argsHlsPlugins = [PluginDescriptor IdeState] -> IdePlugins IdeState
forall ideState. [PluginDescriptor ideState] -> IdePlugins ideState
pluginDescToIdePlugins [PluginDescriptor IdeState]
Ghcide.descriptors
        , argsSessionLoadingOptions :: SessionLoadingOptions
argsSessionLoadingOptions = SessionLoadingOptions
forall a. Default a => a
def
        , argsIdeOptions :: Config -> Action IdeGhcSession -> IdeOptions
argsIdeOptions = (Action IdeGhcSession -> IdeOptions)
-> Config -> Action IdeGhcSession -> IdeOptions
forall a b. a -> b -> a
const Action IdeGhcSession -> IdeOptions
defaultIdeOptions
        , argsLspOptions :: Options
argsLspOptions = Options
forall a. Default a => a
def {completionTriggerCharacters :: Maybe FilePath
LSP.completionTriggerCharacters = FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
"."}
        , argsDefaultHlsConfig :: Config
argsDefaultHlsConfig = Config
forall a. Default a => a
def
        , argsGetHieDbLoc :: FilePath -> IO FilePath
argsGetHieDbLoc = FilePath -> IO FilePath
getHieDbLoc
        , argsDebouncer :: IO (Debouncer NormalizedUri)
argsDebouncer = IO (Debouncer NormalizedUri)
forall k. (Eq k, Hashable k) => IO (Debouncer k)
newAsyncDebouncer
        , argsHandleIn :: IO Handle
argsHandleIn = Handle -> IO Handle
forall (f :: * -> *) a. Applicative f => a -> f a
pure Handle
stdin
        , argsHandleOut :: IO Handle
argsHandleOut = do
                -- Move stdout to another file descriptor and duplicate stderr
                -- to stdout. This guards against stray prints from corrupting the JSON-RPC
                -- message stream.
                Handle
newStdout <- Handle -> IO Handle
hDuplicate Handle
stdout
                Handle
stderr Handle -> Handle -> IO ()
`hDuplicateTo'` Handle
stdout
                Handle -> BufferMode -> IO ()
hSetBuffering Handle
stdout BufferMode
NoBuffering

                -- Print out a single space to assert that the above redirection works.
                -- This is interleaved with the logger, hence we just print a space here in
                -- order not to mess up the output too much. Verified that this breaks
                -- the language server tests without the redirection.
                FilePath -> IO ()
putStr FilePath
" " IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Handle -> IO ()
hFlush Handle
stdout
                return Handle
newStdout
        }

-- | Cheap stderr logger that relies on LineBuffering
stderrLogger :: IO Logger
stderrLogger :: IO Logger
stderrLogger = do
    Lock
lock <- IO Lock
newLock
    return $ (Priority -> Text -> IO ()) -> Logger
Logger ((Priority -> Text -> IO ()) -> Logger)
-> (Priority -> Text -> IO ()) -> Logger
forall a b. (a -> b) -> a -> b
$ \Priority
p Text
m -> Lock -> IO () -> IO ()
forall a. Lock -> IO a -> IO a
withLock Lock
lock (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        Handle -> Text -> IO ()
T.hPutStrLn Handle
stderr (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Text
"[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FilePath -> Text
T.pack (Priority -> FilePath
forall a. Show a => a -> FilePath
show Priority
p) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"] " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
m

defaultMain :: Arguments -> IO ()
defaultMain :: Arguments -> IO ()
defaultMain Arguments{Bool
IO Handle
IO (Debouncer NormalizedUri)
IO Logger
Rules ()
IdePlugins IdeState
Config
Options
SessionLoadingOptions
Plugin Config
Command
FilePath -> IO FilePath
Config -> Action IdeGhcSession -> IdeOptions
argsHandleOut :: IO Handle
argsHandleIn :: IO Handle
argsDebouncer :: IO (Debouncer NormalizedUri)
argsGetHieDbLoc :: FilePath -> IO FilePath
argsDefaultHlsConfig :: Config
argsLspOptions :: Options
argsIdeOptions :: Config -> Action IdeGhcSession -> IdeOptions
argsSessionLoadingOptions :: SessionLoadingOptions
argsGhcidePlugin :: Plugin Config
argsHlsPlugins :: IdePlugins IdeState
argsRules :: Rules ()
argsLogger :: IO Logger
argCommand :: Command
argsOTMemoryProfiling :: Bool
argsHandleOut :: Arguments -> IO Handle
argsHandleIn :: Arguments -> IO Handle
argsDebouncer :: Arguments -> IO (Debouncer NormalizedUri)
argsGetHieDbLoc :: Arguments -> FilePath -> IO FilePath
argsDefaultHlsConfig :: Arguments -> Config
argsLspOptions :: Arguments -> Options
argsIdeOptions :: Arguments -> Config -> Action IdeGhcSession -> IdeOptions
argsSessionLoadingOptions :: Arguments -> SessionLoadingOptions
argsGhcidePlugin :: Arguments -> Plugin Config
argsHlsPlugins :: Arguments -> IdePlugins IdeState
argsRules :: Arguments -> Rules ()
argsLogger :: Arguments -> IO Logger
argCommand :: Arguments -> Command
argsOTMemoryProfiling :: Arguments -> Bool
..} = do
    TextEncoding -> IO ()
setLocaleEncoding TextEncoding
utf8
    Text
pid <- FilePath -> Text
T.pack (FilePath -> Text) -> (Int -> FilePath) -> Int -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> FilePath
forall a. Show a => a -> FilePath
show (Int -> Text) -> IO Int -> IO Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO Int
getProcessID
    Logger
logger <- IO Logger
argsLogger
    Handle -> BufferMode -> IO ()
hSetBuffering Handle
stderr BufferMode
LineBuffering

    let hlsPlugin :: Plugin Config
hlsPlugin = IdePlugins IdeState -> Plugin Config
asGhcIdePlugin IdePlugins IdeState
argsHlsPlugins
        hlsCommands :: [Text]
hlsCommands = Text -> IdePlugins IdeState -> [Text]
forall ideState. Text -> IdePlugins ideState -> [Text]
allLspCmdIds' Text
pid IdePlugins IdeState
argsHlsPlugins
        plugins :: Plugin Config
plugins = Plugin Config
hlsPlugin Plugin Config -> Plugin Config -> Plugin Config
forall a. Semigroup a => a -> a -> a
<> Plugin Config
argsGhcidePlugin
        options :: Options
options = Options
argsLspOptions { executeCommandCommands :: Maybe [Text]
LSP.executeCommandCommands = Options -> Maybe [Text]
LSP.executeCommandCommands Options
argsLspOptions Maybe [Text] -> Maybe [Text] -> Maybe [Text]
forall a. Semigroup a => a -> a -> a
<> [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
hlsCommands }
        argsOnConfigChange :: Config -> Value -> Either Text Config
argsOnConfigChange = Config -> Value -> Either Text Config
getConfigFromNotification
        rules :: Rules ()
rules = Rules ()
argsRules Rules () -> Rules () -> Rules ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Plugin Config -> Rules ()
forall c. Plugin c -> Rules ()
pluginRules Plugin Config
plugins

    Debouncer NormalizedUri
debouncer <- IO (Debouncer NormalizedUri)
argsDebouncer
    Handle
inH <- IO Handle
argsHandleIn
    Handle
outH <- IO Handle
argsHandleOut

    case Command
argCommand of
        Command
PrintExtensionSchema ->
            Text -> IO ()
LT.putStrLn (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ ByteString -> Text
decodeUtf8 (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ Value -> ByteString
forall a. ToJSON a => a -> ByteString
A.encodePretty (Value -> ByteString) -> Value -> ByteString
forall a b. (a -> b) -> a -> b
$ IdePlugins IdeState -> Value
forall a. IdePlugins a -> Value
pluginsToVSCodeExtensionSchema IdePlugins IdeState
argsHlsPlugins
        Command
PrintDefaultConfig ->
            Text -> IO ()
LT.putStrLn (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ ByteString -> Text
decodeUtf8 (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ Value -> ByteString
forall a. ToJSON a => a -> ByteString
A.encodePretty (Value -> ByteString) -> Value -> ByteString
forall a b. (a -> b) -> a -> b
$ IdePlugins IdeState -> Value
forall a. IdePlugins a -> Value
pluginsToDefaultConfig IdePlugins IdeState
argsHlsPlugins
        Command
LSP -> do
            IO Seconds
t <- IO (IO Seconds)
offsetTime
            Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr FilePath
"Starting LSP server..."
            Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr FilePath
"If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option!"
            Options
-> Handle
-> Handle
-> (FilePath -> IO FilePath)
-> Config
-> (Config -> Value -> Either Text Config)
-> Handlers (ServerM Config)
-> (LanguageContextEnv Config
    -> VFSHandle
    -> Maybe FilePath
    -> HieDb
    -> IndexQueue
    -> IO IdeState)
-> IO ()
forall config.
Show config =>
Options
-> Handle
-> Handle
-> (FilePath -> IO FilePath)
-> config
-> (config -> Value -> Either Text config)
-> Handlers (ServerM config)
-> (LanguageContextEnv config
    -> VFSHandle
    -> Maybe FilePath
    -> HieDb
    -> IndexQueue
    -> IO IdeState)
-> IO ()
runLanguageServer Options
options Handle
inH Handle
outH FilePath -> IO FilePath
argsGetHieDbLoc Config
argsDefaultHlsConfig Config -> Value -> Either Text Config
argsOnConfigChange (Plugin Config -> Handlers (ServerM Config)
forall c. Plugin c -> Handlers (ServerM c)
pluginHandlers Plugin Config
plugins) ((LanguageContextEnv Config
  -> VFSHandle
  -> Maybe FilePath
  -> HieDb
  -> IndexQueue
  -> IO IdeState)
 -> IO ())
-> (LanguageContextEnv Config
    -> VFSHandle
    -> Maybe FilePath
    -> HieDb
    -> IndexQueue
    -> IO IdeState)
-> IO ()
forall a b. (a -> b) -> a -> b
$ \LanguageContextEnv Config
env VFSHandle
vfs Maybe FilePath
rootPath HieDb
hiedb IndexQueue
hieChan -> do
                (FilePath -> IO ()) -> Maybe FilePath -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ FilePath -> IO ()
IO.setCurrentDirectory Maybe FilePath
rootPath
                Seconds
t <- IO Seconds
t
                Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Started LSP server in " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ Seconds -> FilePath
showDuration Seconds
t

                FilePath
dir <- IO FilePath
-> (FilePath -> IO FilePath) -> Maybe FilePath -> IO FilePath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IO FilePath
IO.getCurrentDirectory FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FilePath
rootPath

                -- We want to set the global DynFlags right now, so that we can use
                -- `unsafeGlobalDynFlags` even before the project is configured
                Maybe LibDir
_mlibdir <-
                    FilePath -> SessionLoadingOptions -> IO (Maybe LibDir)
setInitialDynFlags FilePath
dir SessionLoadingOptions
argsSessionLoadingOptions
                        IO (Maybe LibDir)
-> (SomeException -> IO (Maybe LibDir)) -> IO (Maybe LibDir)
forall (m :: * -> *) a.
MonadCatch m =>
m a -> (SomeException -> m a) -> m a
`catchAny` (\SomeException
e -> (Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"setInitialDynFlags: " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ SomeException -> FilePath
forall e. Exception e => e -> FilePath
displayException SomeException
e) IO () -> IO (Maybe LibDir) -> IO (Maybe LibDir)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe LibDir -> IO (Maybe LibDir)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe LibDir
forall a. Maybe a
Nothing)


                Action IdeGhcSession
sessionLoader <- SessionLoadingOptions -> FilePath -> IO (Action IdeGhcSession)
loadSessionWithOptions SessionLoadingOptions
argsSessionLoadingOptions FilePath
dir
                Config
config <- LanguageContextEnv Config -> LspT Config IO Config -> IO Config
forall config (m :: * -> *) a.
LanguageContextEnv config -> LspT config m a -> m a
LSP.runLspT LanguageContextEnv Config
env LspT Config IO Config
forall config (m :: * -> *). MonadLsp config m => m config
LSP.getConfig
                let def_options :: IdeOptions
def_options = Config -> Action IdeGhcSession -> IdeOptions
argsIdeOptions Config
config Action IdeGhcSession
sessionLoader

                -- disable runSubset if the client doesn't support watched files
                Bool
runSubset <- (IdeOptions -> Bool
optRunSubset IdeOptions
def_options Bool -> Bool -> Bool
&&) (Bool -> Bool) -> IO Bool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LanguageContextEnv Config -> LspT Config IO Bool -> IO Bool
forall config (m :: * -> *) a.
LanguageContextEnv config -> LspT config m a -> m a
LSP.runLspT LanguageContextEnv Config
env LspT Config IO Bool
isWatchSupported

                let options :: IdeOptions
options = IdeOptions
def_options
                            { optReportProgress :: IdeReportProgress
optReportProgress = ClientCapabilities -> IdeReportProgress
clientSupportsProgress ClientCapabilities
caps
                            , optModifyDynFlags :: Config -> DynFlagsModifications
optModifyDynFlags = IdeOptions -> Config -> DynFlagsModifications
optModifyDynFlags IdeOptions
def_options (Config -> DynFlagsModifications)
-> (Config -> DynFlagsModifications)
-> Config
-> DynFlagsModifications
forall a. Semigroup a => a -> a -> a
<> Plugin Config -> Config -> DynFlagsModifications
forall c. Plugin c -> c -> DynFlagsModifications
pluginModifyDynflags Plugin Config
plugins
                            , optRunSubset :: Bool
optRunSubset = Bool
runSubset
                            }
                    caps :: ClientCapabilities
caps = LanguageContextEnv Config -> ClientCapabilities
forall config. LanguageContextEnv config -> ClientCapabilities
LSP.resClientCapabilities LanguageContextEnv Config
env
                -- FIXME: Remove this after GHC 9 gets fully supported
                Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (GhcVersion
ghcVersion GhcVersion -> GhcVersion -> Bool
forall a. Eq a => a -> a -> Bool
== GhcVersion
GHC90) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
                    Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$
                        FilePath
"Currently, HLS supports GHC 9 only partially. "
                        FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
"See [issue #297](https://github.com/haskell/haskell-language-server/issues/297) for more detail."
                Config
-> Rules ()
-> Maybe (LanguageContextEnv Config)
-> Logger
-> Debouncer NormalizedUri
-> IdeOptions
-> VFSHandle
-> HieDb
-> IndexQueue
-> IO IdeState
initialise
                    Config
argsDefaultHlsConfig
                    Rules ()
rules
                    (LanguageContextEnv Config -> Maybe (LanguageContextEnv Config)
forall a. a -> Maybe a
Just LanguageContextEnv Config
env)
                    Logger
logger
                    Debouncer NormalizedUri
debouncer
                    IdeOptions
options
                    VFSHandle
vfs
                    HieDb
hiedb
                    IndexQueue
hieChan
        Check [FilePath]
argFiles -> do
          FilePath
dir <- IO FilePath
IO.getCurrentDirectory
          FilePath
dbLoc <- FilePath -> IO FilePath
getHieDbLoc FilePath
dir
          FilePath -> (HieDb -> IndexQueue -> IO ()) -> IO ()
runWithDb FilePath
dbLoc ((HieDb -> IndexQueue -> IO ()) -> IO ())
-> (HieDb -> IndexQueue -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \HieDb
hiedb IndexQueue
hieChan -> do
            -- GHC produces messages with UTF8 in them, so make sure the terminal doesn't error
            Handle -> TextEncoding -> IO ()
hSetEncoding Handle
stdout TextEncoding
utf8
            Handle -> TextEncoding -> IO ()
hSetEncoding Handle
stderr TextEncoding
utf8

            FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"ghcide setup tester in " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
dir FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"."
            FilePath -> IO ()
putStrLn FilePath
"Report bugs at https://github.com/haskell/haskell-language-server/issues"

            FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"\nStep 1/4: Finding files to test in " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
dir
            [FilePath]
files <- [FilePath] -> IO [FilePath]
expandFiles ([FilePath]
argFiles [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath
"." | [FilePath] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
argFiles])
            -- LSP works with absolute file paths, so try and behave similarly
            [FilePath]
files <- [FilePath] -> [FilePath]
forall a. Ord a => [a] -> [a]
nubOrd ([FilePath] -> [FilePath]) -> IO [FilePath] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (FilePath -> IO FilePath) -> [FilePath] -> IO [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM FilePath -> IO FilePath
IO.canonicalizePath [FilePath]
files
            FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Found " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> FilePath
forall a. Show a => a -> FilePath
show ([FilePath] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [FilePath]
files) FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" files"

            FilePath -> IO ()
putStrLn FilePath
"\nStep 2/4: Looking for hie.yaml files that control setup"
            [Maybe FilePath]
cradles <- (FilePath -> IO (Maybe FilePath))
-> [FilePath] -> IO [Maybe FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM FilePath -> IO (Maybe FilePath)
findCradle [FilePath]
files
            let ucradles :: [Maybe FilePath]
ucradles = [Maybe FilePath] -> [Maybe FilePath]
forall a. Ord a => [a] -> [a]
nubOrd [Maybe FilePath]
cradles
            let n :: Int
n = [Maybe FilePath] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Maybe FilePath]
ucradles
            FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Found " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> FilePath
forall a. Show a => a -> FilePath
show Int
n FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" cradle" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char
's' | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
1]
            Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"  (" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
intercalate FilePath
", " ([Maybe FilePath] -> [FilePath]
forall a. [Maybe a] -> [a]
catMaybes [Maybe FilePath]
ucradles) FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
")"
            FilePath -> IO ()
putStrLn FilePath
"\nStep 3/4: Initializing the IDE"
            VFSHandle
vfs <- IO VFSHandle
makeVFSHandle
            Action IdeGhcSession
sessionLoader <- SessionLoadingOptions -> FilePath -> IO (Action IdeGhcSession)
loadSessionWithOptions SessionLoadingOptions
argsSessionLoadingOptions FilePath
dir
            let def_options :: IdeOptions
def_options = Config -> Action IdeGhcSession -> IdeOptions
argsIdeOptions Config
argsDefaultHlsConfig Action IdeGhcSession
sessionLoader
                options :: IdeOptions
options = IdeOptions
def_options
                        { optCheckParents :: IO CheckParents
optCheckParents = CheckParents -> IO CheckParents
forall (f :: * -> *) a. Applicative f => a -> f a
pure CheckParents
NeverCheck
                        , optCheckProject :: IO Bool
optCheckProject = Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
                        , optModifyDynFlags :: Config -> DynFlagsModifications
optModifyDynFlags = IdeOptions -> Config -> DynFlagsModifications
optModifyDynFlags IdeOptions
def_options (Config -> DynFlagsModifications)
-> (Config -> DynFlagsModifications)
-> Config
-> DynFlagsModifications
forall a. Semigroup a => a -> a -> a
<> Plugin Config -> Config -> DynFlagsModifications
forall c. Plugin c -> c -> DynFlagsModifications
pluginModifyDynflags Plugin Config
plugins
                        }
            IdeState
ide <- Config
-> Rules ()
-> Maybe (LanguageContextEnv Config)
-> Logger
-> Debouncer NormalizedUri
-> IdeOptions
-> VFSHandle
-> HieDb
-> IndexQueue
-> IO IdeState
initialise Config
argsDefaultHlsConfig Rules ()
rules Maybe (LanguageContextEnv Config)
forall a. Maybe a
Nothing Logger
logger Debouncer NormalizedUri
debouncer IdeOptions
options VFSHandle
vfs HieDb
hiedb IndexQueue
hieChan
            IdeState -> IO ()
shakeSessionInit IdeState
ide
            ShakeExtras -> IdeConfiguration -> IO ()
registerIdeConfiguration (IdeState -> ShakeExtras
shakeExtras IdeState
ide) (IdeConfiguration -> IO ()) -> IdeConfiguration -> IO ()
forall a b. (a -> b) -> a -> b
$ HashSet NormalizedUri -> Hashed (Maybe Value) -> IdeConfiguration
IdeConfiguration HashSet NormalizedUri
forall a. Monoid a => a
mempty (Maybe Value -> Hashed (Maybe Value)
forall a. Hashable a => a -> Hashed a
hashed Maybe Value
forall a. Maybe a
Nothing)

            FilePath -> IO ()
putStrLn FilePath
"\nStep 4/4: Type checking the files"
            IdeState
-> HashMap NormalizedFilePath FileOfInterestStatus -> IO ()
setFilesOfInterest IdeState
ide (HashMap NormalizedFilePath FileOfInterestStatus -> IO ())
-> HashMap NormalizedFilePath FileOfInterestStatus -> IO ()
forall a b. (a -> b) -> a -> b
$ [(NormalizedFilePath, FileOfInterestStatus)]
-> HashMap NormalizedFilePath FileOfInterestStatus
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList ([(NormalizedFilePath, FileOfInterestStatus)]
 -> HashMap NormalizedFilePath FileOfInterestStatus)
-> [(NormalizedFilePath, FileOfInterestStatus)]
-> HashMap NormalizedFilePath FileOfInterestStatus
forall a b. (a -> b) -> a -> b
$ (FilePath -> (NormalizedFilePath, FileOfInterestStatus))
-> [FilePath] -> [(NormalizedFilePath, FileOfInterestStatus)]
forall a b. (a -> b) -> [a] -> [b]
map ((,FileOfInterestStatus
OnDisk) (NormalizedFilePath -> (NormalizedFilePath, FileOfInterestStatus))
-> (FilePath -> NormalizedFilePath)
-> FilePath
-> (NormalizedFilePath, FileOfInterestStatus)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> NormalizedFilePath
toNormalizedFilePath') [FilePath]
files
            [Maybe TcModuleResult]
results <- FilePath
-> IdeState
-> Action [Maybe TcModuleResult]
-> IO [Maybe TcModuleResult]
forall a. FilePath -> IdeState -> Action a -> IO a
runAction FilePath
"User TypeCheck" IdeState
ide (Action [Maybe TcModuleResult] -> IO [Maybe TcModuleResult])
-> Action [Maybe TcModuleResult] -> IO [Maybe TcModuleResult]
forall a b. (a -> b) -> a -> b
$ TypeCheck -> [NormalizedFilePath] -> Action [Maybe TcModuleResult]
forall k v.
IdeRule k v =>
k -> [NormalizedFilePath] -> Action [Maybe v]
uses TypeCheck
TypeCheck ((FilePath -> NormalizedFilePath)
-> [FilePath] -> [NormalizedFilePath]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> NormalizedFilePath
toNormalizedFilePath' [FilePath]
files)
            [Maybe HieAstResult]
_results <- FilePath
-> IdeState
-> Action [Maybe HieAstResult]
-> IO [Maybe HieAstResult]
forall a. FilePath -> IdeState -> Action a -> IO a
runAction FilePath
"GetHie" IdeState
ide (Action [Maybe HieAstResult] -> IO [Maybe HieAstResult])
-> Action [Maybe HieAstResult] -> IO [Maybe HieAstResult]
forall a b. (a -> b) -> a -> b
$ GetHieAst -> [NormalizedFilePath] -> Action [Maybe HieAstResult]
forall k v.
IdeRule k v =>
k -> [NormalizedFilePath] -> Action [Maybe v]
uses GetHieAst
GetHieAst ((FilePath -> NormalizedFilePath)
-> [FilePath] -> [NormalizedFilePath]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> NormalizedFilePath
toNormalizedFilePath' [FilePath]
files)
            [Maybe ModGuts]
_results <- FilePath
-> IdeState -> Action [Maybe ModGuts] -> IO [Maybe ModGuts]
forall a. FilePath -> IdeState -> Action a -> IO a
runAction FilePath
"GenerateCore" IdeState
ide (Action [Maybe ModGuts] -> IO [Maybe ModGuts])
-> Action [Maybe ModGuts] -> IO [Maybe ModGuts]
forall a b. (a -> b) -> a -> b
$ GenerateCore -> [NormalizedFilePath] -> Action [Maybe ModGuts]
forall k v.
IdeRule k v =>
k -> [NormalizedFilePath] -> Action [Maybe v]
uses GenerateCore
GenerateCore ((FilePath -> NormalizedFilePath)
-> [FilePath] -> [NormalizedFilePath]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> NormalizedFilePath
toNormalizedFilePath' [FilePath]
files)
            let ([(Bool, FilePath)]
worked, [(Bool, FilePath)]
failed) = ((Bool, FilePath) -> Bool)
-> [(Bool, FilePath)] -> ([(Bool, FilePath)], [(Bool, FilePath)])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (Bool, FilePath) -> Bool
forall a b. (a, b) -> a
fst ([(Bool, FilePath)] -> ([(Bool, FilePath)], [(Bool, FilePath)]))
-> [(Bool, FilePath)] -> ([(Bool, FilePath)], [(Bool, FilePath)])
forall a b. (a -> b) -> a -> b
$ [Bool] -> [FilePath] -> [(Bool, FilePath)]
forall a b. [a] -> [b] -> [(a, b)]
zip ((Maybe TcModuleResult -> Bool) -> [Maybe TcModuleResult] -> [Bool]
forall a b. (a -> b) -> [a] -> [b]
map Maybe TcModuleResult -> Bool
forall a. Maybe a -> Bool
isJust [Maybe TcModuleResult]
results) [FilePath]
files
            Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([(Bool, FilePath)]
failed [(Bool, FilePath)] -> [(Bool, FilePath)] -> Bool
forall a. Eq a => a -> a -> Bool
/= []) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
                FilePath -> IO ()
putStr (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
unlines ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
"Files that failed:" FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: ((Bool, FilePath) -> FilePath) -> [(Bool, FilePath)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> ShowS
forall a. [a] -> [a] -> [a]
(++) FilePath
" * " ShowS
-> ((Bool, FilePath) -> FilePath) -> (Bool, FilePath) -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool, FilePath) -> FilePath
forall a b. (a, b) -> b
snd) [(Bool, FilePath)]
failed

            let nfiles :: t a -> FilePath
nfiles t a
xs = let n :: Int
n = t a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length t a
xs in if Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 then FilePath
"1 file" else Int -> FilePath
forall a. Show a => a -> FilePath
show Int
n FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" files"
            FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"\nCompleted (" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ [(Bool, FilePath)] -> FilePath
forall (t :: * -> *) a. Foldable t => t a -> FilePath
nfiles [(Bool, FilePath)]
worked FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" worked, " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ [(Bool, FilePath)] -> FilePath
forall (t :: * -> *) a. Foldable t => t a -> FilePath
nfiles [(Bool, FilePath)]
failed FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" failed)"

            Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
argsOTMemoryProfiling (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
                let valuesRef :: Var Values
valuesRef = ShakeExtras -> Var Values
state (ShakeExtras -> Var Values) -> ShakeExtras -> Var Values
forall a b. (a -> b) -> a -> b
$ IdeState -> ShakeExtras
shakeExtras IdeState
ide
                Values
values <- Var Values -> IO Values
forall a. Var a -> IO a
readVar Var Values
valuesRef
                let consoleObserver :: Maybe a -> m (Int -> t)
consoleObserver Maybe a
Nothing = (Int -> t) -> m (Int -> t)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int -> t) -> m (Int -> t)) -> (Int -> t) -> m (Int -> t)
forall a b. (a -> b) -> a -> b
$ \Int
size -> FilePath -> Seconds -> t
forall r. PrintfType r => FilePath -> r
printf FilePath
"Total: %.2fMB\n" (Int -> Seconds
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int @Double Int
size Seconds -> Seconds -> Seconds
forall a. Fractional a => a -> a -> a
/ Seconds
1e6)
                    consoleObserver (Just a
k) = (Int -> t) -> m (Int -> t)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int -> t) -> m (Int -> t)) -> (Int -> t) -> m (Int -> t)
forall a b. (a -> b) -> a -> b
$ \Int
size -> FilePath -> FilePath -> Seconds -> t
forall r. PrintfType r => FilePath -> r
printf FilePath
"  - %s: %.2fKB\n" (a -> FilePath
forall a. Show a => a -> FilePath
show a
k) (Int -> Seconds
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int @Double Int
size Seconds -> Seconds -> Seconds
forall a. Fractional a => a -> a -> a
/ Seconds
1e3)

                FilePath -> Int -> IO ()
forall r. PrintfType r => FilePath -> r
printf FilePath
"# Shake value store contents(%d):\n" (Values -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Values
values)
                let keys :: [Key]
keys =
                        [Key] -> [Key]
forall a. Eq a => [a] -> [a]
nub ([Key] -> [Key]) -> [Key] -> [Key]
forall a b. (a -> b) -> a -> b
$
                            GhcSession -> Key
forall k.
(Typeable k, Hashable k, Eq k, NFData k, Show k) =>
k -> Key
Key GhcSession
GhcSession Key -> [Key] -> [Key]
forall a. a -> [a] -> [a]
:
                            GhcSessionDeps -> Key
forall k.
(Typeable k, Hashable k, Eq k, NFData k, Show k) =>
k -> Key
Key GhcSessionDeps
GhcSessionDeps Key -> [Key] -> [Key]
forall a. a -> [a] -> [a]
:
                            [Key
k | (NormalizedFilePath
_, Key
k) <- Values -> [(NormalizedFilePath, Key)]
forall k v. HashMap k v -> [k]
HashMap.keys Values
values, Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
/= GhcSessionIO -> Key
forall k.
(Typeable k, Hashable k, Eq k, NFData k, Show k) =>
k -> Key
Key GhcSessionIO
GhcSessionIO]
                            [Key] -> [Key] -> [Key]
forall a. [a] -> [a] -> [a]
++ [GhcSessionIO -> Key
forall k.
(Typeable k, Hashable k, Eq k, NFData k, Show k) =>
k -> Key
Key GhcSessionIO
GhcSessionIO]
                Logger
-> [[Key]]
-> (Maybe Key -> IO (Int -> IO ()))
-> Var Values
-> IO ()
measureMemory Logger
logger [[Key]
keys] Maybe Key -> IO (Int -> IO ())
forall (m :: * -> *) t a.
(Monad m, PrintfType t, Show a) =>
Maybe a -> m (Int -> t)
consoleObserver Var Values
valuesRef

            Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([(Bool, FilePath)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Bool, FilePath)]
failed) (ExitCode -> IO ()
forall a. ExitCode -> IO a
exitWith (ExitCode -> IO ()) -> ExitCode -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> ExitCode
ExitFailure ([(Bool, FilePath)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Bool, FilePath)]
failed))
        Db FilePath
dir Options
opts Command
cmd -> do
            FilePath
dbLoc <- FilePath -> IO FilePath
getHieDbLoc FilePath
dir
            Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Using hiedb at: " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
dbLoc
            Maybe LibDir
mlibdir <- FilePath -> SessionLoadingOptions -> IO (Maybe LibDir)
setInitialDynFlags FilePath
dir SessionLoadingOptions
forall a. Default a => a
def
            case Maybe LibDir
mlibdir of
                Maybe LibDir
Nothing     -> ExitCode -> IO ()
forall a. ExitCode -> IO a
exitWith (ExitCode -> IO ()) -> ExitCode -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> ExitCode
ExitFailure Int
1
                Just LibDir
libdir -> LibDir -> Options -> Command -> IO ()
HieDb.runCommand LibDir
libdir Options
opts{database :: FilePath
HieDb.database = FilePath
dbLoc} Command
cmd

        Custom FilePath
projectRoot (IdeCommand IdeState -> IO ()
c) -> do
          FilePath
dbLoc <- FilePath -> IO FilePath
getHieDbLoc FilePath
projectRoot
          FilePath -> (HieDb -> IndexQueue -> IO ()) -> IO ()
runWithDb FilePath
dbLoc ((HieDb -> IndexQueue -> IO ()) -> IO ())
-> (HieDb -> IndexQueue -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \HieDb
hiedb IndexQueue
hieChan -> do
            VFSHandle
vfs <- IO VFSHandle
makeVFSHandle
            Action IdeGhcSession
sessionLoader <- SessionLoadingOptions -> FilePath -> IO (Action IdeGhcSession)
loadSessionWithOptions SessionLoadingOptions
argsSessionLoadingOptions FilePath
"."
            let def_options :: IdeOptions
def_options = Config -> Action IdeGhcSession -> IdeOptions
argsIdeOptions Config
argsDefaultHlsConfig Action IdeGhcSession
sessionLoader
                options :: IdeOptions
options = IdeOptions
def_options
                    { optCheckParents :: IO CheckParents
optCheckParents = CheckParents -> IO CheckParents
forall (f :: * -> *) a. Applicative f => a -> f a
pure CheckParents
NeverCheck
                    , optCheckProject :: IO Bool
optCheckProject = Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
                    , optModifyDynFlags :: Config -> DynFlagsModifications
optModifyDynFlags = IdeOptions -> Config -> DynFlagsModifications
optModifyDynFlags IdeOptions
def_options (Config -> DynFlagsModifications)
-> (Config -> DynFlagsModifications)
-> Config
-> DynFlagsModifications
forall a. Semigroup a => a -> a -> a
<> Plugin Config -> Config -> DynFlagsModifications
forall c. Plugin c -> c -> DynFlagsModifications
pluginModifyDynflags Plugin Config
plugins
                    }
            IdeState
ide <- Config
-> Rules ()
-> Maybe (LanguageContextEnv Config)
-> Logger
-> Debouncer NormalizedUri
-> IdeOptions
-> VFSHandle
-> HieDb
-> IndexQueue
-> IO IdeState
initialise Config
argsDefaultHlsConfig Rules ()
rules Maybe (LanguageContextEnv Config)
forall a. Maybe a
Nothing Logger
logger Debouncer NormalizedUri
debouncer IdeOptions
options VFSHandle
vfs HieDb
hiedb IndexQueue
hieChan
            IdeState -> IO ()
shakeSessionInit IdeState
ide
            ShakeExtras -> IdeConfiguration -> IO ()
registerIdeConfiguration (IdeState -> ShakeExtras
shakeExtras IdeState
ide) (IdeConfiguration -> IO ()) -> IdeConfiguration -> IO ()
forall a b. (a -> b) -> a -> b
$ HashSet NormalizedUri -> Hashed (Maybe Value) -> IdeConfiguration
IdeConfiguration HashSet NormalizedUri
forall a. Monoid a => a
mempty (Maybe Value -> Hashed (Maybe Value)
forall a. Hashable a => a -> Hashed a
hashed Maybe Value
forall a. Maybe a
Nothing)
            IdeState -> IO ()
c IdeState
ide

{-# ANN defaultMain ("HLint: ignore Use nubOrd" :: String) #-}


expandFiles :: [FilePath] -> IO [FilePath]
expandFiles :: [FilePath] -> IO [FilePath]
expandFiles = (FilePath -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM ((FilePath -> IO [FilePath]) -> [FilePath] -> IO [FilePath])
-> (FilePath -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ \FilePath
x -> do
    Bool
b <- FilePath -> IO Bool
IO.doesFileExist FilePath
x
    if Bool
b
        then [FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return [FilePath
x]
        else do
            let recurse :: FilePath -> Bool
recurse FilePath
"." = Bool
True
                recurse FilePath
x | FilePath
"." FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` ShowS
takeFileName FilePath
x = Bool
False -- skip .git etc
                recurse FilePath
x = ShowS
takeFileName FilePath
x FilePath -> [FilePath] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [FilePath
"dist", FilePath
"dist-newstyle"] -- cabal directories
            [FilePath]
files <- (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (\FilePath
x -> ShowS
takeExtension FilePath
x FilePath -> [FilePath] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [FilePath
".hs", FilePath
".lhs"]) ([FilePath] -> [FilePath]) -> IO [FilePath] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (FilePath -> IO Bool) -> FilePath -> IO [FilePath]
IO.listFilesInside (Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> (FilePath -> Bool) -> FilePath -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Bool
recurse) FilePath
x
            Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([FilePath] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
files) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
                FilePath -> IO ()
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Couldn't find any .hs/.lhs files inside directory: " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
x
            return [FilePath]
files