{-# LANGUAGE CPP, RecordWildCards, FlexibleContexts, ConstraintKinds,
GeneralizedNewtypeDeriving, DeriveDataTypeable, DeriveGeneric, DeriveFunctor,
NamedFieldPuns, OverloadedStrings
#-}
module Distribution.Helper (
Query
, runQuery
, packageId
, packageDbStack
, packageFlags
, compilerVersion
, ghcMergedPkgOptions
, configFlags
, nonDefaultConfigFlags
, ComponentQuery
, components
, ghcSrcOptions
, ghcPkgOptions
, ghcLangOptions
, ghcOptions
, sourceDirs
, entrypoints
, needsBuildOutput
, QueryEnv
, mkQueryEnv
, qeReadProcess
, qePrograms
, qeProjectDir
, qeDistDir
, qeCabalPkgDb
, qeCabalVer
, Programs(..)
, defaultPrograms
, ChModuleName(..)
, ChComponentName(..)
, ChPkgDb(..)
, ChEntrypoint(..)
, NeedsBuildOutput(..)
, buildPlatform
, Distribution.Helper.getSandboxPkgDb
, prepare
, reconfigure
, writeAutogenFiles
, LibexecNotFoundError(..)
, libexecNotFoundError
, module Data.Functor.Apply
) where
import Cabal.Plan
import Control.Applicative
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.State.Strict
import Control.Monad.Reader
import Control.Exception as E
import Data.Char
import Data.List
import Data.Maybe
import qualified Data.Map as Map
import Data.Version
import Data.Typeable
import Data.Function
import Data.Functor.Apply
import Distribution.System (buildOS, OS(Windows))
import System.Environment
import System.FilePath hiding ((<.>))
import qualified System.FilePath as FP
import System.Directory
import System.Process
import System.IO.Unsafe
import Text.Printf
import GHC.Generics
import Prelude
import Paths_cabal_helper (getLibexecDir)
import CabalHelper.Shared.InterfaceTypes
import CabalHelper.Shared.Sandbox
data Programs = Programs {
cabalProgram :: FilePath,
ghcProgram :: FilePath,
ghcPkgProgram :: FilePath
} deriving (Eq, Ord, Show, Read, Generic, Typeable)
defaultPrograms :: Programs
defaultPrograms = Programs "cabal" "ghc" "ghc-pkg"
data QueryEnv = QueryEnv {
qeReadProcess :: FilePath -> [String] -> String -> IO String,
qePrograms :: Programs,
qeProjectDir :: FilePath,
qeDistDir :: FilePath,
qeCabalPkgDb :: Maybe FilePath,
qeCabalVer :: Maybe Version
}
mkQueryEnv :: FilePath
-> FilePath
-> QueryEnv
mkQueryEnv projdir distdir = QueryEnv {
qeReadProcess = readProcess
, qePrograms = defaultPrograms
, qeProjectDir = projdir
, qeDistDir = distdir
, qeCabalPkgDb = Nothing
, qeCabalVer = Nothing
}
data SomeLocalBuildInfo = SomeLocalBuildInfo {
slbiPackageDbStack :: [ChPkgDb],
slbiPackageFlags :: [(String, Bool)],
slbiCompilerVersion :: (String, Version),
slbiGhcMergedPkgOptions :: [String],
slbiConfigFlags :: [(String, Bool)],
slbiNonDefaultConfigFlags :: [(String, Bool)],
slbiGhcSrcOptions :: [(ChComponentName, [String])],
slbiGhcPkgOptions :: [(ChComponentName, [String])],
slbiGhcLangOptions :: [(ChComponentName, [String])],
slbiGhcOptions :: [(ChComponentName, [String])],
slbiSourceDirs :: [(ChComponentName, [String])],
slbiEntrypoints :: [(ChComponentName, ChEntrypoint)],
slbiNeedsBuildOutput :: [(ChComponentName, NeedsBuildOutput)]
} deriving (Eq, Ord, Read, Show)
newtype Query m a = Query { unQuery :: StateT (Maybe SomeLocalBuildInfo)
(ReaderT QueryEnv m) a }
deriving (Functor, Applicative, Monad, MonadIO)
instance MonadTrans Query where
lift = Query . lift . lift
type MonadQuery m = ( MonadIO m
, MonadState (Maybe SomeLocalBuildInfo) m
, MonadReader QueryEnv m)
newtype ComponentQuery m a = ComponentQuery (Query m [(ChComponentName, a)])
deriving (Functor)
instance (Functor m, Monad m) => Apply (ComponentQuery m) where
ComponentQuery flab <.> ComponentQuery fla =
ComponentQuery $ liftM2 go flab fla
where
go :: [(ChComponentName, a -> b)]
-> [(ChComponentName, a)]
-> [(ChComponentName, b)]
go lab la =
[ (cn, ab a)
| (cn, ab) <- lab
, (cn', a) <- la
, cn == cn'
]
run :: Monad m => QueryEnv -> Maybe SomeLocalBuildInfo -> Query m a -> m a
run e s action = flip runReaderT e (flip evalStateT s (unQuery action))
runQuery :: Monad m
=> QueryEnv
-> Query m a
-> m a
runQuery qe action = run qe Nothing action
getSlbi :: MonadQuery m => m SomeLocalBuildInfo
getSlbi = do
s <- get
case s of
Nothing -> do
slbi <- getSomeConfigState
put (Just slbi)
return slbi
Just slbi -> return slbi
packageDbStack :: MonadIO m => Query m [ChPkgDb]
ghcMergedPkgOptions :: MonadIO m => Query m [String]
packageFlags :: MonadIO m => Query m [(String, Bool)]
configFlags :: MonadIO m => Query m [(String, Bool)]
nonDefaultConfigFlags :: MonadIO m => Query m [(String, Bool)]
compilerVersion :: MonadIO m => Query m (String, Version)
packageId :: MonadIO m => Query m (String, Version)
components :: Monad m => ComponentQuery m (ChComponentName -> b) -> Query m [b]
components (ComponentQuery sc) = map (\(cn, f) -> f cn) `liftM` sc
entrypoints :: MonadIO m => ComponentQuery m ChEntrypoint
needsBuildOutput :: MonadIO m => ComponentQuery m NeedsBuildOutput
sourceDirs :: MonadIO m => ComponentQuery m [FilePath]
ghcOptions :: MonadIO m => ComponentQuery m [String]
ghcSrcOptions :: MonadIO m => ComponentQuery m [String]
ghcPkgOptions :: MonadIO m => ComponentQuery m [String]
ghcLangOptions :: MonadIO m => ComponentQuery m [String]
packageId = Query $ getPackageId
packageDbStack = Query $ slbiPackageDbStack `liftM` getSlbi
packageFlags = Query $ slbiPackageFlags `liftM` getSlbi
compilerVersion = Query $ slbiCompilerVersion `liftM` getSlbi
ghcMergedPkgOptions = Query $ slbiGhcMergedPkgOptions `liftM` getSlbi
configFlags = Query $ slbiConfigFlags `liftM` getSlbi
nonDefaultConfigFlags = Query $ slbiNonDefaultConfigFlags `liftM` getSlbi
ghcSrcOptions = ComponentQuery $ Query $ slbiGhcSrcOptions `liftM` getSlbi
ghcPkgOptions = ComponentQuery $ Query $ slbiGhcPkgOptions `liftM` getSlbi
ghcOptions = ComponentQuery $ Query $ slbiGhcOptions `liftM` getSlbi
ghcLangOptions = ComponentQuery $ Query $ slbiGhcLangOptions `liftM` getSlbi
sourceDirs = ComponentQuery $ Query $ slbiSourceDirs `liftM` getSlbi
entrypoints = ComponentQuery $ Query $ slbiEntrypoints `liftM` getSlbi
needsBuildOutput = ComponentQuery $ Query $ slbiNeedsBuildOutput `liftM` getSlbi
reconfigure :: MonadIO m
=> (FilePath -> [String] -> String -> IO String)
-> Programs
-> [String]
-> m ()
reconfigure readProc progs cabalOpts = do
let progOpts =
[ "--with-ghc=" ++ ghcProgram progs ]
++ if ghcPkgProgram progs /= "ghc-pkg"
then [ "--with-ghc-pkg=" ++ ghcPkgProgram progs ]
else []
++ cabalOpts
_ <- liftIO $ readProc (cabalProgram progs) ("configure":progOpts) ""
return ()
readHelper :: (MonadIO m, MonadQuery m) => [String] -> m [Maybe ChResponse]
readHelper args = ask >>= \qe -> liftIO $ do
out <- either error id <$> invokeHelper qe args
let res = read out
liftIO $ evaluate res `E.catch` \se@(SomeException _) -> do
md <- lookupEnv' "CABAL_HELPER_DEBUG"
let msg = "readHelper: exception: '" ++ show se ++ "'"
error $ msg ++ case md of
Nothing -> ", for more information set the environment variable CABAL_HELPER_DEBUG"
Just _ -> ", output: '"++ out ++"'"
invokeHelper :: QueryEnv -> [String] -> IO (Either String String)
invokeHelper QueryEnv {..} args = do
let progArgs = [ "--with-ghc=" ++ ghcProgram qePrograms
, "--with-ghc-pkg=" ++ ghcPkgProgram qePrograms
, "--with-cabal=" ++ cabalProgram qePrograms
]
exe <- findLibexecExe
let args' = progArgs ++ "v1-style":qeProjectDir:qeDistDir:args
out <- qeReadProcess exe args' ""
(Right <$> evaluate out) `E.catch` \(SomeException _) ->
return $ Left $ concat
["invokeHelper", ": ", exe, " "
, intercalate " " (map show args')
, " failed"
]
getPackageId :: MonadQuery m => m (String, Version)
getPackageId = ask >>= \QueryEnv {..} -> do
[ Just (ChResponseVersion pkgName pkgVer) ] <- readHelper [ "package-id" ]
return (pkgName, pkgVer)
getSomeConfigState :: MonadQuery m => m SomeLocalBuildInfo
getSomeConfigState = ask >>= \QueryEnv {..} -> do
res <- readHelper
[ "package-db-stack"
, "flags"
, "compiler-version"
, "ghc-merged-pkg-options"
, "config-flags"
, "non-default-config-flags"
, "ghc-src-options"
, "ghc-pkg-options"
, "ghc-lang-options"
, "ghc-options"
, "source-dirs"
, "entrypoints"
, "needs-build-output"
]
let [ Just (ChResponsePkgDbs slbiPackageDbStack),
Just (ChResponseFlags slbiPackageFlags),
Just (ChResponseVersion comp compVer),
Just (ChResponseList slbiGhcMergedPkgOptions),
Just (ChResponseFlags slbiConfigFlags),
Just (ChResponseFlags slbiNonDefaultConfigFlags),
Just (ChResponseCompList slbiGhcSrcOptions),
Just (ChResponseCompList slbiGhcPkgOptions),
Just (ChResponseCompList slbiGhcLangOptions),
Just (ChResponseCompList slbiGhcOptions),
Just (ChResponseCompList slbiSourceDirs),
Just (ChResponseEntrypoints slbiEntrypoints),
Just (ChResponseNeedsBuild slbiNeedsBuildOutput)
] = res
slbiCompilerVersion = (comp, compVer)
return $ SomeLocalBuildInfo {..}
prepare :: MonadIO m => QueryEnv -> m ()
prepare qe =
liftIO $ void $ invokeHelper qe []
writeAutogenFiles :: MonadIO m => QueryEnv -> m ()
writeAutogenFiles qe =
liftIO $ void $ invokeHelper qe ["write-autogen-files"]
getSandboxPkgDb :: (FilePath -> [String] -> String -> IO String)
-> String
-> Version
-> IO (Maybe FilePath)
getSandboxPkgDb readProc =
CabalHelper.Shared.Sandbox.getSandboxPkgDb $ unsafePerformIO $ buildPlatform readProc
buildPlatform :: (FilePath -> [String] -> String -> IO String) -> IO String
buildPlatform readProc = do
exe <- findLibexecExe
CabalHelper.Shared.Sandbox.dropWhileEnd isSpace <$> readProc exe ["print-build-platform"] ""
data LibexecNotFoundError = LibexecNotFoundError String FilePath
deriving (Typeable)
instance Exception LibexecNotFoundError
instance Show LibexecNotFoundError where
show (LibexecNotFoundError exe dir) =
libexecNotFoundError exe dir "https://github.com/DanielG/cabal-helper/issues"
findLibexecExe :: IO FilePath
findLibexecExe = do
libexecdir <- getLibexecDir
let exeName = "cabal-helper-wrapper"
exe = libexecdir </> exeName FP.<.> exeExtension'
exists <- doesFileExist exe
if exists
then return exe
else do
mdir <- tryFindCabalHelperTreeDistDir
dir <- case mdir of
Nothing ->
throwIO $ LibexecNotFoundError exeName libexecdir
Just dir ->
return dir
return $ dir </> "build" </> exeName </> exeName
findPlanJson :: FilePath -> IO (Maybe FilePath)
findPlanJson base =
findFile (map (</> "cache") $ parents base) "plan.json"
parents :: FilePath -> [FilePath]
parents path = takeWhile (not . (`elem` ["", "."]) . dropDrive) dirs
where dirs = iterate takeDirectory path
data DistDir = DistDir { ddType :: DistDirType, unDistDir :: FilePath }
deriving (Eq, Ord, Read, Show)
data DistDirType = NewBuildDist | OldBuildDist
deriving (Eq, Ord, Read, Show)
tryFindCabalHelperTreeDistDir :: IO (Maybe FilePath)
tryFindCabalHelperTreeDistDir = do
exe <- canonicalizePath =<< getExecutablePath'
mplan <- findPlanJson exe
let mdistdir = takeDirectory . takeDirectory <$> mplan
cwd <- getCurrentDirectory
let candidates = sortBy (compare `on` ddType) $ concat
[ maybeToList $ DistDir NewBuildDist <$> mdistdir
, [ DistDir OldBuildDist $ (!!3) $ iterate takeDirectory exe ]
, if takeFileName exe == "ghc"
then [ DistDir NewBuildDist $ cwd </> "dist-newstyle"
, DistDir NewBuildDist $ cwd </> "dist"
, DistDir OldBuildDist $ cwd </> "dist"
]
else []
]
distdirs
<- filterM isDistDir candidates
>>= mapM toOldBuildDistDir
return $ fmap unDistDir $ join $ listToMaybe $ distdirs
isCabalHelperSourceDir :: FilePath -> IO Bool
isCabalHelperSourceDir dir =
doesFileExist $ dir </> "cabal-helper.cabal"
isDistDir :: DistDir -> IO Bool
isDistDir (DistDir NewBuildDist dir) =
doesFileExist (dir </> "cache" </> "plan.json")
isDistDir (DistDir OldBuildDist dir) =
doesFileExist (dir </> "setup-config")
toOldBuildDistDir :: DistDir -> IO (Maybe DistDir)
toOldBuildDistDir (DistDir NewBuildDist dir) = do
PlanJson {pjUnits} <- decodePlanJson $ dir </> "cache" </> "plan.json"
let munit = find isCabalHelperUnit $ Map.elems pjUnits
return $ DistDir OldBuildDist <$> join ((\Unit { uDistDir = mdistdir } -> mdistdir) <$> munit)
where
isCabalHelperUnit
Unit { uPId = PkgId (PkgName n) _
, uType = UnitTypeLocal
, uComps
} | n == "cabal-helper" &&
Map.member (CompNameExe "cabal-helper-wrapper") uComps
= True
isCabalHelperUnit _ = False
toOldBuildDistDir x = return $ Just x
libexecNotFoundError :: String
-> FilePath
-> String
-> String
libexecNotFoundError exe dir reportBug = printf
( "Could not find $libexecdir/%s\n"
++"\n"
++"If you are a cabal-helper developer you can set the environment variable\n"
++"`cabal_helper_libexecdir' to override $libexecdir[1]. The following will\n"
++"work in the cabal-helper source tree:\n"
++"\n"
++" $ export cabal_helper_libexecdir=$PWD/dist/build/%s\n"
++"\n"
++"[1]: %s\n"
++"\n"
++"If you don't know what I'm talking about something went wrong with your\n"
++"installation. Please report this problem here:\n"
++"\n"
++" %s") exe exe dir reportBug
getExecutablePath' :: IO FilePath
getExecutablePath' =
#if MIN_VERSION_base(4,6,0)
getExecutablePath
#else
getProgName
#endif
lookupEnv' :: String -> IO (Maybe String)
lookupEnv' k = lookup k <$> getEnvironment
exeExtension' :: FilePath
exeExtension'
| Windows <- buildOS = "exe"
| otherwise = ""