ghc-mod/src/GhcModMain.hs

185 lines
6.1 KiB
Haskell
Raw Normal View History

{-# LANGUAGE ScopedTypeVariables, DeriveDataTypeable #-}
2010-06-14 06:38:56 +00:00
2010-01-06 05:38:06 +00:00
module Main where
2015-12-20 12:26:16 +00:00
import Control.Applicative
import Control.Monad
2014-03-27 05:46:33 +00:00
import Data.Typeable (Typeable)
import Data.List
2016-01-08 18:37:51 +00:00
import Data.List.Split
import GhcMod.Pretty
2015-08-10 08:10:33 +00:00
import System.FilePath ((</>))
import System.Directory (setCurrentDirectory, getAppUserDataDirectory,
removeDirectoryRecursive)
2015-09-01 02:14:15 +00:00
import System.IO
2015-08-18 02:50:19 +00:00
import System.Exit
2015-12-20 12:26:16 +00:00
import Prelude
2010-01-06 05:38:06 +00:00
import GhcMod
import GhcMod.Exe.Find
import GhcMod.Exe.Options
import GhcMod.Exe.Internal hiding (MonadIO,liftIO)
import GhcMod.Monad
import GhcMod.Types
import Exception
2015-08-14 03:57:33 +00:00
handler :: IOish m => GhcModT m a -> GhcModT m a
2015-12-20 12:02:31 +00:00
handler = flip gcatches
[ GHandler $ \(e :: ExitCode) -> throw e
2015-08-14 03:57:33 +00:00
, GHandler $ \(SomeException e) -> exitError $ "ghc-mod: " ++ show e
]
2010-01-06 05:38:06 +00:00
main :: IO ()
main =
parseArgs >>= \res@(globalOptions, _) -> do
enc <- mkTextEncoding $ optEncoding globalOptions
hSetEncoding stdout enc
hSetEncoding stderr enc
hSetEncoding stdin enc
2015-12-05 20:55:12 +00:00
catches (progMain res) [
Handler $ \(e :: GhcModError) ->
2017-05-12 13:28:08 +00:00
runGmOutT globalOptions $ exitError $ renderGm (gmeDoc e)
2015-12-05 20:55:12 +00:00
]
2015-12-05 20:55:12 +00:00
progMain :: (Options, GhcModCommands) -> IO ()
progMain (globalOptions, commands) = runGmOutT globalOptions $
wrapGhcCommands globalOptions commands
-- ghc-modi
legacyInteractive :: IOish m => GhcModT m ()
legacyInteractive = do
prepareCabalHelper
asyncSymbolDb <- newAsyncSymbolDb
world <- getCurrentWorld
legacyInteractiveLoop asyncSymbolDb world
legacyInteractiveLoop :: IOish m => AsyncSymbolDb -> World -> GhcModT m ()
legacyInteractiveLoop asyncSymbolDb world = do
liftIO . setCurrentDirectory =<< cradleRootDir <$> cradle
-- blocking
cmdArg <- liftIO getLine
-- after blocking, we need to see if the world has changed.
changed <- didWorldChange world
world' <- if changed
then getCurrentWorld -- TODO: gah, we're hitting the fs twice
else return world
when changed dropSession
res <- flip gcatches interactiveHandlers $ do
pargs <- either (throw . InvalidCommandLine . Right) return
2015-12-20 03:05:43 +00:00
$ parseArgsInteractive cmdArg
case pargs of
2015-12-20 03:05:43 +00:00
CmdFind symbol ->
lookupSymbol symbol =<< getAsyncSymbolDb asyncSymbolDb
-- other commands are handled here
x -> ghcCommands x
gmPutStr res >> gmPutStrLn "OK" >> liftIO (hFlush stdout)
legacyInteractiveLoop asyncSymbolDb world'
where
2015-12-05 20:55:12 +00:00
interactiveHandlers =
2015-12-20 12:02:31 +00:00
[ GHandler $ \(e :: ExitCode) -> throw e
, GHandler $ \(InvalidCommandLine e) -> do
2016-01-08 18:37:51 +00:00
let err = notGood $ either ("Invalid command line: "++) Prelude.id e
liftIO $ do
putStr err
exitFailure
, GHandler $ \(SomeException e) -> gmErrStrLn (show e) >> return ""
]
2016-01-08 18:37:51 +00:00
notGood msg = "NG " ++ escapeNewlines msg
escapeNewlines = replace "\n" "\\n" . replace "\\n" "\\\\n"
replace needle replacement = intercalate replacement . splitOn needle
2015-10-03 14:00:46 +00:00
getFileSourceFromStdin :: IO String
getFileSourceFromStdin = do
2015-10-01 06:54:13 +00:00
linesIn <- readStdin'
return (intercalate "\n" linesIn)
where
readStdin' = do
x <- getLine
if x/="\EOT"
then fmap (x:) readStdin'
else return []
2015-12-05 20:55:12 +00:00
wrapGhcCommands :: (IOish m, GmOut m) => Options -> GhcModCommands -> m ()
2015-12-20 12:02:31 +00:00
wrapGhcCommands opts cmd =
handleGmError $ runGhcModT opts $ handler $ do
forM_ (reverse $ optFileMappings opts) $
uncurry loadMMappedFiles
2015-12-05 20:55:12 +00:00
gmPutStr =<< ghcCommands cmd
where
handleGmError action = do
(e, _l) <- liftIO . evaluate =<< action
case e of
Right _ ->
return ()
Left ed ->
2017-05-12 13:28:08 +00:00
exitError $ renderGm (gmeDoc ed)
loadMMappedFiles from (Just to) = loadMappedFile from to
loadMMappedFiles from (Nothing) = do
src <- liftIO getFileSourceFromStdin
loadMappedFileSource from src
2015-12-05 20:55:12 +00:00
ghcCommands :: IOish m => GhcModCommands -> GhcModT m String
-- ghcCommands cmd = action args
ghcCommands (CmdLang) = languages
ghcCommands (CmdFlag) = flags
ghcCommands (CmdDebug) = debugInfo
ghcCommands (CmdDebugComponent ts) = componentInfo ts
ghcCommands (CmdBoot) = boot
-- ghcCommands (CmdNukeCaches) = nukeCaches >> return ""
ghcCommands (CmdRoot) = rootInfo
2015-12-05 20:55:12 +00:00
ghcCommands (CmdLegacyInteractive) = legacyInteractive >> return ""
ghcCommands (CmdModules detail) = modules detail
ghcCommands (CmdDumpSym) = dumpSymbol >> return ""
2015-12-05 20:55:12 +00:00
ghcCommands (CmdFind symb) = findSymbol symb
ghcCommands (CmdDoc m) = pkgDoc m
ghcCommands (CmdLint opts file) = lint opts file
ghcCommands (CmdBrowse opts ms) = concat <$> browse opts `mapM` ms
ghcCommands (CmdCheck files) = checkSyntax files
ghcCommands (CmdExpand files) = expandTemplate files
ghcCommands (CmdInfo file symb) = info file $ Expression symb
ghcCommands (CmdType wCon file (line, col)) = types wCon file line col
2015-12-05 20:55:12 +00:00
ghcCommands (CmdSplit file (line, col)) = splits file line col
ghcCommands (CmdSig file (line, col)) = sig file line col
ghcCommands (CmdAuto file (line, col)) = auto file line col
ghcCommands (CmdRefine file (line, col) expr) = refine file line col $ Expression expr
-- interactive-only commands
ghcCommands (CmdMapFile f) =
liftIO getFileSourceFromStdin
>>= loadMappedFileSource f
>> return ""
ghcCommands (CmdUnmapFile f) = unloadMappedFile f >> return ""
ghcCommands (CmdQuit) = liftIO exitSuccess
ghcCommands (CmdTest file) = test file
2015-12-20 12:02:31 +00:00
ghcCommands cmd = throw $ InvalidCommandLine $ Left $ show cmd
newtype InvalidCommandLine = InvalidCommandLine (Either String String)
deriving (Show, Typeable)
instance Exception InvalidCommandLine
exitError :: (MonadIO m, GmOut m) => String -> m a
2015-08-14 03:57:33 +00:00
exitError msg = gmErrStrLn (dropWhileEnd (=='\n') msg) >> liftIO exitFailure
2015-08-10 08:10:33 +00:00
nukeCaches :: IOish m => GhcModT m ()
nukeCaches = do
chdir <- liftIO $ (</> "cabal-helper") <$> getAppUserDataDirectory "ghc-mod"
c <- cradle
when (isCabalHelperProject $ cradleProject c) $ do
2015-08-10 08:10:33 +00:00
let root = cradleRootDir c
2015-08-18 12:55:45 +00:00
let dist = cradleDistDir c
liftIO $ (trySome . removeDirectoryRecursive) `mapM_` [chdir, root </> dist]
2015-08-10 08:10:33 +00:00
trySome :: IO a -> IO (Either SomeException a)
trySome = try