ghc-modi boot.
This commit is contained in:
14
src/Boot.hs
14
src/Boot.hs
@@ -1,7 +1,10 @@
|
||||
module Boot where
|
||||
|
||||
import Language.Haskell.GhcMod
|
||||
import Control.Applicative ((<$>))
|
||||
import CoreMonad (liftIO)
|
||||
import GHC (Ghc)
|
||||
import Language.Haskell.GhcMod
|
||||
import Language.Haskell.GhcMod.Ghc
|
||||
|
||||
boot :: Options -> Cradle -> IO String
|
||||
boot opt cradle = do
|
||||
@@ -12,6 +15,15 @@ boot opt cradle = do
|
||||
pre <- concat <$> mapM (browseModule opt' cradle) preBrowsedModules
|
||||
return $ mods ++ langs ++ flags ++ pre
|
||||
|
||||
boot' :: Options -> Ghc String
|
||||
boot' opt = do
|
||||
mods <- modules opt
|
||||
langs <- liftIO $ listLanguages opt
|
||||
flags <- liftIO $ listFlags opt
|
||||
let opt' = addPackages opt
|
||||
pre <- concat <$> mapM (browse opt') preBrowsedModules
|
||||
return $ mods ++ langs ++ flags ++ pre
|
||||
|
||||
preBrowsedModules :: [String]
|
||||
preBrowsedModules = [
|
||||
"Prelude"
|
||||
|
||||
@@ -9,6 +9,7 @@
|
||||
-- lint [hlint options] <file>
|
||||
-- the format of hlint options is [String] because they may contain
|
||||
-- spaces and aslo <file> may contain spaces.
|
||||
-- boot
|
||||
--
|
||||
-- Session separators:
|
||||
-- OK -- success
|
||||
@@ -53,6 +54,8 @@ import System.Directory (setCurrentDirectory)
|
||||
import System.Environment (getArgs)
|
||||
import System.IO (hFlush,stdout)
|
||||
|
||||
import Boot
|
||||
|
||||
----------------------------------------------------------------
|
||||
|
||||
type DB = Map String [String]
|
||||
@@ -158,6 +161,7 @@ loop opt set mvar readLog = do
|
||||
"lint" -> lintStx opt set arg
|
||||
"info" -> showInfo opt set arg readLog
|
||||
"type" -> showType opt set arg readLog
|
||||
"boot" -> bootIt opt set
|
||||
_ -> return ([], False, set)
|
||||
let put = case outputStyle opt of
|
||||
LispStyle -> putStr
|
||||
@@ -244,6 +248,8 @@ parseLintOptions optFile = case brk (== ']') (dropWhile (/= '[') optFile) of
|
||||
| p x = ([x],xs')
|
||||
| otherwise = let (ys,zs) = brk p xs' in (x:ys,zs)
|
||||
|
||||
----------------------------------------------------------------
|
||||
|
||||
showInfo :: Options
|
||||
-> Set FilePath
|
||||
-> FilePath
|
||||
@@ -267,3 +273,12 @@ showType opt set fileArg readLog = do
|
||||
ret <- types opt file (read line) (read column)
|
||||
_ <- liftIO readLog
|
||||
return (ret, True, set')
|
||||
|
||||
----------------------------------------------------------------
|
||||
|
||||
bootIt :: Options
|
||||
-> Set FilePath
|
||||
-> Ghc (String, Bool, Set FilePath)
|
||||
bootIt opt set = do
|
||||
ret <- boot' opt
|
||||
return (ret, True, set)
|
||||
|
||||
Reference in New Issue
Block a user