Skip to content

Commit

Permalink
Rework show-build-info to use ProjectPlanning/Building infrastructure
Browse files Browse the repository at this point in the history
This fixes a lot of edge cases for example where the package db wasn't
created at the time of configuring. Manually doing the setup.hs wrapper
stuff was hairy.

It also changes the internal representation of JSON to Text rather than
String, and introduces the buildinfo-components-only flag in the Cabal
part to make it easier to stitch back the JSON into an array in
cabal-install.

Turns out we do need to keep the show-build-info part inside Cabal as we
rely on LocalBuildInfo which can change between versions, and we would
need to do this anyway if we wanted to utilise the
ProjectPlanning/Building infrastructure.
  • Loading branch information
lukel97 committed Jul 8, 2020
1 parent 25aef99 commit 84aa560
Show file tree
Hide file tree
Showing 37 changed files with 328 additions and 239 deletions.
33 changes: 19 additions & 14 deletions Cabal/Distribution/Simple.hs
Original file line number Diff line number Diff line change
Expand Up @@ -108,6 +108,8 @@ import Data.List (unionBy, (\\))

import Distribution.PackageDescription.Parsec

import qualified Data.Text.IO as T

-- | A simple implementation of @main@ for a Cabal setup script.
-- It reads the package description file using IO, and performs the
-- action specified on the command line.
Expand Down Expand Up @@ -265,31 +267,34 @@ buildAction hooks flags args = do
hooks flags' { buildArgs = args } args

showBuildInfoAction :: UserHooks -> ShowBuildInfoFlags -> Args -> IO ()
showBuildInfoAction hooks (ShowBuildInfoFlags flags fileOutput) args = do
distPref <- findDistPrefOrDefault (buildDistPref flags)
let verbosity = fromFlag $ buildVerbosity flags
showBuildInfoAction hooks flags args = do
let buildFlags = buildInfoBuildFlags flags
distPref <- findDistPrefOrDefault (buildDistPref buildFlags)
let verbosity = fromFlag $ buildVerbosity buildFlags
lbi <- getBuildConfig hooks verbosity distPref
let flags' = flags { buildDistPref = toFlag distPref
, buildCabalFilePath = maybeToFlag (cabalFilePath lbi)
}
let buildFlags' =
buildFlags { buildDistPref = toFlag distPref
, buildCabalFilePath = maybeToFlag (cabalFilePath lbi)
}

