showing GHC version.

This commit is contained in:
Kazu Yamamoto 2014-04-25 22:03:09 +09:00
parent c2da82c30f
commit abc660cdfe
3 changed files with 20 additions and 8 deletions

View File

@ -108,20 +108,24 @@
(defun ghc-debug ()
(interactive)
(let ((el-path (locate-file "ghc.el" load-path))
(ghc-path (executable-find "ghc"))
(ghc-mod-path (executable-find ghc-module-command))
(ghc-modi-path (executable-find ghc-interactive-command))
(el-ver ghc-version)
(ghc-ver (ghc-run-ghc-mod '("--version") "ghc"))
(ghc-mod-ver (ghc-run-ghc-mod '("version")))
(ghc-modi-ver (ghc-run-ghc-mod '("version") ghc-interactive-command)))
(switch-to-buffer (get-buffer-create "**GHC Debug**"))
(erase-buffer)
(insert "Path: check if you are using intended programs.\n")
(insert (format "\tghc.el path: \t%s\n" el-path))
(insert (format "\tghc-mod path: \t%s\n" ghc-mod-path))
(insert (format "\tghc-modi path: \t%s\n" ghc-modi-path))
(insert (format "\t ghc.el path: %s\n" el-path))
(insert (format "\t ghc-mod path: %s\n" ghc-mod-path))
(insert (format "\tghc-modi path: %s\n" ghc-modi-path))
(insert (format "\t ghc path: %s\n" ghc-path))
(insert "\nVersion: all versions must be the same.\n")
(insert (format "\t ghc.el version %s\n" el-ver))
(insert (format "\t %s\n" ghc-mod-ver))
(insert (format "\t%s\n" ghc-modi-ver))))
(insert (format "\t%s\n" ghc-modi-ver))
(insert (format "\t%s\n" ghc-ver))))
(provide 'ghc)

View File

@ -2,6 +2,7 @@
module Main where
import Config (cProjectVersion)
import Control.Applicative ((<$>))
import Control.Exception (Exception, Handler(..), ErrorCall(..))
import qualified Control.Exception as E
@ -20,11 +21,14 @@ import Boot
----------------------------------------------------------------
progVersion :: String
progVersion = "ghc-mod version " ++ showVersion version ++ " compiled by GHC " ++ cProjectVersion ++ "\n"
ghcOptHelp :: String
ghcOptHelp = " [-g GHC_opt1 -g GHC_opt2 ...] "
usage :: String
usage = "ghc-mod version " ++ showVersion version ++ "\n"
usage = progVersion
++ "Usage:\n"
++ "\t ghc-mod list" ++ ghcOptHelp ++ "[-l] [-d]\n"
++ "\t ghc-mod lang [-l]\n"
@ -121,7 +125,7 @@ main = flip E.catches handlers $ do
"root" -> rootInfo opt cradle
"doc" -> nArgs 1 $ packageDoc opt cradle cmdArg1
"boot" -> boot opt cradle
"version" -> return $ "ghc-mod version " ++ showVersion version ++ "\n"
"version" -> return progVersion
"help" -> return $ O.usageInfo usage argspec
cmd -> E.throw (NoSuchCommand cmd)
putStr res

View File

@ -17,6 +17,7 @@
module Main where
import Config (cProjectVersion)
import Control.Applicative ((<$>))
import Control.Concurrent (forkIO, MVar, newEmptyMVar, putMVar, readMVar)
import Control.Exception (SomeException(..), Exception)
@ -50,6 +51,9 @@ type Logger = IO String
----------------------------------------------------------------
progVersion :: String
progVersion = "ghc-modi version " ++ showVersion version ++ " compiled by GHC " ++ cProjectVersion ++ "\n"
argspec :: [OptDescr (Options -> Options)]
argspec = [ Option "b" ["boundary"]
(ReqArg (\s opts -> opts { lineSeparator = LineSeparator s }) "sep")
@ -62,7 +66,7 @@ argspec = [ Option "b" ["boundary"]
]
usage :: String
usage = "ghc-modi version " ++ showVersion version ++ "\n"
usage = progVersion
++ "Usage:\n"
++ "\t ghc-modi [-l] [-b sep] [-g flag]\n"
++ "\t ghc-modi version\n"
@ -92,7 +96,7 @@ main = E.handle cmdHandler $
where
cmdHandler (CmdArg _) = putStr $ usageInfo usage argspec
go (_,"help":_) = putStr $ usageInfo usage argspec
go (_,"version":_) = putStr $ "ghc-modi version " ++ showVersion version ++ "\n"
go (_,"version":_) = putStr progVersion
go (opt,_) = E.handle someHandler $ do
cradle0 <- findCradle
let rootdir = cradleRootDir cradle0