-fno-code and no outputDir.

This commit is contained in:
Kazu Yamamoto 2010-04-29 12:39:48 +09:00
parent 8fd3c80a54
commit 2345765077
3 changed files with 5 additions and 53 deletions

View File

@ -2,7 +2,6 @@ module Check (checkSyntax) where
import Bag import Bag
import Control.Applicative import Control.Applicative
import Control.Monad
import Data.IORef import Data.IORef
import DynFlags import DynFlags
import ErrUtils import ErrUtils
@ -14,26 +13,19 @@ import HscTypes
import Outputable hiding (showSDoc) import Outputable hiding (showSDoc)
import Param import Param
import Pretty import Pretty
import System.Directory
import System.FilePath
---------------------------------------------------------------- ----------------------------------------------------------------
checkSyntax :: Options -> String -> IO String checkSyntax :: Options -> String -> IO String
checkSyntax opt file = do checkSyntax _ file = unlines <$> check file
let outdir = outDir opt
objfile = objectFile outdir file
makeDirectory outdir
removeObjFile objfile
unlines <$> check file outdir
---------------------------------------------------------------- ----------------------------------------------------------------
cmdOptions :: [Located String] cmdOptions :: [Located String]
cmdOptions = map noLoc ["-Wall","-fno-warn-unused-do-bind"] cmdOptions = map noLoc ["-Wall","-fno-warn-unused-do-bind"]
check :: String -> String -> IO [String] check :: String -> IO [String]
check fileName dir = ghandle ignore $ runGhc (Just libdir) $ do check fileName = ghandle ignore $ runGhc (Just libdir) $ do
ref <- liftIO $ newIORef [] ref <- liftIO $ newIORef []
initSession initSession
setTargetFile fileName setTargetFile fileName
@ -43,7 +35,7 @@ check fileName dir = ghandle ignore $ runGhc (Just libdir) $ do
initSession = do initSession = do
dflags <- getSessionDynFlags dflags <- getSessionDynFlags
(dflags',_,_) <- parseDynamicFlags dflags cmdOptions (dflags',_,_) <- parseDynamicFlags dflags cmdOptions
setSessionDynFlags $ setGhcPackage $ setImportPath $ setOutputDir dir dflags' setSessionDynFlags $ setTarget $ setGhcPackage $ setImportPath dflags'
setTargetFile file = do setTargetFile file = do
target <- guessTarget file Nothing target <- guessTarget file Nothing
setTargets [target] setTargets [target]
@ -64,13 +56,6 @@ refLogger ref (Just e) = do
---------------------------------------------------------------- ----------------------------------------------------------------
setOutputDir :: String -> DynFlags -> DynFlags
setOutputDir f d = d {
objectDir = Just f
, hiDir = Just f
, stubDir = Just f, includePaths = f : includePaths d
}
setImportPath :: DynFlags -> DynFlags setImportPath :: DynFlags -> DynFlags
setImportPath d = d { setImportPath d = d {
importPaths = importPaths d ++ ["..","../..","../../..","../../../../.."] importPaths = importPaths d ++ ["..","../..","../../..","../../../../.."]
@ -82,12 +67,11 @@ setGhcPackage d = d {
, ghcLink = NoLink , ghcLink = NoLink
} }
{-
setTarget :: DynFlags -> DynFlags setTarget :: DynFlags -> DynFlags
setTarget d = d { setTarget d = d {
hscTarget = HscNothing hscTarget = HscNothing
} }
-}
---------------------------------------------------------------- ----------------------------------------------------------------
showErrMsg :: ErrMsg -> String showErrMsg :: ErrMsg -> String
@ -104,24 +88,3 @@ style = mkUserStyle neverQualify AllTheWay
showSDoc :: SDoc -> String showSDoc :: SDoc -> String
showSDoc d = Pretty.showDocWith OneLineMode (d style) showSDoc d = Pretty.showDocWith OneLineMode (d style)
----------------------------------------------------------------
makeDirectory :: FilePath -> IO ()
makeDirectory dir = makeDirectoryRecur $ normalise dir
where
makeDirectoryRecur "" = return ()
makeDirectoryRecur cur = do
exist <- doesDirectoryExist cur
let par = takeDirectory cur
unless exist $ do
makeDirectoryRecur par
createDirectory cur
objectFile :: FilePath -> FilePath -> FilePath
objectFile dir hsfile = dir </> replaceExtension hsfile ".o"
removeObjFile :: FilePath -> IO ()
removeObjFile objfile = do
exist <- doesFileExist objfile
when exist $ removeFile objfile

View File

@ -26,7 +26,6 @@ usage = "ghc-mod version 0.4.0\n"
defaultOptions :: Options defaultOptions :: Options
defaultOptions = Options { convert = toPlain defaultOptions = Options { convert = toPlain
, ghcPkg = "ghc-pkg" , ghcPkg = "ghc-pkg"
, outDir = outputDir
} }
argspec :: [OptDescr (Options -> Options)] argspec :: [OptDescr (Options -> Options)]
@ -36,9 +35,6 @@ argspec = [ Option "l" ["tolisp"]
, Option "p" ["ghc-pkg"] , Option "p" ["ghc-pkg"]
(ReqArg (\str opts -> opts { ghcPkg = str }) "ghc-pkg") (ReqArg (\str opts -> opts { ghcPkg = str }) "ghc-pkg")
"ghc-pkg path" "ghc-pkg path"
, Option "o" ["output-dir"]
(ReqArg (\str opts -> opts { outDir = str }) "dist/flymake")
"output directory"
] ]
parseArgs :: [OptDescr (Options -> Options)] -> [String] -> (Options, [String]) parseArgs :: [OptDescr (Options -> Options)] -> [String] -> (Options, [String])

View File

@ -3,11 +3,4 @@ module Param where
data Options = Options { data Options = Options {
convert :: [String] -> String convert :: [String] -> String
, ghcPkg :: FilePath , ghcPkg :: FilePath
, outDir :: FilePath
} }
outputDir :: String
outputDir = "dist/flymake"
outputFile :: String
outputFile = "dist/flymake/a.out"