progs <- reconfigurePrograms verbosity
(buildProgramPaths flags')
(buildProgramArgs flags')
(buildProgramPaths buildFlags')
(buildProgramArgs buildFlags')
(withPrograms lbi)

pbi <- preBuild hooks args flags'
pbi <- preBuild hooks args buildFlags'
let lbi' = lbi { withPrograms = progs }
pkg_descr0 = localPkgDescr lbi'
pkg_descr = updatePackageDescription pbi pkg_descr0
-- TODO: Somehow don't ignore build hook?
buildInfoString <- showBuildInfo pkg_descr lbi' flags

case fileOutput of
Nothing -> putStr buildInfoString
Just fp -> writeFile fp buildInfoString
buildInfoText <- showBuildInfo pkg_descr lbi' flags

case buildInfoOutputFile flags of
Nothing -> T.putStr buildInfoText
Just fp -> T.writeFile fp buildInfoText

postBuild hooks args flags' pkg_descr lbi'
postBuild hooks args buildFlags' pkg_descr lbi'

replAction :: UserHooks -> ReplFlags -> Args -> IO ()
replAction hooks flags args = do
Expand Down
24 changes: 17 additions & 7 deletions Cabal/Distribution/Simple/Build.hs
Original file line number Diff line number Diff line change
Expand Up @@ -89,6 +89,7 @@ import Control.Monad
import qualified Data.Set as Set
import System.FilePath ( (</>), (<.>), takeDirectory )
import System.Directory ( getCurrentDirectory )
import qualified Data.Text as Text

-- -----------------------------------------------------------------------------
-- |Build the libraries and executables in this package.
Expand Down Expand Up @@ -133,15 +134,24 @@ build pkg_descr lbi flags suffixes = do


showBuildInfo :: PackageDescription -- ^ Mostly information from the .cabal file
-> LocalBuildInfo -- ^ Configuration information
-> BuildFlags -- ^ Flags that the user passed to build
-> IO String
-> LocalBuildInfo -- ^ Configuration information
-> ShowBuildInfoFlags -- ^ Flags that the user passed to build
-> IO Text.Text
showBuildInfo pkg_descr lbi flags = do
let verbosity = fromFlag (buildVerbosity flags)
targets <- readTargetInfos verbosity pkg_descr lbi (buildArgs flags)
let buildFlags = buildInfoBuildFlags flags
verbosity = fromFlag (buildVerbosity buildFlags)
targets <- readTargetInfos verbosity pkg_descr lbi (buildArgs buildFlags)
pwd <- getCurrentDirectory
let targetsToBuild = neededTargetsInBuildOrder' pkg_descr lbi (map nodeKey targets)
doc = mkBuildInfo pkg_descr lbi flags targetsToBuild
return $ renderJson doc ""
result
| fromFlag (buildInfoComponentsOnly flags) =
let components = map (mkComponentInfo pwd pkg_descr lbi . targetCLBI)
targetsToBuild
in Text.unlines $ map (flip renderJson mempty) components
| otherwise =
let json = mkBuildInfo pwd pkg_descr lbi buildFlags targetsToBuild
in renderJson json mempty
return result


repl :: PackageDescription -- ^ Mostly information from the .cabal file
Expand Down
17 changes: 12 additions & 5 deletions Cabal/Distribution/Simple/Setup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2217,15 +2217,18 @@ optionNumJobs get set =
-- ------------------------------------------------------------

data ShowBuildInfoFlags = ShowBuildInfoFlags
{ buildInfoBuildFlags :: BuildFlags
, buildInfoOutputFile :: Maybe FilePath
{ buildInfoBuildFlags :: BuildFlags
, buildInfoOutputFile :: Maybe FilePath
, buildInfoComponentsOnly :: Flag Bool
-- ^ If 'True' then only print components, each separated by a newline
} deriving (Show, Typeable)

defaultShowBuildFlags :: ShowBuildInfoFlags
defaultShowBuildFlags =
ShowBuildInfoFlags
{ buildInfoBuildFlags = defaultBuildFlags
, buildInfoOutputFile = Nothing
{ buildInfoBuildFlags = defaultBuildFlags
, buildInfoOutputFile = Nothing
, buildInfoComponentsOnly = Flag False
}

showBuildInfoCommand :: ProgramDb -> CommandUI ShowBuildInfoFlags
Expand Down Expand Up @@ -2262,8 +2265,12 @@ showBuildInfoCommand progDb = CommandUI
++
[ option [] ["buildinfo-json-output"]
"Write the result to the given file instead of stdout"
buildInfoOutputFile (\pf flags -> flags { buildInfoOutputFile = pf })
buildInfoOutputFile (\v flags -> flags { buildInfoOutputFile = v })
(reqArg' "FILE" Just (maybe [] pure))
, option [] ["buildinfo-components-only"]
"Print out only the component info, each separated by a newline"
buildInfoComponentsOnly (\v flags -> flags { buildInfoComponentsOnly = v})
trueArg
]

}
Expand Down
50 changes: 30 additions & 20 deletions Cabal/Distribution/Simple/ShowBuildInfo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -54,9 +54,13 @@
-- Note: At the moment this is only supported when using the GHC compiler.
--

{-# LANGUAGE OverloadedStrings #-}

module Distribution.Simple.ShowBuildInfo
( mkBuildInfo, mkBuildInfo', mkCompilerInfo, mkComponentInfo ) where

import qualified Data.Text as T

import Distribution.Compat.Prelude
import Prelude ()

Expand All @@ -79,36 +83,37 @@ import Distribution.Pretty
-- | Construct a JSON document describing the build information for a
-- package.
mkBuildInfo
:: PackageDescription -- ^ Mostly information from the .cabal file
:: FilePath -- ^ The source directory of the package
-> PackageDescription -- ^ Mostly information from the .cabal file
-> LocalBuildInfo -- ^ Configuration information
-> BuildFlags -- ^ Flags that the user passed to build
-> [TargetInfo]
-> Json
mkBuildInfo pkg_descr lbi _flags targetsToBuild =
mkBuildInfo' (mkCompilerInfo (withPrograms lbi) (compiler lbi))
(map (mkComponentInfo pkg_descr lbi . targetCLBI) targetsToBuild)
mkBuildInfo wdir pkg_descr lbi _flags targetsToBuild =
JsonObject $
mkBuildInfo' (mkCompilerInfo (withPrograms lbi) (compiler lbi))
(map (mkComponentInfo wdir pkg_descr lbi . targetCLBI) targetsToBuild)

-- | A variant of 'mkBuildInfo' if you need to call 'mkCompilerInfo' and
-- 'mkComponentInfo' yourself.
mkBuildInfo'
:: Json -- ^ The 'Json' from 'mkCompilerInfo'
-> [Json] -- ^ The 'Json' from 'mkComponentInfo'
-> Json
-> [(T.Text, Json)]
mkBuildInfo' cmplrInfo componentInfos =
JsonObject
[ "cabal-version" .= JsonString (display cabalVersion)
[ "cabal-version" .= JsonString (T.pack (display cabalVersion))
, "compiler" .= cmplrInfo
, "components" .= JsonArray componentInfos
]

mkCompilerInfo :: ProgramDb -> Compiler -> Json
mkCompilerInfo programDb cmplr = JsonObject
[ "flavour" .= JsonString (prettyShow $ compilerFlavor cmplr)
, "compiler-id" .= JsonString (showCompilerId cmplr)
[ "flavour" .= JsonString (T.pack (prettyShow $ compilerFlavor cmplr))
, "compiler-id" .= JsonString (T.pack (showCompilerId cmplr))
, "path" .= path
]
where
path = maybe JsonNull (JsonString . programPath)
path = maybe JsonNull (JsonString . T.pack . programPath)
$ (flavorToProgram . compilerFlavor $ cmplr)
>>= flip lookupProgram programDb

Expand All @@ -119,16 +124,17 @@ mkCompilerInfo programDb cmplr = JsonObject
flavorToProgram JHC = Just jhcProgram
flavorToProgram _ = Nothing

mkComponentInfo :: PackageDescription -> LocalBuildInfo -> ComponentLocalBuildInfo -> Json
mkComponentInfo pkg_descr lbi clbi = JsonObject
mkComponentInfo :: FilePath -> PackageDescription -> LocalBuildInfo -> ComponentLocalBuildInfo -> Json
mkComponentInfo wdir pkg_descr lbi clbi = JsonObject $
[ "type" .= JsonString compType
, "name" .= JsonString (prettyShow name)
, "unit-id" .= JsonString (prettyShow $ componentUnitId clbi)
, "name" .= JsonString (T.pack $ prettyShow name)
, "unit-id" .= JsonString (T.pack $ prettyShow $ componentUnitId clbi)
, "compiler-args" .= JsonArray (map JsonString $ getCompilerArgs bi lbi clbi)
, "modules" .= JsonArray (map (JsonString . display) modules)
, "src-files" .= JsonArray (map JsonString sourceFiles)
, "src-dirs" .= JsonArray (map JsonString $ hsSourceDirs bi)
]
, "modules" .= JsonArray (map (JsonString . T.pack . display) modules)
, "src-files" .= JsonArray (map (JsonString . T.pack) sourceFiles)
, "hs-src-dirs" .= JsonArray (map (JsonString . T.pack) $ hsSourceDirs bi)
, "src-dir" .= JsonString (T.pack wdir)
] <> cabalFile
where
name = componentLocalName clbi
bi = componentBuildInfo comp
Expand All @@ -147,14 +153,17 @@ mkComponentInfo pkg_descr lbi clbi = JsonObject
CLib _ -> []
CExe exe -> [modulePath exe]
_ -> []
cabalFile
| Just fp <- pkgDescrFile lbi = [("cabal-file", JsonString (T.pack fp))]
| otherwise = []

-- | Get the command-line arguments that would be passed
-- to the compiler to build the given component.
getCompilerArgs
:: BuildInfo
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> [String]
-> [T.Text]
getCompilerArgs bi lbi clbi =
case compilerFlavor $ compiler lbi of
GHC -> ghc
Expand All @@ -163,6 +172,7 @@ getCompilerArgs bi lbi clbi =
"build arguments for compiler "++show c
where
-- This is absolutely awful
ghc = GHC.renderGhcOptions (compiler lbi) (hostPlatform lbi) baseOpts
ghc = T.pack <$>
GHC.renderGhcOptions (compiler lbi) (hostPlatform lbi) baseOpts
where
baseOpts = GHC.componentGhcOptions normal lbi bi clbi (buildDir lbi)
69 changes: 42 additions & 27 deletions Cabal/Distribution/Utils/Json.hs
Original file line number Diff line number Diff line change
@@ -1,50 +1,65 @@
-- | Extremely simple JSON helper. Don't do anything too fancy with this!
{-# LANGUAGE OverloadedStrings #-}

-- | Extremely simple JSON helper. Don't do anything too fancy with this!
module Distribution.Utils.Json
( Json(..)
, (.=)
, renderJson
) where

import Data.Text (Text)
import qualified Data.Text as Text

data Json = JsonArray [Json]
| JsonBool !Bool
| JsonNull
| JsonNumber !Int
| JsonObject [(String, Json)]
| JsonString !String
| JsonObject [(Text, Json)]
| JsonRaw !Text
| JsonString !Text

renderJson :: Json -> ShowS
-- | A type to mirror 'ShowS'
type ShowT = Text -> Text

renderJson :: Json -> ShowT
renderJson (JsonArray objs) =
surround "[" "]" $ intercalate "," $ map renderJson objs
renderJson (JsonBool True) = showString "true"
renderJson (JsonBool False) = showString "false"
renderJson JsonNull = showString "null"
renderJson (JsonNumber n) = shows n
renderJson (JsonBool True) = showText "true"
renderJson (JsonBool False) = showText "false"
renderJson JsonNull = showText "null"
renderJson (JsonNumber n) = showText $ Text.pack (show n)
renderJson (JsonObject attrs) =
surround "{" "}" $ intercalate "," $ map render attrs
where
render (k,v) = (surround "\"" "\"" $ showString' k) . showString ":" . renderJson v
renderJson (JsonString s) = surround "\"" "\"" $ showString' s

surround :: String -> String -> ShowS -> ShowS
surround begin end middle = showString begin . middle . showString end

showString' :: String -> ShowS
showString' xs = showStringWorker xs
where
showStringWorker :: String -> ShowS
showStringWorker ('\"':as) = showString "\\\"" . showStringWorker as
showStringWorker ('\\':as) = showString "\\\\" . showStringWorker as
showStringWorker ('\'':as) = showString "\\\'" . showStringWorker as
showStringWorker (x:as) = showString [x] . showStringWorker as
showStringWorker [] = showString ""

intercalate :: String -> [ShowS] -> ShowS
render (k,v) = (surround "\"" "\"" $ showText' k) . showText ":" . renderJson v
renderJson (JsonString s) = surround "\"" "\"" $ showText' s
renderJson (JsonRaw s) = showText s

surround :: Text -> Text -> ShowT -> ShowT
surround begin end middle = showText begin . middle . showText end

showText :: Text -> ShowT
showText = (<>)

showText' :: Text -> ShowT
showText' xs = showStringWorker xs
where
showStringWorker :: Text -> ShowT
showStringWorker t =
case Text.uncons t of
Just ('\r', as) -> showText "\\r" . showStringWorker as
Just ('\n', as) -> showText "\\n" . showStringWorker as
Just ('\"', as) -> showText "\\\"" . showStringWorker as
Just ('\\', as) -> showText "\\\\" . showStringWorker as
Just (x, as) -> showText (Text.singleton x) . showStringWorker as
Nothing -> showText ""

intercalate :: Text -> [ShowT] -> ShowT
intercalate sep = go
where
go [] = id
go [x] = x
go (x:xs) = x . showString' sep . go xs
go (x:xs) = x . showText' sep . go xs

(.=) :: String -> Json -> (String, Json)
(.=) :: Text -> Json -> (Text, Json)
k .= v = (k, v)
Loading

0 comments on commit 84aa560

Please sign in to comment.