22{-# LANGUAGE RankNTypes #-}
33module Main where
44
5+ import qualified Control.Exception as E
56import Control.Monad
67import Data.Monoid ((<>) )
78import Data.Version (showVersion )
9+ import qualified Data.Yaml as Yaml
10+ import HIE.Bios.Types
11+ import Haskell.Ide.Engine.Cradle (findLocalCradle , cradleDisplay )
812import Haskell.Ide.Engine.MonadFunctions
913import Haskell.Ide.Engine.MonadTypes
1014import Haskell.Ide.Engine.Options
@@ -16,26 +20,26 @@ import Options.Applicative.Simple
1620import qualified Paths_haskell_ide_engine as Meta
1721import System.Directory
1822import System.Environment
19- import qualified System.Log.Logger as L
20- import HIE.Bios.Types
23+ import System.FilePath ((</>) )
2124import System.IO
25+ import qualified System.Log.Logger as L
2226
2327-- ---------------------------------------------------------------------
2428-- plugins
2529
2630import Haskell.Ide.Engine.Plugin.ApplyRefact
2731import Haskell.Ide.Engine.Plugin.Brittany
2832import Haskell.Ide.Engine.Plugin.Example2
33+ import Haskell.Ide.Engine.Plugin.Floskell
34+ import Haskell.Ide.Engine.Plugin.Generic
35+ import Haskell.Ide.Engine.Plugin.GhcMod
2936-- import Haskell.Ide.Engine.Plugin.HaRe
3037import Haskell.Ide.Engine.Plugin.Haddock
3138import Haskell.Ide.Engine.Plugin.HfaAlign
3239import Haskell.Ide.Engine.Plugin.HsImport
3340import Haskell.Ide.Engine.Plugin.Liquid
3441import Haskell.Ide.Engine.Plugin.Package
3542import Haskell.Ide.Engine.Plugin.Pragmas
36- import Haskell.Ide.Engine.Plugin.Floskell
37- import Haskell.Ide.Engine.Plugin.Generic
38- import Haskell.Ide.Engine.Plugin.GhcMod
3943
4044-- ---------------------------------------------------------------------
4145
@@ -110,23 +114,56 @@ run opts = do
110114 maybe (pure () ) setCurrentDirectory $ projectRoot opts
111115
112116 progName <- getProgName
113- logm $ " Run entered for HIE(" ++ progName ++ " ) " ++ hieVersion
114- logm $ " Current directory:" ++ origDir
115117 args <- getArgs
116- logm $ " args:" ++ show args
117118
118- let initOpts = defaultCradleOpts { cradleOptsVerbosity = verbosity }
119- verbosity = if optBiosVerbose opts then Verbose else Silent
119+ if optLsp opts
120+ then do
121+ -- Start up in LSP mode
122+ logm $ " Run entered for HIE(" ++ progName ++ " ) " ++ hieVersion
123+ logm $ " Current directory:" ++ origDir
124+ logm $ " args:" ++ show args
125+
126+ let initOpts = defaultCradleOpts { cradleOptsVerbosity = verbosity }
127+ verbosity = if optBiosVerbose opts then Verbose else Silent
120128
121129
122- when (optBiosVerbose opts) $
123- logm " Enabling verbose mode for hie-bios. This option currently doesn't do anything."
130+ when (optBiosVerbose opts) $
131+ logm " Enabling verbose mode for hie-bios. This option currently doesn't do anything."
124132
125- when (optExamplePlugin opts) $
126- logm " Enabling Example2 plugin, will insert constant diagnostics etc."
133+ when (optExamplePlugin opts) $
134+ logm " Enabling Example2 plugin, will insert constant diagnostics etc."
127135
128- let plugins' = plugins (optExamplePlugin opts)
136+ let plugins' = plugins (optExamplePlugin opts)
129137
130- -- launch the dispatcher.
131- scheduler <- newScheduler plugins' initOpts
132- server scheduler origDir plugins' (optCaptureFile opts)
138+ -- launch the dispatcher.
139+ scheduler <- newScheduler plugins' initOpts
140+ server scheduler origDir plugins' (optCaptureFile opts)
141+ else do
142+ -- Provide debug info
143+ cliOut $ " Running HIE(" ++ progName ++ " )"
144+ cliOut $ " " ++ hieVersion
145+ cliOut $ " Current directory:" ++ origDir
146+ -- args <- getArgs
147+ cliOut $ " \n args:" ++ show args
148+
149+ cliOut $ " \n Looking for project config cradle...\n "
150+
151+ ecradle <- getCradleInfo origDir
152+ case ecradle of
153+ Left e -> cliOut $ " Could not get cradle:" ++ show e
154+ Right cradle -> cliOut $ " Cradle:" ++ cradleDisplay cradle
155+
156+ -- ---------------------------------------------------------------------
157+
158+ getCradleInfo :: FilePath -> IO (Either Yaml. ParseException Cradle )
159+ getCradleInfo currentDir = do
160+ let dummyCradleFile = currentDir </> " File.hs"
161+ cradleRes <- E. try (findLocalCradle dummyCradleFile)
162+ return cradleRes
163+
164+ -- ---------------------------------------------------------------------
165+
166+ cliOut :: String -> IO ()
167+ cliOut = putStrLn
168+
169+ -- ---------------------------------------------------------------------
0 commit comments