Skip to content
This repository has been archived by the owner on Oct 7, 2020. It is now read-only.

First pass at printing out debug info if started without --lsp #1538

Merged
merged 2 commits into from
Jan 2, 2020
Merged
Show file tree
Hide file tree
Changes from 1 commit
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
73 changes: 55 additions & 18 deletions app/MainHie.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,13 @@
{-# LANGUAGE RankNTypes #-}
module Main where

import qualified Control.Exception as E
import Control.Monad
import Data.Monoid ((<>))
import Data.Version (showVersion)
import qualified Data.Yaml as Yaml
import HIE.Bios.Types
import Haskell.Ide.Engine.Cradle (findLocalCradle, cradleDisplay)
import Haskell.Ide.Engine.MonadFunctions
import Haskell.Ide.Engine.MonadTypes
import Haskell.Ide.Engine.Options
Expand All @@ -16,26 +20,26 @@ import Options.Applicative.Simple
import qualified Paths_haskell_ide_engine as Meta
import System.Directory
import System.Environment
import qualified System.Log.Logger as L
import HIE.Bios.Types
import System.FilePath ((</>))
import System.IO
import qualified System.Log.Logger as L

-- ---------------------------------------------------------------------
-- plugins

import Haskell.Ide.Engine.Plugin.ApplyRefact
import Haskell.Ide.Engine.Plugin.Brittany
import Haskell.Ide.Engine.Plugin.Example2
import Haskell.Ide.Engine.Plugin.Floskell
import Haskell.Ide.Engine.Plugin.Generic
import Haskell.Ide.Engine.Plugin.GhcMod
-- import Haskell.Ide.Engine.Plugin.HaRe
import Haskell.Ide.Engine.Plugin.Haddock
import Haskell.Ide.Engine.Plugin.HfaAlign
import Haskell.Ide.Engine.Plugin.HsImport
import Haskell.Ide.Engine.Plugin.Liquid
import Haskell.Ide.Engine.Plugin.Package
import Haskell.Ide.Engine.Plugin.Pragmas
import Haskell.Ide.Engine.Plugin.Floskell
import Haskell.Ide.Engine.Plugin.Generic
import Haskell.Ide.Engine.Plugin.GhcMod

-- ---------------------------------------------------------------------

Expand Down Expand Up @@ -110,23 +114,56 @@ run opts = do
maybe (pure ()) setCurrentDirectory $ projectRoot opts

progName <- getProgName
logm $ "Run entered for HIE(" ++ progName ++ ") " ++ hieVersion
logm $ "Current directory:" ++ origDir
args <- getArgs
logm $ "args:" ++ show args

let initOpts = defaultCradleOpts { cradleOptsVerbosity = verbosity }
verbosity = if optBiosVerbose opts then Verbose else Silent
if optLsp opts
then do
-- Start up in LSP mode
logm $ "Run entered for HIE(" ++ progName ++ ") " ++ hieVersion
logm $ "Current directory:" ++ origDir
logm $ "args:" ++ show args

let initOpts = defaultCradleOpts { cradleOptsVerbosity = verbosity }
verbosity = if optBiosVerbose opts then Verbose else Silent


when (optBiosVerbose opts) $
logm "Enabling verbose mode for hie-bios. This option currently doesn't do anything."
when (optBiosVerbose opts) $
logm "Enabling verbose mode for hie-bios. This option currently doesn't do anything."

when (optExamplePlugin opts) $
logm "Enabling Example2 plugin, will insert constant diagnostics etc."
when (optExamplePlugin opts) $
logm "Enabling Example2 plugin, will insert constant diagnostics etc."

let plugins' = plugins (optExamplePlugin opts)
let plugins' = plugins (optExamplePlugin opts)

-- launch the dispatcher.
scheduler <- newScheduler plugins' initOpts
server scheduler origDir plugins' (optCaptureFile opts)
-- launch the dispatcher.
scheduler <- newScheduler plugins' initOpts
server scheduler origDir plugins' (optCaptureFile opts)
else do
-- Provide debug info
cliOut $ "Running HIE(" ++ progName ++ ")"
cliOut $ " " ++ hieVersion
cliOut $ "Current directory:" ++ origDir
-- args <- getArgs
cliOut $ "\nargs:" ++ show args

cliOut $ "\nLooking for project config cradle...\n"

ecradle <- getCradleInfo origDir
case ecradle of
Left e -> cliOut $ "Could not get cradle:" ++ show e
Right cradle -> cliOut $ "Cradle:" ++ cradleDisplay cradle

-- ---------------------------------------------------------------------

getCradleInfo :: FilePath -> IO (Either Yaml.ParseException Cradle)
getCradleInfo currentDir = do
let dummyCradleFile = currentDir </> "File.hs"
cradleRes <- E.try (findLocalCradle dummyCradleFile)
return cradleRes

-- ---------------------------------------------------------------------

cliOut :: String -> IO ()
cliOut = putStrLn

-- ---------------------------------------------------------------------
5 changes: 5 additions & 0 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -9,4 +9,9 @@ tests: true
package haskell-ide-engine
test-show-details: direct

-- Match the flag settings we use in stac builds
constraints:
haskell-ide-engine +pedantic
hie-plugin-api +pedantic

write-ghc-environment-files: never
1 change: 1 addition & 0 deletions haskell-ide-engine.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -118,6 +118,7 @@ executable hie
, hie-plugin-api
, hslogger
, optparse-simple
, yaml
ghc-options: -threaded -rtsopts -with-rtsopts=-N -Wall -Wredundant-constraints
-with-rtsopts=-T
if flag(pedantic)
Expand Down
6 changes: 3 additions & 3 deletions src/Haskell/Ide/Engine/Options.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ import Options.Applicative.Simple
data GlobalOpts = GlobalOpts
{ optDebugOn :: Bool
, optLogFile :: Maybe String
, _optLsp :: Bool -- Kept for a while, to not break legacy clients
, optLsp :: Bool -- Kept for a while, to not break legacy clients
, projectRoot :: Maybe String
, optBiosVerbose :: Bool
, optCaptureFile :: Maybe FilePath
Expand All @@ -26,9 +26,9 @@ globalOptsParser = GlobalOpts
<> metavar "LOGFILE"
<> help "File to log to, defaults to stdout"
))
<*> flag True True
<*> flag False True
( long "lsp"
<> help "Legacy flag, no longer used, to enable LSP mode. Not required.")
<> help "Start HIE as an LSP server. Otherwise it dumps debug info to stdout")
<*> optional (strOption
( long "project-root"
<> short 'r'
Expand Down