bootInfo as API.
This commit is contained in:
@@ -13,6 +13,7 @@ module Language.Haskell.GhcMod (
|
||||
, ModuleString
|
||||
, Expression
|
||||
-- * 'IO' utilities
|
||||
, bootInfo
|
||||
, browseModule
|
||||
, checkSyntax
|
||||
, lintSyntax
|
||||
@@ -28,6 +29,7 @@ module Language.Haskell.GhcMod (
|
||||
, findSymbol
|
||||
) where
|
||||
|
||||
import Language.Haskell.GhcMod.Boot
|
||||
import Language.Haskell.GhcMod.Browse
|
||||
import Language.Haskell.GhcMod.Check
|
||||
import Language.Haskell.GhcMod.Cradle
|
||||
|
||||
38
Language/Haskell/GhcMod/Boot.hs
Normal file
38
Language/Haskell/GhcMod/Boot.hs
Normal file
@@ -0,0 +1,38 @@
|
||||
module Language.Haskell.GhcMod.Boot where
|
||||
|
||||
import Control.Applicative ((<$>))
|
||||
import CoreMonad (liftIO, liftIO)
|
||||
import GHC (Ghc)
|
||||
import Language.Haskell.GhcMod.Browse
|
||||
import Language.Haskell.GhcMod.Flag
|
||||
import Language.Haskell.GhcMod.GHCApi
|
||||
import Language.Haskell.GhcMod.Lang
|
||||
import Language.Haskell.GhcMod.List
|
||||
import Language.Haskell.GhcMod.Types
|
||||
|
||||
-- | Print necessary information for front-end booting.
|
||||
bootInfo :: Options -> Cradle -> IO String
|
||||
bootInfo opt cradle = withGHC' $ do
|
||||
initializeFlagsWithCradle opt cradle
|
||||
boot opt
|
||||
|
||||
-- | Print necessary information for front-end booting.
|
||||
boot :: Options -> Ghc String
|
||||
boot opt = do
|
||||
mods <- modules opt
|
||||
langs <- liftIO $ listLanguages opt
|
||||
flags <- liftIO $ listFlags opt
|
||||
pre <- concat <$> mapM (browse opt) preBrowsedModules
|
||||
return $ mods ++ langs ++ flags ++ pre
|
||||
|
||||
preBrowsedModules :: [String]
|
||||
preBrowsedModules = [
|
||||
"Prelude"
|
||||
, "Control.Applicative"
|
||||
, "Control.Exception"
|
||||
, "Control.Monad"
|
||||
, "Data.Char"
|
||||
, "Data.List"
|
||||
, "Data.Maybe"
|
||||
, "System.IO"
|
||||
]
|
||||
@@ -3,6 +3,7 @@ module Language.Haskell.GhcMod.Ghc (
|
||||
withGHC
|
||||
, withGHC'
|
||||
-- * 'Ghc' utilities
|
||||
, boot
|
||||
, browse
|
||||
, check
|
||||
, info
|
||||
@@ -15,6 +16,7 @@ module Language.Haskell.GhcMod.Ghc (
|
||||
, lookupSym
|
||||
) where
|
||||
|
||||
import Language.Haskell.GhcMod.Boot
|
||||
import Language.Haskell.GhcMod.Browse
|
||||
import Language.Haskell.GhcMod.Check
|
||||
import Language.Haskell.GhcMod.Find
|
||||
|
||||
Reference in New Issue
Block a user