Obsoleting fromCabalFile.
This commit is contained in:
parent
97da4e9be1
commit
8e4d2cec21
@ -1,7 +1,7 @@
|
|||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.CabalApi (
|
module Language.Haskell.GhcMod.CabalApi (
|
||||||
fromCabalFile
|
getCompilerOptions
|
||||||
, parseCabalFile
|
, parseCabalFile
|
||||||
, cabalAllBuildInfo
|
, cabalAllBuildInfo
|
||||||
, cabalDependPackages
|
, cabalDependPackages
|
||||||
@ -33,24 +33,15 @@ import System.FilePath
|
|||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
-- | Parsing a cabal file in 'Cradle' and returns
|
getCompilerOptions :: [GHCOption] -> Cradle -> PackageDescription -> IO CompilerOptions
|
||||||
-- options for GHC, include directories for modules and
|
getCompilerOptions ghcopts cradle pkgDesc = do
|
||||||
-- 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
|
|
||||||
gopts <- getGHCOptions ghcopts cdir $ head buildInfos
|
gopts <- getGHCOptions ghcopts cdir $ head buildInfos
|
||||||
return $ CompilerOptions gopts idirs depPkgs
|
return $ CompilerOptions gopts idirs depPkgs
|
||||||
where
|
where
|
||||||
wdir = cradleCurrentDir cradle
|
wdir = cradleCurrentDir cradle
|
||||||
Just cdir = cradleCabalDir cradle
|
Just cdir = cradleCabalDir cradle
|
||||||
Just cfile = cradleCabalFile cradle
|
Just cfile = cradleCabalFile cradle
|
||||||
buildInfos = cabalAllBuildInfo cabal
|
buildInfos = cabalAllBuildInfo pkgDesc
|
||||||
idirs = includeDirectories cdir wdir $ cabalSourceDirs buildInfos
|
idirs = includeDirectories cdir wdir $ cabalSourceDirs buildInfos
|
||||||
depPkgs = removeThem problematicPackages $ removeMe cfile $ cabalDependPackages buildInfos
|
depPkgs = removeThem problematicPackages $ removeMe cfile $ cabalDependPackages buildInfos
|
||||||
|
|
||||||
|
@ -31,9 +31,9 @@ debug :: Options
|
|||||||
debug opt cradle ver fileName = do
|
debug opt cradle ver fileName = do
|
||||||
CompilerOptions gopts incDir pkgs <-
|
CompilerOptions gopts incDir pkgs <-
|
||||||
if cabal then
|
if cabal then
|
||||||
liftIO $ fromCabalFile (ghcOpts opt) cradle ||> return (CompilerOptions (ghcOpts opt) [] [])
|
liftIO (fromCabalFile ||> return simpleCompilerOption)
|
||||||
else
|
else
|
||||||
return (CompilerOptions (ghcOpts opt) [] [])
|
return simpleCompilerOption
|
||||||
[fast] <- do
|
[fast] <- do
|
||||||
void $ initializeFlagsWithCradle opt cradle gopts True
|
void $ initializeFlagsWithCradle opt cradle gopts True
|
||||||
setTargetFiles [fileName]
|
setTargetFiles [fileName]
|
||||||
@ -49,5 +49,11 @@ debug opt cradle ver fileName = do
|
|||||||
]
|
]
|
||||||
where
|
where
|
||||||
currentDir = cradleCurrentDir cradle
|
currentDir = cradleCurrentDir cradle
|
||||||
cabal = isJust $ cradleCabalFile cradle
|
mCabalFile = cradleCabalFile cradle
|
||||||
cabalFile = fromMaybe "" $ cradleCabalFile cradle
|
cabal = isJust mCabalFile
|
||||||
|
cabalFile = fromMaybe "" mCabalFile
|
||||||
|
origGopts = ghcOpts opt
|
||||||
|
simpleCompilerOption = CompilerOptions origGopts [] []
|
||||||
|
fromCabalFile = parseCabalFile file >>= getCompilerOptions origGopts cradle
|
||||||
|
where
|
||||||
|
file = fromJust mCabalFile
|
||||||
|
@ -16,7 +16,7 @@ import Control.Applicative
|
|||||||
import Control.Exception
|
import Control.Exception
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import CoreMonad
|
import CoreMonad
|
||||||
import Data.Maybe (isJust)
|
import Data.Maybe (isJust,fromJust)
|
||||||
import DynFlags
|
import DynFlags
|
||||||
import Exception
|
import Exception
|
||||||
import GHC
|
import GHC
|
||||||
@ -65,9 +65,11 @@ initializeFlagsWithCradle opt cradle ghcopts logging
|
|||||||
| cabal = withCabal |||> withoutCabal
|
| cabal = withCabal |||> withoutCabal
|
||||||
| otherwise = withoutCabal
|
| otherwise = withoutCabal
|
||||||
where
|
where
|
||||||
cabal = isJust $ cradleCabalFile cradle
|
mCradleFile = cradleCabalFile cradle
|
||||||
|
cabal = isJust mCradleFile
|
||||||
withCabal = do
|
withCabal = do
|
||||||
compOpts <- liftIO $ fromCabalFile ghcopts cradle
|
pkgDesc <- liftIO $ parseCabalFile $ fromJust mCradleFile
|
||||||
|
compOpts <- liftIO $ getCompilerOptions ghcopts cradle pkgDesc
|
||||||
initSession CabalPkg opt compOpts logging
|
initSession CabalPkg opt compOpts logging
|
||||||
withoutCabal =
|
withoutCabal =
|
||||||
initSession SingleFile opt compOpts logging
|
initSession SingleFile opt compOpts logging
|
||||||
|
@ -8,7 +8,7 @@ module Language.Haskell.GhcMod.Internal (
|
|||||||
, IncludeDir
|
, IncludeDir
|
||||||
, CompilerOptions(..)
|
, CompilerOptions(..)
|
||||||
-- * Cabal API
|
-- * Cabal API
|
||||||
, fromCabalFile
|
, getCompilerOptions
|
||||||
, parseCabalFile
|
, parseCabalFile
|
||||||
, cabalAllBuildInfo
|
, cabalAllBuildInfo
|
||||||
, cabalDependPackages
|
, cabalDependPackages
|
||||||
|
Loading…
Reference in New Issue
Block a user