fixing #118.
This commit is contained in:
parent
0c84d9464a
commit
7ec9fc1ffb
@ -12,7 +12,7 @@ module CabalApi (
|
||||
import Control.Applicative
|
||||
import Control.Exception (throwIO)
|
||||
import Data.List (intercalate)
|
||||
import Data.Maybe (maybeToList, listToMaybe, fromMaybe)
|
||||
import Data.Maybe (maybeToList, listToMaybe, fromJust)
|
||||
import Data.Set (fromList, toList)
|
||||
import Distribution.Package (Dependency(Dependency), PackageName(PackageName))
|
||||
import Distribution.PackageDescription
|
||||
@ -71,7 +71,7 @@ getGHCOptions ghcOptions binfo = ghcOptions ++ exts ++ [lang] ++ libs ++ libDirs
|
||||
|
||||
-- Causes error, catched in the upper function.
|
||||
cabalBuildInfo :: GenericPackageDescription -> BuildInfo
|
||||
cabalBuildInfo pd = fromMaybe emptyBuildInfo $ fromLibrary pd <|> fromExecutable pd
|
||||
cabalBuildInfo pd = fromJust $ fromLibrary pd <|> fromExecutable pd
|
||||
where
|
||||
fromLibrary c = libBuildInfo . condTreeData <$> condLibrary c
|
||||
fromExecutable c = buildInfo . condTreeData . snd <$> listToMaybe (condExecutables c)
|
||||
|
16
GHCApi.hs
16
GHCApi.hs
@ -1,3 +1,5 @@
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
|
||||
module GHCApi (
|
||||
withGHC
|
||||
, withGHCDummyFile
|
||||
@ -50,13 +52,17 @@ data Build = CabalPkg | SingleFile deriving Eq
|
||||
|
||||
initializeFlagsWithCradle :: Options -> Cradle -> [GHCOption] -> Bool -> Ghc LogReader
|
||||
initializeFlagsWithCradle opt cradle ghcOptions logging
|
||||
| cabal = do
|
||||
(gopts,idirs,depPkgs) <- liftIO $ fromCabalFile ghcOptions cradle
|
||||
initSession CabalPkg opt gopts idirs (Just depPkgs) logging
|
||||
| otherwise =
|
||||
initSession SingleFile opt ghcOptions importDirs Nothing logging
|
||||
| cabal = withCabal `gcatch` fallback
|
||||
| otherwise = withoutCabal
|
||||
where
|
||||
cabal = isJust $ cradleCabalFile cradle
|
||||
withCabal = do
|
||||
(gopts,idirs,depPkgs) <- liftIO $ fromCabalFile ghcOptions cradle
|
||||
initSession CabalPkg opt gopts idirs (Just depPkgs) logging
|
||||
withoutCabal =
|
||||
initSession SingleFile opt ghcOptions importDirs Nothing logging
|
||||
fallback :: SomeException -> Ghc LogReader
|
||||
fallback _ = withoutCabal
|
||||
|
||||
----------------------------------------------------------------
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user