2014-08-18 06:06:36 +00:00
|
|
|
{-# LANGUAGE ScopedTypeVariables, DeriveDataTypeable #-}
|
2014-03-25 02:14:25 +00:00
|
|
|
|
2014-03-27 01:34:43 +00:00
|
|
|
-- Commands:
|
|
|
|
-- check <file>
|
|
|
|
-- find <symbol>
|
2014-04-19 11:48:44 +00:00
|
|
|
-- info <file> <expr>
|
|
|
|
-- type <file> <line> <column>
|
2014-03-28 04:44:44 +00:00
|
|
|
-- lint [hlint options] <file>
|
|
|
|
-- the format of hlint options is [String] because they may contain
|
2014-04-21 08:33:53 +00:00
|
|
|
-- spaces and also <file> may contain spaces.
|
2014-04-21 07:30:31 +00:00
|
|
|
-- boot
|
2014-04-24 02:26:30 +00:00
|
|
|
-- browse [<package>:]<module>
|
2014-04-28 00:29:24 +00:00
|
|
|
-- quit
|
2014-03-27 01:34:43 +00:00
|
|
|
--
|
|
|
|
-- Session separators:
|
|
|
|
-- OK -- success
|
|
|
|
-- NG -- failure
|
|
|
|
|
2014-03-19 01:23:47 +00:00
|
|
|
module Main where
|
|
|
|
|
2014-04-25 13:03:09 +00:00
|
|
|
import Config (cProjectVersion)
|
2014-03-25 03:28:39 +00:00
|
|
|
import Control.Applicative ((<$>))
|
2014-08-28 09:54:01 +00:00
|
|
|
import Control.Concurrent.Async (Async, async, wait)
|
2014-04-23 05:44:05 +00:00
|
|
|
import Control.Exception (SomeException(..), Exception)
|
2014-03-27 05:55:24 +00:00
|
|
|
import qualified Control.Exception as E
|
2014-08-28 09:54:01 +00:00
|
|
|
import Control.Monad (when)
|
2014-03-27 06:08:07 +00:00
|
|
|
import CoreMonad (liftIO)
|
2014-09-18 03:17:59 +00:00
|
|
|
import Data.List (intercalate)
|
2014-08-18 06:06:36 +00:00
|
|
|
import Data.List.Split (splitOn)
|
2014-04-11 07:07:36 +00:00
|
|
|
import Data.Typeable (Typeable)
|
2014-04-07 02:06:17 +00:00
|
|
|
import Data.Version (showVersion)
|
2014-03-19 01:23:47 +00:00
|
|
|
import Language.Haskell.GhcMod
|
2014-08-28 09:54:01 +00:00
|
|
|
import Language.Haskell.GhcMod.Internal
|
2014-04-07 02:06:17 +00:00
|
|
|
import Paths_ghc_mod
|
|
|
|
import System.Console.GetOpt
|
2014-04-03 07:18:35 +00:00
|
|
|
import System.Directory (setCurrentDirectory)
|
2014-04-07 02:06:17 +00:00
|
|
|
import System.Environment (getArgs)
|
2014-03-24 08:32:06 +00:00
|
|
|
import System.IO (hFlush,stdout)
|
2014-08-18 06:06:36 +00:00
|
|
|
import System.Exit (ExitCode, exitFailure)
|
2014-03-19 01:23:47 +00:00
|
|
|
|
2014-08-13 06:21:13 +00:00
|
|
|
import Utils
|
|
|
|
|
2014-03-25 02:14:25 +00:00
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2014-04-21 05:04:58 +00:00
|
|
|
type Logger = IO String
|
2014-03-25 02:14:25 +00:00
|
|
|
|
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2014-04-25 13:03:09 +00:00
|
|
|
progVersion :: String
|
|
|
|
progVersion = "ghc-modi version " ++ showVersion version ++ " compiled by GHC " ++ cProjectVersion ++ "\n"
|
|
|
|
|
2014-04-07 02:06:17 +00:00
|
|
|
argspec :: [OptDescr (Options -> Options)]
|
|
|
|
argspec = [ Option "b" ["boundary"]
|
|
|
|
(ReqArg (\s opts -> opts { lineSeparator = LineSeparator s }) "sep")
|
|
|
|
"specify line separator (default is Nul string)"
|
2014-04-18 08:28:12 +00:00
|
|
|
, Option "l" ["tolisp"]
|
|
|
|
(NoArg (\opts -> opts { outputStyle = LispStyle }))
|
|
|
|
"print as a list of Lisp"
|
2014-04-10 13:21:30 +00:00
|
|
|
, Option "g" []
|
2014-08-13 16:40:01 +00:00
|
|
|
(ReqArg (\s opts -> opts { ghcUserOptions = s : ghcUserOptions opts }) "flag") "specify a ghc flag"
|
2014-04-07 02:06:17 +00:00
|
|
|
]
|
|
|
|
|
|
|
|
usage :: String
|
2014-04-25 13:03:09 +00:00
|
|
|
usage = progVersion
|
2014-04-07 02:06:17 +00:00
|
|
|
++ "Usage:\n"
|
2014-04-18 08:28:12 +00:00
|
|
|
++ "\t ghc-modi [-l] [-b sep] [-g flag]\n"
|
2014-04-25 05:09:32 +00:00
|
|
|
++ "\t ghc-modi version\n"
|
2014-04-07 02:06:17 +00:00
|
|
|
++ "\t ghc-modi help\n"
|
|
|
|
|
|
|
|
parseArgs :: [OptDescr (Options -> Options)] -> [String] -> (Options, [String])
|
|
|
|
parseArgs spec argv
|
|
|
|
= case getOpt Permute spec argv of
|
|
|
|
(o,n,[] ) -> (foldr id defaultOptions o, n)
|
2014-04-23 05:44:05 +00:00
|
|
|
(_,_,errs) -> E.throw (CmdArg errs)
|
2014-04-07 02:06:17 +00:00
|
|
|
|
|
|
|
----------------------------------------------------------------
|
|
|
|
|
|
|
|
data GHCModiError = CmdArg [String]
|
|
|
|
deriving (Show, Typeable)
|
|
|
|
|
2014-04-23 05:44:05 +00:00
|
|
|
instance Exception GHCModiError
|
2014-04-07 02:06:17 +00:00
|
|
|
|
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2014-03-25 02:34:58 +00:00
|
|
|
-- Running two GHC monad threads disables the handling of
|
|
|
|
-- C-c since installSignalHandlers is called twice, sigh.
|
|
|
|
|
2014-03-19 01:23:47 +00:00
|
|
|
main :: IO ()
|
2014-04-23 05:44:05 +00:00
|
|
|
main = E.handle cmdHandler $
|
2014-04-07 02:06:17 +00:00
|
|
|
go =<< parseArgs argspec <$> getArgs
|
2014-03-19 01:23:47 +00:00
|
|
|
where
|
2014-04-23 05:44:05 +00:00
|
|
|
cmdHandler (CmdArg _) = putStr $ usageInfo usage argspec
|
|
|
|
go (_,"help":_) = putStr $ usageInfo usage argspec
|
2014-04-25 13:03:09 +00:00
|
|
|
go (_,"version":_) = putStr progVersion
|
2014-08-18 06:06:36 +00:00
|
|
|
go (opt,_) = flip E.catches handlers $ do
|
2014-04-07 02:06:17 +00:00
|
|
|
cradle0 <- findCradle
|
|
|
|
let rootdir = cradleRootDir cradle0
|
2014-07-11 01:10:37 +00:00
|
|
|
-- c = cradle0 { cradleCurrentDir = rootdir } TODO: ?????
|
2014-04-07 02:06:17 +00:00
|
|
|
setCurrentDirectory rootdir
|
2014-08-28 09:54:01 +00:00
|
|
|
symDb <- async $ runGhcModT opt loadSymbolDb
|
2014-09-18 03:17:59 +00:00
|
|
|
(res, _) <- runGhcModT opt $ loop symDb
|
2014-07-22 17:45:48 +00:00
|
|
|
|
|
|
|
case res of
|
|
|
|
Right () -> return ()
|
2014-08-18 06:06:36 +00:00
|
|
|
Left (GMECabalConfigure msg) -> do
|
2014-08-28 09:54:01 +00:00
|
|
|
putStrLn $ notGood $ "cabal configure failed: " ++ show msg
|
2014-08-18 06:06:36 +00:00
|
|
|
exitFailure
|
|
|
|
Left e -> bug $ show e
|
2014-04-23 05:44:05 +00:00
|
|
|
where
|
2014-04-24 03:53:14 +00:00
|
|
|
-- this is just in case.
|
|
|
|
-- If an error is caught here, it is a bug of GhcMod library.
|
2014-08-18 06:06:36 +00:00
|
|
|
handlers = [ E.Handler (\(_ :: ExitCode) -> return ())
|
|
|
|
, E.Handler (\(SomeException e) -> bug $ show e) ]
|
2014-04-25 02:08:29 +00:00
|
|
|
|
2014-08-18 06:06:36 +00:00
|
|
|
bug :: String -> IO ()
|
|
|
|
bug msg = do
|
|
|
|
putStrLn $ notGood $ "BUG: " ++ msg
|
|
|
|
exitFailure
|
|
|
|
|
|
|
|
notGood :: String -> String
|
|
|
|
notGood msg = "NG " ++ escapeNewlines msg
|
|
|
|
|
|
|
|
escapeNewlines :: String -> String
|
|
|
|
escapeNewlines = replace "\n" "\\n" . replace "\\n" "\\\\n"
|
|
|
|
|
|
|
|
replace :: String -> String -> String -> String
|
|
|
|
replace needle replacement = intercalate replacement . splitOn needle
|
2014-03-20 08:40:06 +00:00
|
|
|
|
2014-03-25 02:14:25 +00:00
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2014-09-18 03:17:59 +00:00
|
|
|
loop :: IOish m => SymDbReq -> GhcModT m ()
|
|
|
|
loop symDbReq = do
|
2014-03-28 04:53:58 +00:00
|
|
|
cmdArg <- liftIO getLine
|
2014-03-24 08:32:06 +00:00
|
|
|
let (cmd,arg') = break (== ' ') cmdArg
|
|
|
|
arg = dropWhile (== ' ') arg'
|
2014-09-18 03:17:59 +00:00
|
|
|
(ret,ok) <- case cmd of
|
|
|
|
"check" -> checkStx arg
|
|
|
|
"find" -> findSym arg symDbReq
|
|
|
|
"lint" -> lintStx arg
|
|
|
|
"info" -> showInfo arg
|
|
|
|
"type" -> showType arg
|
|
|
|
"split" -> doSplit arg
|
|
|
|
"sig" -> doSig arg
|
|
|
|
"refine" -> doRefine arg
|
|
|
|
"auto" -> doAuto arg
|
|
|
|
"boot" -> bootIt
|
|
|
|
"browse" -> browseIt arg
|
|
|
|
"quit" -> return ("quit", False)
|
|
|
|
"" -> return ("quit", False)
|
|
|
|
_ -> return ([], True)
|
2014-04-25 02:08:29 +00:00
|
|
|
if ok then do
|
|
|
|
liftIO $ putStr ret
|
|
|
|
liftIO $ putStrLn "OK"
|
|
|
|
else do
|
2014-08-18 06:06:36 +00:00
|
|
|
liftIO $ putStrLn $ notGood ret
|
2014-03-24 08:32:06 +00:00
|
|
|
liftIO $ hFlush stdout
|
2014-09-18 03:17:59 +00:00
|
|
|
when ok $ loop symDbReq
|
2014-03-24 08:32:06 +00:00
|
|
|
|
2014-03-25 02:14:25 +00:00
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2014-09-18 03:17:59 +00:00
|
|
|
checkStx :: IOish m => FilePath -> GhcModT m (String, Bool)
|
|
|
|
checkStx file = do
|
|
|
|
eret <- check [file]
|
2014-04-28 04:52:28 +00:00
|
|
|
case eret of
|
2014-09-18 03:17:59 +00:00
|
|
|
Right ret -> return (ret, True)
|
|
|
|
Left ret -> return (ret, True)
|
2014-04-28 07:31:28 +00:00
|
|
|
|
|
|
|
----------------------------------------------------------------
|
2014-03-25 02:14:25 +00:00
|
|
|
|
2014-08-28 09:54:01 +00:00
|
|
|
type SymDbReq = Async (Either GhcModError SymbolDb, GhcModLog)
|
|
|
|
|
2014-09-18 03:17:59 +00:00
|
|
|
findSym :: IOish m => String -> SymDbReq
|
|
|
|
-> GhcModT m (String, Bool)
|
|
|
|
findSym sym dbReq = do
|
2014-08-28 09:54:01 +00:00
|
|
|
db <- hoistGhcModT =<< liftIO (wait dbReq)
|
2014-07-18 06:13:30 +00:00
|
|
|
ret <- lookupSymbol sym db
|
2014-09-18 03:17:59 +00:00
|
|
|
return (ret, True)
|
2014-03-27 01:34:43 +00:00
|
|
|
|
2014-09-18 03:17:59 +00:00
|
|
|
lintStx :: IOish m => FilePath -> GhcModT m (String, Bool)
|
|
|
|
lintStx optFile = do
|
2014-07-18 06:31:42 +00:00
|
|
|
ret <- withOptions changeOpt $ lint file
|
2014-09-18 03:17:59 +00:00
|
|
|
return (ret, True)
|
2014-03-27 01:34:43 +00:00
|
|
|
where
|
2014-04-19 12:23:01 +00:00
|
|
|
(opts,file) = parseLintOptions optFile
|
|
|
|
hopts = if opts == "" then [] else read opts
|
2014-07-18 06:31:42 +00:00
|
|
|
changeOpt o = o { hlintOpts = hopts }
|
2014-03-28 05:41:01 +00:00
|
|
|
|
|
|
|
-- |
|
|
|
|
-- >>> parseLintOptions "[\"--ignore=Use camelCase\", \"--ignore=Eta reduce\"] file name"
|
|
|
|
-- (["--ignore=Use camelCase", "--ignore=Eta reduce"], "file name")
|
|
|
|
-- >>> parseLintOptions "file name"
|
|
|
|
-- ([], "file name")
|
|
|
|
parseLintOptions :: String -> (String, String)
|
|
|
|
parseLintOptions optFile = case brk (== ']') (dropWhile (/= '[') optFile) of
|
|
|
|
("","") -> ([], optFile)
|
2014-03-28 06:03:41 +00:00
|
|
|
(opt',file') -> (opt', dropWhile (== ' ') file')
|
2014-03-28 05:41:01 +00:00
|
|
|
where
|
|
|
|
brk _ [] = ([],[])
|
|
|
|
brk p (x:xs')
|
|
|
|
| p x = ([x],xs')
|
|
|
|
| otherwise = let (ys,zs) = brk p xs' in (x:ys,zs)
|
2014-04-11 07:07:36 +00:00
|
|
|
|
2014-04-21 07:30:31 +00:00
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2014-09-18 03:17:59 +00:00
|
|
|
showInfo :: IOish m => FilePath -> GhcModT m (String, Bool)
|
|
|
|
showInfo fileArg = do
|
2014-08-13 06:21:13 +00:00
|
|
|
let [file, expr] = splitN 2 fileArg
|
2014-06-28 19:43:51 +00:00
|
|
|
ret <- info file expr
|
2014-09-18 03:17:59 +00:00
|
|
|
return (ret, True)
|
2014-04-11 07:07:36 +00:00
|
|
|
|
2014-09-18 03:17:59 +00:00
|
|
|
showType :: IOish m => FilePath -> GhcModT m (String, Bool)
|
|
|
|
showType fileArg = do
|
2014-08-13 06:21:13 +00:00
|
|
|
let [file, line, column] = splitN 3 fileArg
|
2014-06-28 19:43:51 +00:00
|
|
|
ret <- types file (read line) (read column)
|
2014-09-18 03:17:59 +00:00
|
|
|
return (ret, True)
|
2014-04-21 07:30:31 +00:00
|
|
|
|
2014-09-18 03:17:59 +00:00
|
|
|
doSplit :: IOish m => FilePath -> GhcModT m (String, Bool)
|
|
|
|
doSplit fileArg = do
|
2014-08-13 06:21:13 +00:00
|
|
|
let [file, line, column] = splitN 3 fileArg
|
2014-06-28 19:43:51 +00:00
|
|
|
ret <- splits file (read line) (read column)
|
2014-09-18 03:17:59 +00:00
|
|
|
return (ret, True)
|
2014-06-08 10:33:13 +00:00
|
|
|
|
2014-09-18 03:17:59 +00:00
|
|
|
doSig :: IOish m => FilePath -> GhcModT m (String, Bool)
|
|
|
|
doSig fileArg = do
|
2014-08-13 06:21:13 +00:00
|
|
|
let [file, line, column] = splitN 3 fileArg
|
2014-06-28 19:43:51 +00:00
|
|
|
ret <- sig file (read line) (read column)
|
2014-09-18 03:17:59 +00:00
|
|
|
return (ret, True)
|
2014-06-10 19:34:05 +00:00
|
|
|
|
2014-09-18 03:17:59 +00:00
|
|
|
doRefine :: IOish m => FilePath -> GhcModT m (String, Bool)
|
|
|
|
doRefine fileArg = do
|
2014-08-13 06:21:13 +00:00
|
|
|
let [file, line, column, expr] = splitN 4 fileArg
|
2014-07-17 04:59:10 +00:00
|
|
|
ret <- refine file (read line) (read column) expr
|
2014-09-18 03:17:59 +00:00
|
|
|
return (ret, True)
|
2014-07-16 16:20:52 +00:00
|
|
|
|
2014-09-18 03:17:59 +00:00
|
|
|
doAuto :: IOish m => FilePath -> GhcModT m (String, Bool)
|
|
|
|
doAuto fileArg = do
|
2014-08-13 06:21:13 +00:00
|
|
|
let [file, line, column] = splitN 3 fileArg
|
2014-08-01 15:08:23 +00:00
|
|
|
ret <- auto file (read line) (read column)
|
2014-09-18 03:17:59 +00:00
|
|
|
return (ret, True)
|
2014-08-01 15:08:23 +00:00
|
|
|
|
2014-04-21 07:30:31 +00:00
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2014-09-18 03:17:59 +00:00
|
|
|
bootIt :: IOish m => GhcModT m (String, Bool)
|
|
|
|
bootIt = do
|
2014-05-10 11:51:35 +00:00
|
|
|
ret <- boot
|
2014-09-18 03:17:59 +00:00
|
|
|
return (ret, True)
|
2014-04-21 08:33:53 +00:00
|
|
|
|
2014-09-18 03:17:59 +00:00
|
|
|
browseIt :: IOish m => ModuleString -> GhcModT m (String, Bool)
|
|
|
|
browseIt mdl = do
|
2014-08-23 08:00:40 +00:00
|
|
|
let (det,rest') = break (== ' ') mdl
|
|
|
|
rest = dropWhile (== ' ') rest'
|
|
|
|
ret <- if det == "-d"
|
|
|
|
then withOptions setDetailed (browse rest)
|
|
|
|
else browse mdl
|
2014-09-18 03:17:59 +00:00
|
|
|
return (ret, True)
|
2014-08-23 08:00:40 +00:00
|
|
|
where
|
2014-09-16 07:07:17 +00:00
|
|
|
setDetailed opt = opt { detailed = True }
|