module Configuration.Utils.Setup
( main
, mkPkgInfoModules
) where
import Distribution.PackageDescription
import Distribution.Simple
import Distribution.Simple.Setup
import qualified Distribution.InstalledPackageInfo as I
import Distribution.Simple.LocalBuildInfo
import Distribution.Simple.BuildPaths
import Distribution.Simple.PackageIndex
import Distribution.Text
import System.Process
import Control.Applicative
import Control.Monad
import qualified Data.ByteString as B
import Data.ByteString.Char8 (pack)
import Data.Char (isSpace)
import Data.List (intercalate)
import Data.Monoid
import Prelude hiding (readFile, writeFile)
import System.Directory (doesFileExist, doesDirectoryExist, createDirectoryIfMissing)
import System.Exit (ExitCode(ExitSuccess))
main :: IO ()
main = defaultMainWithHooks (mkPkgInfoModules simpleUserHooks)
mkPkgInfoModules
:: UserHooks
-> UserHooks
mkPkgInfoModules hooks = hooks
{ postConf = mkPkgInfoModulesPostConf (postConf hooks)
}
mkPkgInfoModulesPostConf
:: (Args -> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO ())
-> Args
-> ConfigFlags
-> PackageDescription
-> LocalBuildInfo
-> IO ()
mkPkgInfoModulesPostConf hook args flags pkgDesc bInfo = do
mkModules
hook args flags pkgDesc bInfo
where
mkModules = mapM_ (f . \(a,_,_) -> a) $ componentsConfigs bInfo
f cname = case cname of
CLibName -> updatePkgInfoModule Nothing pkgDesc bInfo
CExeName s -> updatePkgInfoModule (Just s) pkgDesc bInfo
CTestName s -> updatePkgInfoModule (Just s) pkgDesc bInfo
CBenchName s -> updatePkgInfoModule (Just s) pkgDesc bInfo
pkgInfoModuleName :: Maybe String -> String
pkgInfoModuleName Nothing = "PkgInfo"
pkgInfoModuleName (Just cn) = "PkgInfo_" ++ map tr cn
where
tr '-' = '_'
tr c = c
pkgInfoFileName :: Maybe String -> LocalBuildInfo -> FilePath
pkgInfoFileName cn bInfo = autogenModulesDir bInfo ++ "/" ++ pkgInfoModuleName cn ++ ".hs"
trim :: String -> String
trim = f . f
where f = reverse . dropWhile isSpace
getVCS :: IO (Maybe RepoType)
getVCS =
doesDirectoryExist ".hg" >>= \x0 -> if x0
then return (Just Mercurial)
else doesDirectoryExist ".git" >>= \x1 -> return $ if x1
then Just Git
else Nothing
flagNameStr :: FlagName -> String
flagNameStr (FlagName s) = s
pkgInfoModule :: Maybe String -> PackageDescription -> LocalBuildInfo -> IO B.ByteString
pkgInfoModule cName pkgDesc bInfo = do
(tag, revision, branch) <- getVCS >>= \x -> case x of
Just Mercurial -> hgInfo
Just Git -> gitInfo
_ -> noVcsInfo
let vcsBranch = if branch == "default" || branch == "master" then "" else branch
vcsVersion = intercalate "-" . filter (/= "") $ [tag, revision, vcsBranch]
flags = map (flagNameStr . fst) . filter snd . configConfigurationsFlags . configFlags $ bInfo
licenseString <- licenseFilesText pkgDesc
return $ B.intercalate "\n"
[ "{-# LANGUAGE OverloadedStrings #-}"
, "{-# LANGUAGE RankNTypes #-}"
, ""
, "module " <> (pack . pkgInfoModuleName) cName <> " where"
, ""
, " import Data.String (IsString)"
, " import Data.Monoid"
, ""
, " name :: IsString a => Maybe a"
, " name = " <> maybe "Nothing" (\x -> "Just \"" <> pack x <> "\"") cName
, ""
, " tag :: IsString a => a"
, " tag = \"" <> pack tag <> "\""
, ""
, " revision :: IsString a => a"
, " revision = \"" <> pack revision <> "\""
, ""
, " branch :: IsString a => a"
, " branch = \"" <> pack branch <> "\""
, ""
, " branch' :: IsString a => a"
, " branch' = \"" <> pack vcsBranch <> "\""
, ""
, " vcsVersion :: IsString a => a"
, " vcsVersion = \"" <> pack vcsVersion <> "\""
, ""
, " compiler :: IsString a => a"
, " compiler = \"" <> (pack . display . compilerId . compiler) bInfo <> "\""
, ""
, " flags :: IsString a => [a]"
, " flags = " <> (pack . show) flags
, ""
, " optimisation :: IsString a => a"
, " optimisation = \"" <> (displayOptimisationLevel . withOptimization) bInfo <> "\""
, ""
, " arch :: IsString a => a"
, " arch = \"" <> (pack . display . hostPlatform) bInfo <> "\""
, ""
, " license :: IsString a => a"
, " license = \"" <> (pack . display . license) pkgDesc <> "\""
, ""
, " licenseText :: IsString a => a"
, " licenseText = " <> (pack . show) licenseString
, ""
, " copyright :: IsString a => a"
, " copyright = \"" <> (pack . copyright) pkgDesc <> "\""
, ""
, " author :: IsString a => a"
, " author = \"" <> (pack . author) pkgDesc <> "\""
, ""
, " homepage :: IsString a => a"
, " homepage = \"" <> (pack . homepage) pkgDesc <> "\""
, ""
, " package :: IsString a => a"
, " package = \"" <> (pack . display . package) pkgDesc <> "\""
, ""
, " packageName :: IsString a => a"
, " packageName = \"" <> (pack . display . packageName) pkgDesc <> "\""
, ""
, " packageVersion :: IsString a => a"
, " packageVersion = \"" <> (pack . display . packageVersion) pkgDesc <> "\""
, ""
, " dependencies :: IsString a => [a]"
, " dependencies = " <> (pack . show . map (display . packageId) . allPackages . installedPkgs) bInfo
, ""
, " dependenciesWithLicenses :: IsString a => [a]"
, " dependenciesWithLicenses = " <> (pack . show . map pkgIdWithLicense . allPackages . installedPkgs) bInfo
, ""
, " versionString :: (Monoid a, IsString a) => a"
, " versionString = case name of"
, " Nothing -> package <> \" (revision \" <> vcsVersion <> \")\""
, " Just n -> n <> \"-\" <> packageVersion <> \" (package \" <> package <> \" revision \" <> vcsVersion <> \")\""
, ""
, " info :: (Monoid a, IsString a) => a"
, " info = versionString <> \"\\n\" <> copyright"
, ""
, " longInfo :: (Monoid a, IsString a) => a"
, " longInfo = info <> \"\\n\\n\""
, " <> \"Author: \" <> author <> \"\\n\""
, " <> \"License: \" <> license <> \"\\n\""
, " <> \"Homepage: \" <> homepage <> \"\\n\""
, " <> \"Build with: \" <> compiler <> \" (\" <> arch <> \")\" <> \"\\n\""
, " <> \"Build flags: \" <> mconcat (map (\\x -> \" \" <> x) flags) <> \"\\n\""
, " <> \"Optimisation: \" <> optimisation <> \"\\n\\n\""
, " <> \"Dependencies:\\n\" <> mconcat (map (\\x -> \" \" <> x <> \"\\n\") dependenciesWithLicenses)"
, ""
, " pkgInfo :: (Monoid a, IsString a) => (a, a, a, a)"
, " pkgInfo ="
, " ( info"
, " , longInfo"
, " , versionString"
, " , licenseText"
, " )"
, ""
]
where
displayOptimisationLevel NoOptimisation = "none"
displayOptimisationLevel NormalOptimisation = "normal"
displayOptimisationLevel MaximumOptimisation = "maximum"
updatePkgInfoModule :: Maybe String -> PackageDescription -> LocalBuildInfo -> IO ()
updatePkgInfoModule cName pkgDesc bInfo = do
createDirectoryIfMissing True $ autogenModulesDir bInfo
newFile <- pkgInfoModule cName pkgDesc bInfo
let update = B.writeFile fileName newFile
doesFileExist fileName >>= \x -> if x
then do
oldRevisionFile <- B.readFile fileName
when (oldRevisionFile /= newFile) update
else
update
where
fileName = pkgInfoFileName cName bInfo
licenseFilesText :: PackageDescription -> IO B.ByteString
licenseFilesText PackageDescription{ licenseFiles = fileNames } =
B.intercalate "\n------------------------------------------------------------\n" <$> mapM fileText fileNames
where
fileText file = doesFileExist file >>= \x -> if x
then B.readFile file
else return ""
hgInfo :: IO (String, String, String)
hgInfo = do
tag <- trim <$> readProcess "hg" ["id", "-r", "max(ancestors(\".\") and tag())", "-t"] ""
rev <- trim <$> readProcess "hg" ["id", "-i"] ""
branch <- trim <$> readProcess "hg" ["id", "-b"] ""
return (tag, rev, branch)
gitInfo :: IO (String, String, String)
gitInfo = do
tag <- do
(exitCode, out, _err) <- readProcessWithExitCode "git" ["describe", "--exact-match", "--tags", "--abbrev=0"] ""
case exitCode of
ExitSuccess -> return $ trim out
_ -> return ""
rev <- trim <$> readProcess "git" ["rev-parse", "--short", "HEAD"] ""
branch <- trim <$> readProcess "git" ["rev-parse", "--abbrev-ref", "HEAD"] ""
return (tag, rev, branch)
noVcsInfo :: IO (String, String, String)
noVcsInfo = return ("", "", "")
pkgIdWithLicense :: I.InstalledPackageInfo -> String
pkgIdWithLicense a = (display . packageId) a
++ " ["
++ (display . I.license) a
++ (if cr /= "" then ", " ++ cr else "")
++ "]"
where
cr = (unwords . words . I.copyright) a