Merge branch 'master' into ghc_option
This commit is contained in:
commit
3db0d17352
1
.gitignore
vendored
1
.gitignore
vendored
@ -1 +1,2 @@
|
|||||||
dist/
|
dist/
|
||||||
|
elisp/*.elc
|
||||||
|
45
CabalDev.hs
Normal file
45
CabalDev.hs
Normal file
@ -0,0 +1,45 @@
|
|||||||
|
{-# LANGUAGE DoAndIfThenElse #-}
|
||||||
|
|
||||||
|
module CabalDev (modifyOptions) where
|
||||||
|
|
||||||
|
{-
|
||||||
|
If the directory 'cabal-dev/packages-X.X.X.conf' exists, add it to the
|
||||||
|
options ghc-mod uses to check the source. Otherwise just pass it on.
|
||||||
|
-}
|
||||||
|
|
||||||
|
import Data.Maybe (listToMaybe)
|
||||||
|
import System.FilePath.Find
|
||||||
|
import System.FilePath.Posix (splitPath,joinPath)
|
||||||
|
import System.Posix.Directory (getWorkingDirectory)
|
||||||
|
import System.Directory
|
||||||
|
|
||||||
|
import Types
|
||||||
|
|
||||||
|
modifyOptions :: Options -> IO Options
|
||||||
|
modifyOptions opts =
|
||||||
|
fmap (has_cdev opts) findCabalDev
|
||||||
|
where
|
||||||
|
has_cdev :: Options -> Maybe String -> Options
|
||||||
|
has_cdev op Nothing = op
|
||||||
|
has_cdev op (Just path) = addPath op path
|
||||||
|
|
||||||
|
findCabalDev :: IO (Maybe String)
|
||||||
|
findCabalDev =
|
||||||
|
getWorkingDirectory >>= searchIt . splitPath
|
||||||
|
|
||||||
|
addPath :: Options -> String -> Options
|
||||||
|
addPath orig_opts path = do
|
||||||
|
let orig_paths = packageConfs orig_opts
|
||||||
|
orig_opts { packageConfs = orig_paths ++ [path] }
|
||||||
|
|
||||||
|
searchIt :: [FilePath] -> IO (Maybe FilePath)
|
||||||
|
searchIt [] = return Nothing
|
||||||
|
searchIt path = do
|
||||||
|
a <- doesDirectoryExist (mpath path)
|
||||||
|
if a then do
|
||||||
|
b <- find always (fileName ~~? "packages*.conf") $ mpath path
|
||||||
|
maybe (searchIt $ init path) (return . Just) $ listToMaybe b
|
||||||
|
else
|
||||||
|
return Nothing
|
||||||
|
where
|
||||||
|
mpath a = joinPath a ++ "cabal-dev/"
|
5
Check.hs
5
Check.hs
@ -1,6 +1,7 @@
|
|||||||
module Check (checkSyntax) where
|
module Check (checkSyntax) where
|
||||||
|
|
||||||
import Cabal
|
import Cabal
|
||||||
|
import CabalDev (modifyOptions)
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import CoreMonad
|
import CoreMonad
|
||||||
import ErrMsg
|
import ErrMsg
|
||||||
@ -12,7 +13,9 @@ import Types
|
|||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
checkSyntax :: Options -> String -> IO String
|
checkSyntax :: Options -> String -> IO String
|
||||||
checkSyntax opt file = unlines <$> check opt file
|
checkSyntax opt file = do
|
||||||
|
opt' <- modifyOptions opt
|
||||||
|
unlines <$> check opt' file
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
|
@ -21,7 +21,7 @@ import Types
|
|||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
usage :: String
|
usage :: String
|
||||||
usage = "ghc-mod version 0.6.2\n"
|
usage = "ghc-mod version 1.0.0\n"
|
||||||
++ "Usage:\n"
|
++ "Usage:\n"
|
||||||
++ "\t ghc-mod list [-l]\n"
|
++ "\t ghc-mod list [-l]\n"
|
||||||
++ "\t ghc-mod lang [-l]\n"
|
++ "\t ghc-mod lang [-l]\n"
|
||||||
@ -51,10 +51,10 @@ argspec = [ Option "l" ["tolisp"]
|
|||||||
"print as a list of Lisp"
|
"print as a list of Lisp"
|
||||||
, Option "h" ["hlintOpt"]
|
, Option "h" ["hlintOpt"]
|
||||||
(ReqArg (\h opts -> opts { hlintOpts = h : hlintOpts opts }) "hlintOpt")
|
(ReqArg (\h opts -> opts { hlintOpts = h : hlintOpts opts }) "hlintOpt")
|
||||||
"hint to be ignored"
|
"hlint options"
|
||||||
, Option "g" ["ghcOpt"]
|
, Option "g" ["ghcOpt"]
|
||||||
(ReqArg (\g opts -> opts { ghcOpts = g : ghcOpts opts }) "ghcOpt")
|
(ReqArg (\g opts -> opts { ghcOpts = g : ghcOpts opts }) "ghcOpt")
|
||||||
"extra GHC options"
|
"GHC options"
|
||||||
, Option "o" ["operators"]
|
, Option "o" ["operators"]
|
||||||
(NoArg (\opts -> opts { operators = True }))
|
(NoArg (\opts -> opts { operators = True }))
|
||||||
"print operators, too"
|
"print operators, too"
|
||||||
|
@ -16,7 +16,7 @@
|
|||||||
|
|
||||||
;;; Code:
|
;;; Code:
|
||||||
|
|
||||||
(defconst ghc-version "0.6.1")
|
(defconst ghc-version "1.0.0")
|
||||||
|
|
||||||
;; (eval-when-compile
|
;; (eval-when-compile
|
||||||
;; (require 'haskell-mode))
|
;; (require 'haskell-mode))
|
||||||
|
@ -1,5 +1,5 @@
|
|||||||
Name: ghc-mod
|
Name: ghc-mod
|
||||||
Version: 0.6.2
|
Version: 1.0.0
|
||||||
Author: Kazu Yamamoto <kazu@iij.ad.jp>
|
Author: Kazu Yamamoto <kazu@iij.ad.jp>
|
||||||
Maintainer: Kazu Yamamoto <kazu@iij.ad.jp>
|
Maintainer: Kazu Yamamoto <kazu@iij.ad.jp>
|
||||||
License: BSD3
|
License: BSD3
|
||||||
@ -29,8 +29,8 @@ Executable ghc-mod
|
|||||||
else
|
else
|
||||||
GHC-Options: -Wall
|
GHC-Options: -Wall
|
||||||
Build-Depends: base >= 4.0 && < 5, ghc, ghc-paths, transformers,
|
Build-Depends: base >= 4.0 && < 5, ghc, ghc-paths, transformers,
|
||||||
process, directory, filepath, old-time,
|
process, directory, filepath, old-time, unix,
|
||||||
hlint >= 1.7.1,
|
hlint >= 1.7.1, filemanip,
|
||||||
attoparsec, enumerator, attoparsec-enumerator
|
attoparsec, enumerator, attoparsec-enumerator
|
||||||
Source-Repository head
|
Source-Repository head
|
||||||
Type: git
|
Type: git
|
||||||
|
Loading…
Reference in New Issue
Block a user