make ghc-modi robust.
This commit is contained in:
parent
ebc1499d13
commit
d0a10277bf
@ -8,6 +8,7 @@ module Language.Haskell.GhcMod.GHCApi (
|
|||||||
, setTargetFiles
|
, setTargetFiles
|
||||||
, addTargetFiles
|
, addTargetFiles
|
||||||
, getDynamicFlags
|
, getDynamicFlags
|
||||||
|
, getSystemLibDir
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
|
@ -29,6 +29,8 @@ module Language.Haskell.GhcMod.Internal (
|
|||||||
, runAnyOne
|
, runAnyOne
|
||||||
-- * 'GhcMonad' Choice
|
-- * 'GhcMonad' Choice
|
||||||
, (|||>)
|
, (|||>)
|
||||||
|
-- * GHC
|
||||||
|
, getSystemLibDir
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.CabalApi
|
import Language.Haskell.GhcMod.CabalApi
|
||||||
|
@ -1,26 +1,38 @@
|
|||||||
module Main where
|
module Main where
|
||||||
|
|
||||||
import System.IO
|
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import CoreMonad (liftIO)
|
import CoreMonad (liftIO)
|
||||||
|
import Data.List
|
||||||
import Data.Set as S
|
import Data.Set as S
|
||||||
import Exception (ghandle)
|
import Exception (ghandle, SomeException(..))
|
||||||
import GHC
|
import GHC
|
||||||
import Language.Haskell.GhcMod
|
import Language.Haskell.GhcMod
|
||||||
import Language.Haskell.GhcMod.Internal
|
import Language.Haskell.GhcMod.Internal
|
||||||
|
import System.IO
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
cradle <- findCradle
|
cradle <- findCradle
|
||||||
void $ withGHCDummyFile $ do
|
run ls $ do
|
||||||
(readLog,_) <- initializeFlagsWithCradle opt cradle ["-Wall"] True
|
(readLog,_) <- initializeFlagsWithCradle opt cradle ["-Wall"] True
|
||||||
loop readLog ls S.empty
|
loop readLog ls S.empty
|
||||||
return []
|
|
||||||
return ()
|
|
||||||
where
|
where
|
||||||
opt = defaultOptions
|
opt = defaultOptions
|
||||||
ls = lineSeparator opt
|
ls = lineSeparator opt
|
||||||
|
|
||||||
|
run :: LineSeparator -> Ghc () -> IO ()
|
||||||
|
run (LineSeparator ls) body = do
|
||||||
|
mlibdir <- getSystemLibDir
|
||||||
|
ghandle ignore $ runGhc mlibdir $ do
|
||||||
|
dflags <- getSessionDynFlags
|
||||||
|
defaultCleanupHandler dflags body
|
||||||
|
where
|
||||||
|
ignore (SomeException e) = do
|
||||||
|
putStr "ghc-modi:0:0:Error:"
|
||||||
|
let x = intercalate ls $ lines $ show e
|
||||||
|
putStrLn x
|
||||||
|
putStrLn "NG"
|
||||||
|
|
||||||
loop :: IO [String] -> LineSeparator -> Set FilePath -> Ghc ()
|
loop :: IO [String] -> LineSeparator -> Set FilePath -> Ghc ()
|
||||||
loop readLog ls set = do
|
loop readLog ls set = do
|
||||||
file <- liftIO $ getLine
|
file <- liftIO $ getLine
|
||||||
|
Loading…
Reference in New Issue
Block a user