Switch when using cabal-dev case. Bugfix of cabal-dev case.

This commit is contained in:
HIBINO Kei 2011-11-14 19:20:02 +09:00
parent 21441da080
commit 748c57f0c1
3 changed files with 8 additions and 9 deletions

View File

@ -9,7 +9,7 @@ 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.FilePath.Posix (splitPath,joinPath,(</>))
import System.Posix.Directory (getWorkingDirectory)
import System.Directory
@ -29,8 +29,8 @@ findCabalDev =
addPath :: Options -> String -> Options
addPath orig_opts path = do
let orig_paths = packageConfs orig_opts
orig_opts { packageConfs = orig_paths ++ [path] }
let orig_ghcopt = ghcOpts orig_opts
orig_opts { ghcOpts = orig_ghcopt ++ ["-package-conf", path] }
searchIt :: [FilePath] -> IO (Maybe FilePath)
searchIt [] = return Nothing
@ -42,4 +42,4 @@ searchIt path = do
else
return Nothing
where
mpath a = joinPath a ++ "cabal-dev/"
mpath a = joinPath a </> "cabal-dev/"

View File

@ -1,7 +1,6 @@
module Check (checkSyntax) where
import Cabal
import CabalDev (modifyOptions)
import Control.Applicative
import CoreMonad
import ErrMsg
@ -14,8 +13,7 @@ import Types
checkSyntax :: Options -> String -> IO String
checkSyntax opt file = do
opt' <- modifyOptions opt
unlines <$> check opt' file
unlines <$> check opt file
----------------------------------------------------------------

View File

@ -2,6 +2,7 @@
module Main where
import CabalDev (modifyOptions)
import Browse
import Check
import Control.Applicative
@ -89,8 +90,8 @@ instance Exception GHCModError
main :: IO ()
main = flip catches handlers $ do
args <- getArgs
let (opt,cmdArg) = parseArgs argspec args
res <- case safelist cmdArg 0 of
let (opt',cmdArg) = parseArgs argspec args
res <- modifyOptions opt' >>= \opt -> case safelist cmdArg 0 of
"browse" -> concat <$> mapM (browseModule opt) (tail cmdArg)
"list" -> listModules opt
"check" -> withFile (checkSyntax opt) (safelist cmdArg 1)