Obsoleting fromCabalFile.

This commit is contained in:
Kazu Yamamoto 2013-09-19 16:21:48 +09:00
parent 97da4e9be1
commit 8e4d2cec21
4 changed files with 20 additions and 21 deletions

View File

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Language.Haskell.GhcMod.CabalApi (
fromCabalFile
getCompilerOptions
, parseCabalFile
, cabalAllBuildInfo
, cabalDependPackages
@ -33,24 +33,15 @@ import System.FilePath
----------------------------------------------------------------
-- | Parsing a cabal file in 'Cradle' and returns
-- options for GHC, include directories for modules and
-- package names of dependency.
fromCabalFile :: [GHCOption] -> Cradle -> IO CompilerOptions
fromCabalFile ghcopts cradle =
parseCabalFile cfile >>= cookInfo ghcopts cradle
where
Just cfile = cradleCabalFile cradle
cookInfo :: [GHCOption] -> Cradle -> PackageDescription -> IO CompilerOptions
cookInfo ghcopts cradle cabal = do
getCompilerOptions :: [GHCOption] -> Cradle -> PackageDescription -> IO CompilerOptions
getCompilerOptions ghcopts cradle pkgDesc = do
gopts <- getGHCOptions ghcopts cdir $ head buildInfos
return $ CompilerOptions gopts idirs depPkgs
where
wdir = cradleCurrentDir cradle
Just cdir = cradleCabalDir cradle
Just cfile = cradleCabalFile cradle
buildInfos = cabalAllBuildInfo cabal
buildInfos = cabalAllBuildInfo pkgDesc
idirs = includeDirectories cdir wdir $ cabalSourceDirs buildInfos
depPkgs = removeThem problematicPackages $ removeMe cfile $ cabalDependPackages buildInfos

View File

@ -31,9 +31,9 @@ debug :: Options
debug opt cradle ver fileName = do
CompilerOptions gopts incDir pkgs <-
if cabal then
liftIO $ fromCabalFile (ghcOpts opt) cradle ||> return (CompilerOptions (ghcOpts opt) [] [])
liftIO (fromCabalFile ||> return simpleCompilerOption)
else
return (CompilerOptions (ghcOpts opt) [] [])
return simpleCompilerOption
[fast] <- do
void $ initializeFlagsWithCradle opt cradle gopts True
setTargetFiles [fileName]
@ -49,5 +49,11 @@ debug opt cradle ver fileName = do
]
where
currentDir = cradleCurrentDir cradle
cabal = isJust $ cradleCabalFile cradle
cabalFile = fromMaybe "" $ cradleCabalFile cradle
mCabalFile = cradleCabalFile cradle
cabal = isJust mCabalFile
cabalFile = fromMaybe "" mCabalFile
origGopts = ghcOpts opt
simpleCompilerOption = CompilerOptions origGopts [] []
fromCabalFile = parseCabalFile file >>= getCompilerOptions origGopts cradle
where
file = fromJust mCabalFile

View File

@ -16,7 +16,7 @@ import Control.Applicative
import Control.Exception
import Control.Monad
import CoreMonad
import Data.Maybe (isJust)
import Data.Maybe (isJust,fromJust)
import DynFlags
import Exception
import GHC
@ -65,9 +65,11 @@ initializeFlagsWithCradle opt cradle ghcopts logging
| cabal = withCabal |||> withoutCabal
| otherwise = withoutCabal
where
cabal = isJust $ cradleCabalFile cradle
mCradleFile = cradleCabalFile cradle
cabal = isJust mCradleFile
withCabal = do
compOpts <- liftIO $ fromCabalFile ghcopts cradle
pkgDesc <- liftIO $ parseCabalFile $ fromJust mCradleFile
compOpts <- liftIO $ getCompilerOptions ghcopts cradle pkgDesc
initSession CabalPkg opt compOpts logging
withoutCabal =
initSession SingleFile opt compOpts logging

View File

@ -8,7 +8,7 @@ module Language.Haskell.GhcMod.Internal (
, IncludeDir
, CompilerOptions(..)
-- * Cabal API
, fromCabalFile
, getCompilerOptions
, parseCabalFile
, cabalAllBuildInfo
, cabalDependPackages