Make “sublibrary” standard terminology in docs
[cabal.git] / Cabal / src / Distribution / Simple / BuildPaths.hs
blob386a6e7fc822cd30405ece11d760c92b489628aa
1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE RankNTypes #-}
4 -----------------------------------------------------------------------------
6 -- |
7 -- Module : Distribution.Simple.BuildPaths
8 -- Copyright : Isaac Jones 2003-2004,
9 -- Duncan Coutts 2008
10 -- License : BSD3
12 -- Maintainer : cabal-devel@haskell.org
13 -- Portability : portable
15 -- A bunch of dirs, paths and file names used for intermediate build steps.
16 module Distribution.Simple.BuildPaths
17 ( defaultDistPref
18 , srcPref
19 , buildInfoPref
20 , haddockDirName
21 , hscolourPref
22 , haddockPref
23 , autogenPackageModulesDir
24 , autogenComponentModulesDir
25 , autogenPathsModuleName
26 , autogenPackageInfoModuleName
27 , cppHeaderName
28 , haddockName
29 , mkGenericStaticLibName
30 , mkLibName
31 , mkProfLibName
32 , mkGenericSharedLibName
33 , mkSharedLibName
34 , mkStaticLibName
35 , mkGenericSharedBundledLibName
36 , exeExtension
37 , objExtension
38 , dllExtension
39 , staticLibExtension
41 -- * Source files & build directories
42 , getSourceFiles
43 , getLibSourceFiles
44 , getExeSourceFiles
45 , getFLibSourceFiles
46 , exeBuildDir
47 , flibBuildDir
48 ) where
50 import Distribution.Compat.Prelude
51 import Prelude ()
53 import Data.List (stripPrefix)
54 import Distribution.Compiler
55 import Distribution.ModuleName as ModuleName
56 import Distribution.Package
57 import Distribution.PackageDescription
58 import Distribution.Pretty
59 import Distribution.Simple.Errors
60 import Distribution.Simple.LocalBuildInfo
61 import Distribution.Simple.Setup.Common (defaultDistPref)
62 import Distribution.Simple.Setup.Haddock (HaddockTarget (..))
63 import Distribution.Simple.Utils
64 import Distribution.System
65 import Distribution.Utils.Path
66 import Distribution.Verbosity
67 import System.FilePath (normalise, (<.>), (</>))
69 -- ---------------------------------------------------------------------------
70 -- Build directories and files
72 srcPref :: FilePath -> FilePath
73 srcPref distPref = distPref </> "src"
75 hscolourPref :: HaddockTarget -> FilePath -> PackageDescription -> FilePath
76 hscolourPref = haddockPref
78 -- | Build info json file, generated in every build
79 buildInfoPref :: FilePath -> FilePath
80 buildInfoPref distPref = distPref </> "build-info.json"
82 -- | This is the name of the directory in which the generated haddocks
83 -- should be stored. It does not include the @<dist>/doc/html@ prefix.
84 haddockDirName :: HaddockTarget -> PackageDescription -> FilePath
85 haddockDirName ForDevelopment = prettyShow . packageName
86 haddockDirName ForHackage = (++ "-docs") . prettyShow . packageId
88 -- | The directory to which generated haddock documentation should be written.
89 haddockPref :: HaddockTarget -> FilePath -> PackageDescription -> FilePath
90 haddockPref haddockTarget distPref pkg_descr =
91 distPref </> "doc" </> "html" </> haddockDirName haddockTarget pkg_descr
93 -- | The directory in which we put auto-generated modules for EVERY
94 -- component in the package.
95 autogenPackageModulesDir :: LocalBuildInfo -> String
96 autogenPackageModulesDir lbi = buildDir lbi </> "global-autogen"
98 -- | The directory in which we put auto-generated modules for a
99 -- particular component.
100 autogenComponentModulesDir :: LocalBuildInfo -> ComponentLocalBuildInfo -> String
101 autogenComponentModulesDir lbi clbi = componentBuildDir lbi clbi </> "autogen"
103 -- NB: Look at 'checkForeignDeps' for where a simplified version of this
104 -- has been copy-pasted.
106 cppHeaderName :: String
107 cppHeaderName = "cabal_macros.h"
109 -- | The name of the auto-generated Paths_* module associated with a package
110 autogenPathsModuleName :: PackageDescription -> ModuleName
111 autogenPathsModuleName pkg_descr =
112 ModuleName.fromString $
113 "Paths_" ++ map fixchar (prettyShow (packageName pkg_descr))
114 where
115 fixchar '-' = '_'
116 fixchar c = c
118 -- | The name of the auto-generated PackageInfo_* module associated with a package
119 autogenPackageInfoModuleName :: PackageDescription -> ModuleName
120 autogenPackageInfoModuleName pkg_descr =
121 ModuleName.fromString $
122 "PackageInfo_" ++ map fixchar (prettyShow (packageName pkg_descr))
123 where
124 fixchar '-' = '_'
125 fixchar c = c
127 haddockName :: PackageDescription -> FilePath
128 haddockName pkg_descr = prettyShow (packageName pkg_descr) <.> "haddock"
130 -- -----------------------------------------------------------------------------
131 -- Source File helper
133 getLibSourceFiles
134 :: Verbosity
135 -> LocalBuildInfo
136 -> Library
137 -> ComponentLocalBuildInfo
138 -> IO [(ModuleName.ModuleName, FilePath)]
139 getLibSourceFiles verbosity lbi lib clbi = getSourceFiles verbosity searchpaths modules
140 where
141 bi = libBuildInfo lib
142 modules = allLibModules lib clbi
143 searchpaths =
144 componentBuildDir lbi clbi
145 : map getSymbolicPath (hsSourceDirs bi)
146 ++ [ autogenComponentModulesDir lbi clbi
147 , autogenPackageModulesDir lbi
150 getExeSourceFiles
151 :: Verbosity
152 -> LocalBuildInfo
153 -> Executable
154 -> ComponentLocalBuildInfo
155 -> IO [(ModuleName.ModuleName, FilePath)]
156 getExeSourceFiles verbosity lbi exe clbi = do
157 moduleFiles <- getSourceFiles verbosity searchpaths modules
158 srcMainPath <- findFileEx verbosity (map getSymbolicPath $ hsSourceDirs bi) (modulePath exe)
159 return ((ModuleName.main, srcMainPath) : moduleFiles)
160 where
161 bi = buildInfo exe
162 modules = otherModules bi
163 searchpaths =
164 autogenComponentModulesDir lbi clbi
165 : autogenPackageModulesDir lbi
166 : exeBuildDir lbi exe
167 : map getSymbolicPath (hsSourceDirs bi)
169 getFLibSourceFiles
170 :: Verbosity
171 -> LocalBuildInfo
172 -> ForeignLib
173 -> ComponentLocalBuildInfo
174 -> IO [(ModuleName.ModuleName, FilePath)]
175 getFLibSourceFiles verbosity lbi flib clbi = getSourceFiles verbosity searchpaths modules
176 where
177 bi = foreignLibBuildInfo flib
178 modules = otherModules bi
179 searchpaths =
180 autogenComponentModulesDir lbi clbi
181 : autogenPackageModulesDir lbi
182 : flibBuildDir lbi flib
183 : map getSymbolicPath (hsSourceDirs bi)
185 getSourceFiles
186 :: Verbosity
187 -> [FilePath]
188 -> [ModuleName.ModuleName]
189 -> IO [(ModuleName.ModuleName, FilePath)]
190 getSourceFiles verbosity dirs modules = flip traverse modules $ \m ->
191 fmap ((,) m) $
192 findFileWithExtension ["hs", "lhs", "hsig", "lhsig"] dirs (ModuleName.toFilePath m)
193 >>= maybe (notFound m) (return . normalise)
194 where
195 notFound module_ =
196 dieWithException verbosity $ CantFindSourceModule module_
198 -- | The directory where we put build results for an executable
199 exeBuildDir :: LocalBuildInfo -> Executable -> FilePath
200 exeBuildDir lbi exe = buildDir lbi </> nm </> nm ++ "-tmp"
201 where
202 nm = unUnqualComponentName $ exeName exe
204 -- | The directory where we put build results for a foreign library
205 flibBuildDir :: LocalBuildInfo -> ForeignLib -> FilePath
206 flibBuildDir lbi flib = buildDir lbi </> nm </> nm ++ "-tmp"
207 where
208 nm = unUnqualComponentName $ foreignLibName flib
210 -- ---------------------------------------------------------------------------
211 -- Library file names
213 -- | Create a library name for a static library from a given name.
214 -- Prepends @lib@ and appends the static library extension (@.a@).
215 mkGenericStaticLibName :: String -> String
216 mkGenericStaticLibName lib = "lib" ++ lib <.> "a"
218 mkLibName :: UnitId -> String
219 mkLibName lib = mkGenericStaticLibName (getHSLibraryName lib)
221 mkProfLibName :: UnitId -> String
222 mkProfLibName lib = mkGenericStaticLibName (getHSLibraryName lib ++ "_p")
224 -- | Create a library name for a shared library from a given name.
225 -- Prepends @lib@ and appends the @-\<compilerFlavour\>\<compilerVersion\>@
226 -- as well as the shared library extension.
227 mkGenericSharedLibName :: Platform -> CompilerId -> String -> String
228 mkGenericSharedLibName platform (CompilerId compilerFlavor compilerVersion) lib =
229 mconcat ["lib", lib, "-", comp <.> dllExtension platform]
230 where
231 comp = prettyShow compilerFlavor ++ prettyShow compilerVersion
233 -- Implement proper name mangling for dynamical shared objects
234 -- @libHS\<packagename\>-\<compilerFlavour\>\<compilerVersion\>@
235 -- e.g. @libHSbase-2.1-ghc6.6.1.so@
236 mkSharedLibName :: Platform -> CompilerId -> UnitId -> String
237 mkSharedLibName platform comp lib =
238 mkGenericSharedLibName platform comp (getHSLibraryName lib)
240 -- Static libs are named the same as shared libraries, only with
241 -- a different extension.
242 mkStaticLibName :: Platform -> CompilerId -> UnitId -> String
243 mkStaticLibName platform (CompilerId compilerFlavor compilerVersion) lib =
244 "lib" ++ getHSLibraryName lib ++ "-" ++ comp <.> staticLibExtension platform
245 where
246 comp = prettyShow compilerFlavor ++ prettyShow compilerVersion
248 -- | Create a library name for a bundled shared library from a given name.
249 -- This matches the naming convention for shared libraries as implemented in
250 -- GHC's packageHsLibs function in the Packages module.
251 -- If the given name is prefixed with HS, then this prepends 'lib' and appends
252 -- the compiler flavour/version and shared library extension e.g.:
253 -- "HSrts-1.0" -> "libHSrts-1.0-ghc8.7.20190109.so"
254 -- Otherwise the given name should be prefixed with 'C', then this strips the
255 -- 'C', prepends 'lib' and appends the shared library extension e.g.:
256 -- "Cffi" -> "libffi.so"
257 mkGenericSharedBundledLibName :: Platform -> CompilerId -> String -> String
258 mkGenericSharedBundledLibName platform comp lib
259 | "HS" `isPrefixOf` lib =
260 mkGenericSharedLibName platform comp lib
261 | Just lib' <- stripPrefix "C" lib =
262 "lib" ++ lib' <.> dllExtension platform
263 | otherwise =
264 error ("Don't understand library name " ++ lib)
266 -- ------------------------------------------------------------
268 -- * Platform file extensions
270 -- ------------------------------------------------------------
272 -- | Default extension for executable files on the current platform.
273 -- (typically @\"\"@ on Unix and @\"exe\"@ on Windows or OS\/2)
274 exeExtension :: Platform -> String
275 exeExtension platform = case platform of
276 Platform _ Windows -> "exe"
277 Platform Wasm32 _ -> "wasm"
278 _ -> ""
280 -- | Extension for object files. For GHC the extension is @\"o\"@.
281 objExtension :: String
282 objExtension = "o"
284 -- | Extension for dynamically linked (or shared) libraries
285 -- (typically @\"so\"@ on Unix and @\"dll\"@ on Windows)
286 dllExtension :: Platform -> String
287 dllExtension (Platform _arch os) = case os of
288 Windows -> "dll"
289 OSX -> "dylib"
290 _ -> "so"
292 -- | Extension for static libraries
294 -- TODO: Here, as well as in dllExtension, it's really the target OS that we're
295 -- interested in, not the build OS.
296 staticLibExtension :: Platform -> String
297 staticLibExtension (Platform _arch os) = case os of
298 Windows -> "lib"
299 _ -> "a"