54
54
-- Note: At the moment this is only supported when using the GHC compiler.
55
55
--
56
56
57
+ {-# LANGUAGE OverloadedStrings #-}
58
+
57
59
module Distribution.Simple.ShowBuildInfo
58
60
( mkBuildInfo , mkBuildInfo' , mkCompilerInfo , mkComponentInfo ) where
59
61
62
+ import qualified Data.Text as T
63
+
60
64
import Distribution.Compat.Prelude
61
65
import Prelude ()
62
66
@@ -79,36 +83,37 @@ import Distribution.Pretty
79
83
-- | Construct a JSON document describing the build information for a
80
84
-- package.
81
85
mkBuildInfo
82
- :: PackageDescription -- ^ Mostly information from the .cabal file
86
+ :: FilePath -- ^ The source directory of the package
87
+ -> PackageDescription -- ^ Mostly information from the .cabal file
83
88
-> LocalBuildInfo -- ^ Configuration information
84
89
-> BuildFlags -- ^ Flags that the user passed to build
85
90
-> [TargetInfo ]
86
91
-> Json
87
- mkBuildInfo pkg_descr lbi _flags targetsToBuild =
88
- mkBuildInfo' (mkCompilerInfo (withPrograms lbi) (compiler lbi))
89
- (map (mkComponentInfo pkg_descr lbi . targetCLBI) targetsToBuild)
92
+ mkBuildInfo wdir pkg_descr lbi _flags targetsToBuild =
93
+ JsonObject $
94
+ mkBuildInfo' (mkCompilerInfo (withPrograms lbi) (compiler lbi))
95
+ (map (mkComponentInfo wdir pkg_descr lbi . targetCLBI) targetsToBuild)
90
96
91
97
-- | A variant of 'mkBuildInfo' if you need to call 'mkCompilerInfo' and
92
98
-- 'mkComponentInfo' yourself.
93
99
mkBuildInfo'
94
100
:: Json -- ^ The 'Json' from 'mkCompilerInfo'
95
101
-> [Json ] -- ^ The 'Json' from 'mkComponentInfo'
96
- -> Json
102
+ -> [( T. Text , Json )]
97
103
mkBuildInfo' cmplrInfo componentInfos =
98
- JsonObject
99
- [ " cabal-version" .= JsonString (display cabalVersion)
104
+ [ " cabal-version" .= JsonString (T. pack (display cabalVersion))
100
105
, " compiler" .= cmplrInfo
101
106
, " components" .= JsonArray componentInfos
102
107
]
103
108
104
109
mkCompilerInfo :: ProgramDb -> Compiler -> Json
105
110
mkCompilerInfo programDb cmplr = JsonObject
106
- [ " flavour" .= JsonString (prettyShow $ compilerFlavor cmplr)
107
- , " compiler-id" .= JsonString (showCompilerId cmplr)
111
+ [ " flavour" .= JsonString (T. pack ( prettyShow $ compilerFlavor cmplr) )
112
+ , " compiler-id" .= JsonString (T. pack ( showCompilerId cmplr) )
108
113
, " path" .= path
109
114
]
110
115
where
111
- path = maybe JsonNull (JsonString . programPath)
116
+ path = maybe JsonNull (JsonString . T. pack . programPath)
112
117
$ (flavorToProgram . compilerFlavor $ cmplr)
113
118
>>= flip lookupProgram programDb
114
119
@@ -119,16 +124,17 @@ mkCompilerInfo programDb cmplr = JsonObject
119
124
flavorToProgram JHC = Just jhcProgram
120
125
flavorToProgram _ = Nothing
121
126
122
- mkComponentInfo :: PackageDescription -> LocalBuildInfo -> ComponentLocalBuildInfo -> Json
123
- mkComponentInfo pkg_descr lbi clbi = JsonObject
127
+ mkComponentInfo :: FilePath -> PackageDescription -> LocalBuildInfo -> ComponentLocalBuildInfo -> Json
128
+ mkComponentInfo wdir pkg_descr lbi clbi = JsonObject $
124
129
[ " type" .= JsonString compType
125
- , " name" .= JsonString (prettyShow name)
126
- , " unit-id" .= JsonString (prettyShow $ componentUnitId clbi)
130
+ , " name" .= JsonString (T. pack $ prettyShow name)
131
+ , " unit-id" .= JsonString (T. pack $ prettyShow $ componentUnitId clbi)
127
132
, " compiler-args" .= JsonArray (map JsonString $ getCompilerArgs bi lbi clbi)
128
- , " modules" .= JsonArray (map (JsonString . display) modules)
129
- , " src-files" .= JsonArray (map JsonString sourceFiles)
130
- , " src-dirs" .= JsonArray (map JsonString $ hsSourceDirs bi)
131
- ]
133
+ , " modules" .= JsonArray (map (JsonString . T. pack . display) modules)
134
+ , " src-files" .= JsonArray (map (JsonString . T. pack) sourceFiles)
135
+ , " hs-src-dirs" .= JsonArray (map (JsonString . T. pack) $ hsSourceDirs bi)
136
+ , " src-dir" .= JsonString (T. pack wdir)
137
+ ] <> cabalFile
132
138
where
133
139
name = componentLocalName clbi
134
140
bi = componentBuildInfo comp
@@ -147,14 +153,17 @@ mkComponentInfo pkg_descr lbi clbi = JsonObject
147
153
CLib _ -> []
148
154
CExe exe -> [modulePath exe]
149
155
_ -> []
156
+ cabalFile
157
+ | Just fp <- pkgDescrFile lbi = [(" cabal-file" , JsonString (T. pack fp))]
158
+ | otherwise = []
150
159
151
160
-- | Get the command-line arguments that would be passed
152
161
-- to the compiler to build the given component.
153
162
getCompilerArgs
154
163
:: BuildInfo
155
164
-> LocalBuildInfo
156
165
-> ComponentLocalBuildInfo
157
- -> [String ]
166
+ -> [T. Text ]
158
167
getCompilerArgs bi lbi clbi =
159
168
case compilerFlavor $ compiler lbi of
160
169
GHC -> ghc
@@ -163,6 +172,7 @@ getCompilerArgs bi lbi clbi =
163
172
" build arguments for compiler " ++ show c
164
173
where
165
174
-- This is absolutely awful
166
- ghc = GHC. renderGhcOptions (compiler lbi) (hostPlatform lbi) baseOpts
175
+ ghc = T. pack <$>
176
+ GHC. renderGhcOptions (compiler lbi) (hostPlatform lbi) baseOpts
167
177
where
168
178
baseOpts = GHC. componentGhcOptions normal lbi bi clbi (buildDir lbi)
0 commit comments