ghc-mod/Cabal.hs

94 lines
3.0 KiB
Haskell
Raw Normal View History

2011-05-27 01:07:27 +00:00
{-# LANGUAGE OverloadedStrings #-}
2012-02-06 09:07:32 +00:00
2011-05-24 07:18:22 +00:00
module Cabal (initializeGHC) where
2011-11-29 18:02:55 +00:00
import Control.Applicative
2011-10-18 03:09:25 +00:00
import Control.Monad
2011-08-24 06:58:12 +00:00
import CoreMonad
2011-05-24 07:18:22 +00:00
import Data.List
2012-02-06 09:07:32 +00:00
import Distribution.PackageDescription
import Distribution.PackageDescription.Parse (readPackageDescription)
import Distribution.Verbosity (silent)
2011-08-24 07:50:26 +00:00
import ErrMsg
2011-05-24 07:18:22 +00:00
import GHC
import System.Directory
import System.FilePath
import Types
----------------------------------------------------------------
2011-10-18 03:22:48 +00:00
importDirs :: [String]
2011-12-19 06:54:46 +00:00
importDirs = [".","..","../..","../../..","../../../..","../../../../.."]
2011-10-18 03:22:48 +00:00
2011-08-24 06:58:12 +00:00
initializeGHC :: Options -> FilePath -> [String] -> Bool -> Ghc (FilePath,LogReader)
initializeGHC opt fileName ghcOptions logging = do
(owdir,mdirfile) <- liftIO getDirs
2011-05-24 07:18:22 +00:00
case mdirfile of
Nothing -> do
2011-10-18 03:22:48 +00:00
logReader <- initSession opt ghcOptions importDirs logging
2011-08-24 06:58:12 +00:00
return (fileName,logReader)
2011-05-24 07:18:22 +00:00
Just (cdir,cfile) -> do
midirs <- parseCabalFile cfile
changeToCabalDirectory cdir
let idirs = case midirs of
2012-02-06 09:07:32 +00:00
[] -> [cdir,owdir]
dirs -> dirs ++ [owdir]
2011-08-24 06:58:12 +00:00
file = ajustFileName fileName owdir cdir
2011-10-18 03:22:48 +00:00
logReader <- initSession opt ghcOptions idirs logging
2011-08-24 06:58:12 +00:00
return (file,logReader)
2011-05-24 07:18:22 +00:00
----------------------------------------------------------------
2012-02-06 09:07:32 +00:00
parseCabalFile :: FilePath -> Ghc [String]
parseCabalFile file = do
cabal <- liftIO $ readPackageDescription silent file
return $ fromLibrary cabal ||| fromExecutable cabal
where
[] ||| y = y
x ||| _ = x
fromLibrary c = case condLibrary c of
Nothing -> []
Just lib -> libHsSourceDir lib
libHsSourceDir = hsSourceDirs . libBuildInfo . condTreeData
fromExecutable = execHsSrouceDir . condExecutables
execHsSrouceDir [] = []
execHsSrouceDir (x:_) = hsSourceDirs . buildInfo . condTreeData . snd $ x
2011-05-24 07:18:22 +00:00
----------------------------------------------------------------
ajustFileName :: FilePath -> FilePath -> FilePath -> FilePath
ajustFileName name olddir newdir
| olen == nlen = name
| otherwise = drop (nlen+1) olddir </> name
where
olen = length olddir
nlen = length newdir
changeToCabalDirectory :: FilePath -> Ghc ()
changeToCabalDirectory dir = do
2011-08-24 06:58:12 +00:00
liftIO $ setCurrentDirectory dir
2011-05-24 07:18:22 +00:00
workingDirectoryChanged
2011-08-24 06:58:12 +00:00
getDirs :: IO (FilePath, Maybe (FilePath,FilePath))
2011-05-24 07:18:22 +00:00
getDirs = do
2011-08-24 06:58:12 +00:00
wdir <- getCurrentDirectory
2011-05-24 07:18:22 +00:00
mcabdir <- cabalDir wdir
case mcabdir of
Nothing -> return (wdir,Nothing)
jdf -> return (wdir,jdf)
2011-08-24 06:58:12 +00:00
cabalDir :: FilePath -> IO (Maybe (FilePath,FilePath))
2011-05-24 07:18:22 +00:00
cabalDir dir = do
2011-10-18 03:09:25 +00:00
cnts <- (filter isCabal <$> getDirectoryContents dir)
2011-10-19 05:22:28 +00:00
>>= filterM (\file -> doesFileExist (dir </> file))
2011-10-18 03:09:25 +00:00
case cnts of
2011-05-24 07:18:22 +00:00
[] -> do
let dir' = takeDirectory dir
if dir' == dir
then return Nothing
else cabalDir dir'
cfile:_ -> return (Just (dir,dir </> cfile))
where
isCabal name = ".cabal" `isSuffixOf` name
&& length name > 6