Exporting more low level APIs.

This commit is contained in:
Kazu Yamamoto 2013-09-16 09:56:08 +09:00
parent 5750673e0e
commit 45751e3926
5 changed files with 61 additions and 23 deletions

View File

@ -3,9 +3,9 @@
module Language.Haskell.GhcMod.CabalApi ( module Language.Haskell.GhcMod.CabalApi (
fromCabalFile fromCabalFile
, parseCabalFile , parseCabalFile
, cabalAllDependPackages
, cabalAllSourceDirs
, cabalAllBuildInfo , cabalAllBuildInfo
, cabalDependPackages
, cabalSourceDirs
, getGHCVersion , getGHCVersion
) where ) where
@ -32,6 +32,9 @@ 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] fromCabalFile :: [GHCOption]
-> Cradle -> Cradle
-> IO ([GHCOption],[IncludeDir],[Package]) -> IO ([GHCOption],[IncludeDir],[Package])
@ -50,8 +53,8 @@ cookInfo ghcOptions cradle cabal = (gopts,idirs,depPkgs)
Just cfile = cradleCabalFile cradle Just cfile = cradleCabalFile cradle
buildInfos = cabalAllBuildInfo cabal buildInfos = cabalAllBuildInfo cabal
gopts = getGHCOptions ghcOptions $ head buildInfos gopts = getGHCOptions ghcOptions $ head buildInfos
idirs = includeDirectories cdir wdir $ cabalAllSourceDirs buildInfos idirs = includeDirectories cdir wdir $ cabalSourceDirs buildInfos
depPkgs = removeThem problematicPackages $ removeMe cfile $ cabalAllDependPackages buildInfos depPkgs = removeThem problematicPackages $ removeMe cfile $ cabalDependPackages buildInfos
removeMe :: FilePath -> [String] -> [String] removeMe :: FilePath -> [String] -> [String]
removeMe cabalfile = filter (/= me) removeMe cabalfile = filter (/= me)
@ -72,6 +75,8 @@ includeDirectories cdir wdir dirs = uniqueAndSort (map (cdir </>) dirs ++ [cdir,
---------------------------------------------------------------- ----------------------------------------------------------------
-- | Parsing a cabal file and returns 'PackageDescription'.
-- 'IOException' is thrown if parsing fails.
parseCabalFile :: FilePath -> IO PackageDescription parseCabalFile :: FilePath -> IO PackageDescription
parseCabalFile file = do parseCabalFile file = do
cid <- getGHCId cid <- getGHCId
@ -99,6 +104,7 @@ getGHCOptions ghcOptions binfo = ghcOptions ++ exts ++ [lang] ++ libs ++ libDirs
---------------------------------------------------------------- ----------------------------------------------------------------
-- | Extracting all 'BuildInfo' for libraries, executables, tests and benchmarks.
cabalAllBuildInfo :: PackageDescription -> [BuildInfo] cabalAllBuildInfo :: PackageDescription -> [BuildInfo]
cabalAllBuildInfo pd = libBI ++ execBI ++ testBI ++ benchBI cabalAllBuildInfo pd = libBI ++ execBI ++ testBI ++ benchBI
where where
@ -109,19 +115,21 @@ cabalAllBuildInfo pd = libBI ++ execBI ++ testBI ++ benchBI
---------------------------------------------------------------- ----------------------------------------------------------------
cabalAllSourceDirs :: [BuildInfo] -> [FilePath] -- | Extracting package names of dependency.
cabalAllSourceDirs bis = uniqueAndSort $ concatMap hsSourceDirs bis cabalDependPackages :: [BuildInfo] -> [Package]
cabalDependPackages bis = uniqueAndSort $ pkgs
----------------------------------------------------------------
cabalAllDependPackages :: [BuildInfo] -> [Package]
cabalAllDependPackages bis = uniqueAndSort $ pkgs
where where
pkgs = map getDependencyPackageName $ concatMap targetBuildDepends bis pkgs = map getDependencyPackageName $ concatMap targetBuildDepends bis
getDependencyPackageName (Dependency (PackageName nm) _) = nm getDependencyPackageName (Dependency (PackageName nm) _) = nm
---------------------------------------------------------------- ----------------------------------------------------------------
-- | Extracting include directories for modules.
cabalSourceDirs :: [BuildInfo] -> [IncludeDir]
cabalSourceDirs bis = uniqueAndSort $ concatMap hsSourceDirs bis
----------------------------------------------------------------
uniqueAndSort :: [String] -> [String] uniqueAndSort :: [String] -> [String]
uniqueAndSort = toList . fromList uniqueAndSort = toList . fromList

View File

@ -96,6 +96,8 @@ initSession build opt cmdOpts idirs mDepPkgs logging = do
---------------------------------------------------------------- ----------------------------------------------------------------
-- | Initialize the 'DynFlags' relating to the compilation of a single
-- file or GHC session.
initializeFlags :: GhcMonad m => Options -> m () initializeFlags :: GhcMonad m => Options -> m ()
initializeFlags opt = do initializeFlags opt = do
dflags0 <- getSessionDynFlags dflags0 <- getSessionDynFlags
@ -167,6 +169,8 @@ setTargetFiles files = do
getDynamicFlags :: IO DynFlags getDynamicFlags :: IO DynFlags
getDynamicFlags = runGhc (Just libdir) getSessionDynFlags getDynamicFlags = runGhc (Just libdir) getSessionDynFlags
-- | Checking if Template Haskell or quasi quotes are used.
-- If not, the process can be faster.
canCheckFast :: ModuleGraph -> Bool canCheckFast :: ModuleGraph -> Bool
canCheckFast = not . any (hasTHorQQ . ms_hspp_opts) canCheckFast = not . any (hasTHorQQ . ms_hspp_opts)
where where

View File

@ -9,20 +9,22 @@ import GHC
---------------------------------------------------------------- ----------------------------------------------------------------
-- | Try the left 'Ghc' action. If 'IOException' occurs, try
-- the right 'Ghc' action.
(||>) :: Ghc a -> Ghc a -> Ghc a (||>) :: Ghc a -> Ghc a -> Ghc a
x ||> y = x `gcatch` (\(_ :: IOException) -> y) x ||> y = x `gcatch` (\(_ :: IOException) -> y)
(|||>) :: GhcMonad m => m a -> m a -> m a -- | Go to the next 'Ghc' monad by throwing 'AltGhcgoNext'.
x |||> y = x `gcatch` (\(_ :: IOException) -> y)
----------------------------------------------------------------
{-| Go to the next 'Ghc' monad by throwing 'AltGhcgoNext'.
-}
goNext :: Ghc a goNext :: Ghc a
goNext = liftIO . throwIO $ userError "goNext" goNext = liftIO . throwIO $ userError "goNext"
{-| Run any one 'Ghc' monad. -- | Run any one 'Ghc' monad.
-}
runAnyOne :: [Ghc a] -> Ghc a runAnyOne :: [Ghc a] -> Ghc a
runAnyOne = foldr (||>) goNext runAnyOne = foldr (||>) goNext
----------------------------------------------------------------
-- | Try the left 'GhcMonad' action. If 'IOException' occurs, try
-- the right 'GhcMonad' action.
(|||>) :: GhcMonad m => m a -> m a -> m a
x |||> y = x `gcatch` (\(_ :: IOException) -> y)

View File

@ -1,16 +1,37 @@
-- | Low level access to the ghc-mod library. -- | Low level access to the ghc-mod library.
module Language.Haskell.GhcMod.Internal ( module Language.Haskell.GhcMod.Internal (
-- * Low level access -- * Types
LogReader LogReader
, GHCOption , GHCOption
, Package
, IncludeDir
-- * Cabal API
, fromCabalFile
, parseCabalFile
, cabalAllBuildInfo
, cabalDependPackages
, cabalSourceDirs
-- * GHC API
, canCheckFast
-- * Getting 'DynFlags'
, getDynamicFlags
-- * Initializing 'DynFlags'
, initializeFlags
, initializeFlagsWithCradle , initializeFlagsWithCradle
-- * 'GhcMonad'
, setTargetFiles , setTargetFiles
, checkSlowAndSet , checkSlowAndSet
, getDynamicFlags -- * 'Ghc' Choice
, (||>)
, goNext
, runAnyOne
-- * 'GhcMonad' Choice
, (|||>)
) where ) where
import Language.Haskell.GhcMod.CabalApi
import Language.Haskell.GhcMod.ErrMsg import Language.Haskell.GhcMod.ErrMsg
import Language.Haskell.GhcMod.GHCApi import Language.Haskell.GhcMod.GHCApi
import Language.Haskell.GhcMod.GHCChoice
import Language.Haskell.GhcMod.Types import Language.Haskell.GhcMod.Types

View File

@ -94,7 +94,10 @@ data Cradle = Cradle {
-- | A single GHC option, as it would appear on the command line. -- | A single GHC option, as it would appear on the command line.
type GHCOption = String type GHCOption = String
-- | Include directories for modules
type IncludeDir = FilePath type IncludeDir = FilePath
-- | Package names
type Package = String type Package = String
-- | GHC version in 'String'. -- | GHC version in 'String'.