1This patch is based on https://github.com/sternenseemann/cabal/compare/982646d67b95b32813b89ab5d2d2f4d4dc03fb2b..7c49047f253e1f128e2df356400ec5da6f11066b
2and has been postprocessed with `filterdiff --strip=1 --addoldprefix=a/libraries/Cabal/ --addnewprefix=b/libraries/Cabal/`.
3Note that the base for the diff is not the Cabal 3.6.3.0 release tag, but
4982646d67b95b32813b89ab5d2d2f4d4dc03fb2b which is obtained by applying
5https://github.com/haskell/cabal/commit/6c796218c92f93c95e94d5ec2d077f6956f68e98
6on top of said release tag. That patch is applied to all our GHCs in the 9.2 series.
7
8Reasoning and explanation of the patch can be found in the comment in the diff for PathsModule.hs below.
9
10diffCabal/src/Distribution/Simple/Build/PathsModule.hs b/Cabal/src/Distribution/Simple/Build/PathsModule.hs
11index b2be7e1a8..9b63e9850 100644
12--- a/libraries/Cabal/Cabal/src/Distribution/Simple/Build/PathsModule.hs
13+++ b/libraries/Cabal/Cabal/src/Distribution/Simple/Build/PathsModule.hs
14@@ -46,6 +46,7 @@ generatePathsModule pkg_descr lbi clbi = Z.render Z.Z
15 , Z.zIsWindows = isWindows
16 , Z.zIsI386 = buildArch == I386
17 , Z.zIsX8664 = buildArch == X86_64
18+ , Z.zOr = (||)
19 , Z.zNot = not
20 , Z.zManglePkgName = showPkgName
21
22@@ -56,8 +57,112 @@ generatePathsModule pkg_descr lbi clbi = Z.render Z.Z
23 , Z.zDatadir = zDatadir
24 , Z.zLibexecdir = zLibexecdir
25 , Z.zSysconfdir = zSysconfdir
26+
27+ -- Sadly we can't be cleverer about this – we can't have literals in the template
28+ , Z.zShouldEmitDataDir = shouldEmit "DataDir"
29+ , Z.zShouldEmitLibDir = shouldEmit "LibDir"
30+ , Z.zShouldEmitDynLibDir = shouldEmit "DynLibDir"
31+ , Z.zShouldEmitLibexecDir = shouldEmit "LibexecDir"
32+ , Z.zShouldEmitSysconfDir = shouldEmit "SysconfDir"
33+
34+ , Z.zWarning = zWarning
35+ , Z.zShouldEmitWarning = zShouldEmitWarning
36 }
37 where
38+ -- GHC's NCG backend for aarch64-darwin does not support link-time dead code
39+ -- elimination to the extent that NCG does for other targets. Consequently,
40+ -- we struggle with unnecessarily retained store path references due to the
41+ -- use of `Paths_*` modules – even if `getLibDir` is not used, it'll end up
42+ -- in the final library or executables we build.
43+ --
44+ -- When using a different output for the executables and library, this
45+ -- becomes more sinister: The library will contain a reference to the bin
46+ -- output and itself due to `getLibDir` and `getBinDir`, but the executables
47+ -- will do so, too. Either due to linking dynamically or because the library
48+ -- is linked statically into the executable and retains those references.
49+ -- Since Nix disallows cyclical references between two outputs, it becomes
50+ -- impossible to use the `Paths_*` module and a separate `bin` output for
51+ -- aarch64-darwin.
52+ --
53+ -- The solution we have resorted to for now, is to trim the `Paths_*` module
54+ -- dynamically depending on what references *could* be used without causing
55+ -- a cyclical reference. That has the effect that any code that would not
56+ -- cause a cyclical reference with dead code elimination will compile and
57+ -- work for aarch64-darwin. If the code would use a `get*Dir` function that
58+ -- has been omitted, this would indicate that the code would have caused a
59+ -- cyclical reference anyways.
60+ --
61+ -- The logic for this makes some pretty big assumptions about installation
62+ -- prefixes that probably only hold fully in nixpkgs with
63+ -- `haskellPackages.mkDerivation`. Simple uses outside nixpkgs that have
64+ -- everything below the same prefix should continue to work as expected,
65+ -- though.
66+ --
67+ -- We assume the following:
68+ --
69+ -- - flat_prefix is `$out`.
70+ -- - flat_libdir etc. are always below `$out`.
71+ --
72+ -- Since in the normal case due to static linking `$bin` and `$out` will
73+ -- have the same references in libraries/executables, we need to either
74+ -- prevent usage of `getBinDir` or `getLibDir` to break the cycle in case
75+ -- `flat_bindir` is not below `$out`. We have decided to always allow usage
76+ -- of `getBinDir`, so `getLibDir` gets dropped if a separate `bin` output is
77+ -- used. This has the simple reason that `$out` which contains `flat_libdir`
78+ -- tends to be quite big – we would like to have a `bin` output that doesn't
79+ -- require keeping that around.
80+ pathEmittable :: FilePath -> Bool
81+ pathEmittable p
82+ -- If the executable installation target is below `$out` the reference
83+ -- cycle is within a single output (since libs are installed to `$out`)
84+ -- and thus unproblematic. We can use any and all `get*Dir` functions.
85+ | flat_prefix `isPrefixOf` flat_bindir = True
86+ -- Otherwise, we need to disallow all `get*Dir` functions that would cause
87+ -- a reference to `$out` which contains the libraries that would in turn
88+ -- reference `$bin`. This always include `flat_libdir` and friends, but
89+ -- can also include `flat_datadir` if no separate output for data files is
90+ -- used.
91+ | otherwise = not (flat_prefix `isPrefixOf` p)
92+
93+ -- This list maps the "name" of the directory to whether we want to include
94+ -- it in the `Paths_*` module or not. `shouldEmit` performs a lookup in this.
95+ dirs :: [(String, Bool)]
96+ dirs =
97+ map
98+ (\(name, path) -> (name, pathEmittable path))
99+ [ ("LibDir", flat_libdir)
100+ , ("DynLibDir", flat_dynlibdir)
101+ , ("DataDir", flat_datadir)
102+ , ("LibexecDir", flat_libexecdir)
103+ , ("SysconfDir", flat_sysconfdir)
104+ ]
105+
106+ shouldEmit :: String -> Bool
107+ shouldEmit name =
108+ case lookup name dirs of
109+ Just b -> b
110+ Nothing -> error "panic! BUG in Cabal Paths_ patch for aarch64-darwin, report this at https://github.com/nixos/nixpkgs/issues"
111+
112+ -- This is a comma separated list of all functions that have been omitted.
113+ -- This is included in a GHC warning which will be attached to the `Paths_*`
114+ -- module in case we are dropping any `get*Dir` functions that would
115+ -- normally exist.
116+ --
117+ -- TODO: getDataFileName is not accounted for at the moment.
118+ omittedFunctions :: String
119+ omittedFunctions =
120+ intercalate ", "
121+ $ map (("get" ++) . fst)
122+ $ filter (not . snd) dirs
123+
124+ zWarning :: String
125+ zWarning =
126+ show $
127+ "The following functions have been omitted by a nixpkgs-specific patch to Cabal: "
128+ ++ omittedFunctions
129+ zShouldEmitWarning :: Bool
130+ zShouldEmitWarning = any (not . snd) dirs
131+
132 supports_cpp = supports_language_pragma
133 supports_rebindable_syntax = ghc_newer_than (mkVersion [7,0,1])
134 supports_language_pragma = ghc_newer_than (mkVersion [6,6,1])
135diffCabal/src/Distribution/Simple/Build/PathsModule/Z.hs b/Cabal/src/Distribution/Simple/Build/PathsModule/Z.hs
136index 6488ea061..a6cdc8e31 100644
137--- a/libraries/Cabal/Cabal/src/Distribution/Simple/Build/PathsModule/Z.hs
138+++ b/libraries/Cabal/Cabal/src/Distribution/Simple/Build/PathsModule/Z.hs
139@@ -18,6 +18,14 @@ data Z
140 zDatadir :: FilePath,
141 zLibexecdir :: FilePath,
142 zSysconfdir :: FilePath,
143+ zShouldEmitLibDir :: Bool,
144+ zShouldEmitDynLibDir :: Bool,
145+ zShouldEmitLibexecDir :: Bool,
146+ zShouldEmitDataDir :: Bool,
147+ zShouldEmitSysconfDir :: Bool,
148+ zShouldEmitWarning :: Bool,
149+ zWarning :: String,
150+ zOr :: (Bool -> Bool -> Bool),
151 zNot :: (Bool -> Bool),
152 zManglePkgName :: (PackageName -> String)}
153 deriving Generic
154@@ -45,10 +53,51 @@ render z_root = execWriter $ do
155 tell "{-# OPTIONS_GHC -w #-}\n"
156 tell "module Paths_"
157 tell (zManglePkgName z_root (zPackageName z_root))
158- tell " (\n"
159+ tell "\n"
160+ tell " "
161+ if (zShouldEmitWarning z_root)
162+ then do
163+ tell "{-# WARNING "
164+ tell (zWarning z_root)
165+ tell " #-}"
166+ return ()
167+ else do
168+ return ()
169+ tell "\n"
170+ tell " (\n"
171 tell " version,\n"
172- tell " getBinDir, getLibDir, getDynLibDir, getDataDir, getLibexecDir,\n"
173- tell " getDataFileName, getSysconfDir\n"
174+ tell " getBinDir,\n"
175+ if (zOr z_root (zNot z_root (zAbsolute z_root)) (zShouldEmitLibDir z_root))
176+ then do
177+ tell " getLibDir,\n"
178+ return ()
179+ else do
180+ return ()
181+ if (zOr z_root (zNot z_root (zAbsolute z_root)) (zShouldEmitDynLibDir z_root))
182+ then do
183+ tell " getDynLibDir,\n"
184+ return ()
185+ else do
186+ return ()
187+ if (zOr z_root (zNot z_root (zAbsolute z_root)) (zShouldEmitLibexecDir z_root))
188+ then do
189+ tell " getLibexecDir,\n"
190+ return ()
191+ else do
192+ return ()
193+ if (zOr z_root (zNot z_root (zAbsolute z_root)) (zShouldEmitDataDir z_root))
194+ then do
195+ tell " getDataFileName,\n"
196+ tell " getDataDir,\n"
197+ return ()
198+ else do
199+ return ()
200+ if (zOr z_root (zNot z_root (zAbsolute z_root)) (zShouldEmitSysconfDir z_root))
201+ then do
202+ tell " getSysconfDir\n"
203+ return ()
204+ else do
205+ return ()
206 tell " ) where\n"
207 tell "\n"
208 if (zNot z_root (zAbsolute z_root))
209@@ -97,12 +146,15 @@ render z_root = execWriter $ do
210 tell (zVersionDigits z_root)
211 tell " []\n"
212 tell "\n"
213- tell "getDataFileName :: FilePath -> IO FilePath\n"
214- tell "getDataFileName name = do\n"
215- tell " dir <- getDataDir\n"
216- tell " return (dir `joinFileName` name)\n"
217- tell "\n"
218- tell "getBinDir, getLibDir, getDynLibDir, getDataDir, getLibexecDir, getSysconfDir :: IO FilePath\n"
219+ if (zOr z_root (zNot z_root (zAbsolute z_root)) (zShouldEmitDataDir z_root))
220+ then do
221+ tell "getDataFileName :: FilePath -> IO FilePath\n"
222+ tell "getDataFileName name = do\n"
223+ tell " dir <- getDataDir\n"
224+ tell " return (dir `joinFileName` name)\n"
225+ return ()
226+ else do
227+ return ()
228 tell "\n"
229 let
230 z_var0_function_defs = do
231@@ -130,6 +182,7 @@ render z_root = execWriter $ do
232 tell "\n"
233 if (zRelocatable z_root)
234 then do
235+ tell "\n"
236 tell "\n"
237 tell "getPrefixDirReloc :: FilePath -> IO FilePath\n"
238 tell "getPrefixDirReloc dirRel = do\n"
239@@ -139,31 +192,37 @@ render z_root = execWriter $ do
240 tell (zBindir z_root)
241 tell ") `joinFileName` dirRel)\n"
242 tell "\n"
243+ tell "getBinDir :: IO FilePath\n"
244 tell "getBinDir = catchIO (getEnv \""
245 tell (zManglePkgName z_root (zPackageName z_root))
246 tell "_bindir\") (\\_ -> getPrefixDirReloc $ "
247 tell (zBindir z_root)
248 tell ")\n"
249+ tell "getLibDir :: IO FilePath\n"
250 tell "getLibDir = catchIO (getEnv \""
251 tell (zManglePkgName z_root (zPackageName z_root))
252 tell "_libdir\") (\\_ -> getPrefixDirReloc $ "
253 tell (zLibdir z_root)
254 tell ")\n"
255+ tell "getDynLibDir :: IO FilePath\n"
256 tell "getDynLibDir = catchIO (getEnv \""
257 tell (zManglePkgName z_root (zPackageName z_root))
258 tell "_dynlibdir\") (\\_ -> getPrefixDirReloc $ "
259 tell (zDynlibdir z_root)
260 tell ")\n"
261+ tell "getDataDir :: IO FilePath\n"
262 tell "getDataDir = catchIO (getEnv \""
263 tell (zManglePkgName z_root (zPackageName z_root))
264 tell "_datadir\") (\\_ -> getPrefixDirReloc $ "
265 tell (zDatadir z_root)
266 tell ")\n"
267+ tell "getLibexecDir :: IO FilePath\n"
268 tell "getLibexecDir = catchIO (getEnv \""
269 tell (zManglePkgName z_root (zPackageName z_root))
270 tell "_libexecdir\") (\\_ -> getPrefixDirReloc $ "
271 tell (zLibexecdir z_root)
272 tell ")\n"
273+ tell "getSysconfDir :: IO FilePath\n"
274 tell "getSysconfDir = catchIO (getEnv \""
275 tell (zManglePkgName z_root (zPackageName z_root))
276 tell "_sysconfdir\") (\\_ -> getPrefixDirReloc $ "
277@@ -177,72 +236,119 @@ render z_root = execWriter $ do
278 if (zAbsolute z_root)
279 then do
280 tell "\n"
281- tell "bindir, libdir, dynlibdir, datadir, libexecdir, sysconfdir :: FilePath\n"
282+ tell "bindir :: FilePath\n"
283 tell "bindir = "
284 tell (zBindir z_root)
285 tell "\n"
286- tell "libdir = "
287- tell (zLibdir z_root)
288- tell "\n"
289- tell "dynlibdir = "
290- tell (zDynlibdir z_root)
291+ tell "getBinDir :: IO FilePath\n"
292+ tell "getBinDir = catchIO (getEnv \""
293+ tell (zManglePkgName z_root (zPackageName z_root))
294+ tell "_bindir\") (\\_ -> return bindir)\n"
295 tell "\n"
296- tell "datadir = "
297- tell (zDatadir z_root)
298+ if (zShouldEmitLibDir z_root)
299+ then do
300+ tell "libdir :: FilePath\n"
301+ tell "libdir = "
302+ tell (zLibdir z_root)
303+ tell "\n"
304+ tell "getLibDir :: IO FilePath\n"
305+ tell "getLibDir = catchIO (getEnv \""
306+ tell (zManglePkgName z_root (zPackageName z_root))
307+ tell "_libdir\") (\\_ -> return libdir)\n"
308+ return ()
309+ else do
310+ return ()
311 tell "\n"
312- tell "libexecdir = "
313- tell (zLibexecdir z_root)
314+ if (zShouldEmitDynLibDir z_root)
315+ then do
316+ tell "dynlibdir :: FilePath\n"
317+ tell "dynlibdir = "
318+ tell (zDynlibdir z_root)
319+ tell "\n"
320+ tell "getDynLibDir :: IO FilePath\n"
321+ tell "getDynLibDir = catchIO (getEnv \""
322+ tell (zManglePkgName z_root (zPackageName z_root))
323+ tell "_dynlibdir\") (\\_ -> return dynlibdir)\n"
324+ return ()
325+ else do
326+ return ()
327 tell "\n"
328- tell "sysconfdir = "
329- tell (zSysconfdir z_root)
330+ if (zShouldEmitDataDir z_root)
331+ then do
332+ tell "datadir :: FilePath\n"
333+ tell "datadir = "
334+ tell (zDatadir z_root)
335+ tell "\n"
336+ tell "getDataDir :: IO FilePath\n"
337+ tell "getDataDir = catchIO (getEnv \""
338+ tell (zManglePkgName z_root (zPackageName z_root))
339+ tell "_datadir\") (\\_ -> return datadir)\n"
340+ return ()
341+ else do
342+ return ()
343 tell "\n"
344+ if (zShouldEmitLibexecDir z_root)
345+ then do
346+ tell "libexecdir :: FilePath\n"
347+ tell "libexecdir = "
348+ tell (zLibexecdir z_root)
349+ tell "\n"
350+ tell "getLibexecDir :: IO FilePath\n"
351+ tell "getLibexecDir = catchIO (getEnv \""
352+ tell (zManglePkgName z_root (zPackageName z_root))
353+ tell "_libexecdir\") (\\_ -> return libexecdir)\n"
354+ return ()
355+ else do
356+ return ()
357 tell "\n"
358- tell "getBinDir = catchIO (getEnv \""
359- tell (zManglePkgName z_root (zPackageName z_root))
360- tell "_bindir\") (\\_ -> return bindir)\n"
361- tell "getLibDir = catchIO (getEnv \""
362- tell (zManglePkgName z_root (zPackageName z_root))
363- tell "_libdir\") (\\_ -> return libdir)\n"
364- tell "getDynLibDir = catchIO (getEnv \""
365- tell (zManglePkgName z_root (zPackageName z_root))
366- tell "_dynlibdir\") (\\_ -> return dynlibdir)\n"
367- tell "getDataDir = catchIO (getEnv \""
368- tell (zManglePkgName z_root (zPackageName z_root))
369- tell "_datadir\") (\\_ -> return datadir)\n"
370- tell "getLibexecDir = catchIO (getEnv \""
371- tell (zManglePkgName z_root (zPackageName z_root))
372- tell "_libexecdir\") (\\_ -> return libexecdir)\n"
373- tell "getSysconfDir = catchIO (getEnv \""
374- tell (zManglePkgName z_root (zPackageName z_root))
375- tell "_sysconfdir\") (\\_ -> return sysconfdir)\n"
376+ if (zShouldEmitSysconfDir z_root)
377+ then do
378+ tell "sysconfdir :: FilePath\n"
379+ tell "sysconfdir = "
380+ tell (zSysconfdir z_root)
381+ tell "\n"
382+ tell "getSysconfDir :: IO FilePath\n"
383+ tell "getSysconfDir = catchIO (getEnv \""
384+ tell (zManglePkgName z_root (zPackageName z_root))
385+ tell "_sysconfdir\") (\\_ -> return sysconfdir)\n"
386+ return ()
387+ else do
388+ return ()
389 tell "\n"
390 return ()
391 else do
392 if (zIsWindows z_root)
393 then do
394+ tell "\n"
395 tell "\n"
396 tell "prefix :: FilePath\n"
397 tell "prefix = "
398 tell (zPrefix z_root)
399 tell "\n"
400 tell "\n"
401+ tell "getBinDir :: IO FilePath\n"
402 tell "getBinDir = getPrefixDirRel $ "
403 tell (zBindir z_root)
404 tell "\n"
405+ tell "getLibDir :: IO FilePath\n"
406 tell "getLibDir = "
407 tell (zLibdir z_root)
408 tell "\n"
409+ tell "getDynLibDir :: IO FilePath\n"
410 tell "getDynLibDir = "
411 tell (zDynlibdir z_root)
412 tell "\n"
413+ tell "getDataDir :: IO FilePath\n"
414 tell "getDataDir = catchIO (getEnv \""
415 tell (zManglePkgName z_root (zPackageName z_root))
416 tell "_datadir\") (\\_ -> "
417 tell (zDatadir z_root)
418 tell ")\n"
419+ tell "getLibexecDir :: IO FilePath\n"
420 tell "getLibexecDir = "
421 tell (zLibexecdir z_root)
422 tell "\n"
423+ tell "getSysconfDir :: IO FilePath\n"
424 tell "getSysconfDir = "
425 tell (zSysconfdir z_root)
426 tell "\n"
427diffcabal-dev-scripts/src/GenPathsModule.hs b/cabal-dev-scripts/src/GenPathsModule.hs
428index e4b930635..9b978f284 100644
429--- a/libraries/Cabal/cabal-dev-scripts/src/GenPathsModule.hs
430+++ b/libraries/Cabal/cabal-dev-scripts/src/GenPathsModule.hs
431@@ -41,6 +41,16 @@ $(capture "decls" [d|
432 , zLibexecdir :: FilePath
433 , zSysconfdir :: FilePath
434
435+ , zShouldEmitLibDir :: Bool
436+ , zShouldEmitDynLibDir :: Bool
437+ , zShouldEmitLibexecDir :: Bool
438+ , zShouldEmitDataDir :: Bool
439+ , zShouldEmitSysconfDir :: Bool
440+
441+ , zShouldEmitWarning :: Bool
442+ , zWarning :: String
443+
444+ , zOr :: Bool -> Bool -> Bool
445 , zNot :: Bool -> Bool
446 , zManglePkgName :: PackageName -> String
447 }
448difftemplates/Paths_pkg.template.hs b/templates/Paths_pkg.template.hs
449index 6bc6b7875..aa90a9382 100644
450--- a/libraries/Cabal/templates/Paths_pkg.template.hs
451+++ b/libraries/Cabal/templates/Paths_pkg.template.hs
452@@ -9,10 +9,31 @@
453 {% endif %}
454 {-# OPTIONS_GHC -fno-warn-missing-import-lists #-}
455 {-# OPTIONS_GHC -w #-}
456-module Paths_{{ manglePkgName packageName }} (
457+module Paths_{{ manglePkgName packageName }}
458+ {% if shouldEmitWarning %}{-# WARNING {{ warning }} #-}{% endif %}
459+ (
460 version,
461- getBinDir, getLibDir, getDynLibDir, getDataDir, getLibexecDir,
462- getDataFileName, getSysconfDir
463+ getBinDir,
464+{# We only care about the absolute case for our emit logic, since only in this
465+ case references are incurred. We are not going to hit isWindows and relocatable
466+ has no absolute references to begin with.
467+#}
468+{% if or (not absolute) shouldEmitLibDir %}
469+ getLibDir,
470+{% endif %}
471+{% if or (not absolute) shouldEmitDynLibDir %}
472+ getDynLibDir,
473+{% endif %}
474+{% if or (not absolute) shouldEmitLibexecDir %}
475+ getLibexecDir,
476+{% endif %}
477+{% if or (not absolute) shouldEmitDataDir %}
478+ getDataFileName,
479+ getDataDir,
480+{% endif %}
481+{% if or (not absolute) shouldEmitSysconfDir %}
482+ getSysconfDir
483+{% endif %}
484 ) where
485
486 {% if not absolute %}
487@@ -51,12 +72,12 @@ catchIO = Exception.catch
488 version :: Version
489 version = Version {{ versionDigits }} []
490
491+{% if or (not absolute) shouldEmitDataDir %}
492 getDataFileName :: FilePath -> IO FilePath
493 getDataFileName name = do
494 dir <- getDataDir
495 return (dir `joinFileName` name)
496-
497-getBinDir, getLibDir, getDynLibDir, getDataDir, getLibexecDir, getSysconfDir :: IO FilePath
498+{% endif %}
499
500 {% defblock function_defs %}
501 minusFileName :: FilePath -> String -> FilePath
502@@ -85,48 +106,93 @@ splitFileName p = (reverse (path2++drive), reverse fname)
503
504 {% if relocatable %}
505
506+{# Relocatable can not incur any absolute references, so we can ignore it.
507+ Additionally, --enable-relocatable is virtually useless in Nix builds
508+#}
509+
510 getPrefixDirReloc :: FilePath -> IO FilePath
511 getPrefixDirReloc dirRel = do
512 exePath <- getExecutablePath
513 let (dir,_) = splitFileName exePath
514 return ((dir `minusFileName` {{ bindir }}) `joinFileName` dirRel)
515
516+getBinDir :: IO FilePath
517 getBinDir = catchIO (getEnv "{{ manglePkgName packageName }}_bindir") (\_ -> getPrefixDirReloc $ {{ bindir }})
518+getLibDir :: IO FilePath
519 getLibDir = catchIO (getEnv "{{ manglePkgName packageName }}_libdir") (\_ -> getPrefixDirReloc $ {{ libdir }})
520+getDynLibDir :: IO FilePath
521 getDynLibDir = catchIO (getEnv "{{ manglePkgName packageName }}_dynlibdir") (\_ -> getPrefixDirReloc $ {{ dynlibdir }})
522+getDataDir :: IO FilePath
523 getDataDir = catchIO (getEnv "{{ manglePkgName packageName }}_datadir") (\_ -> getPrefixDirReloc $ {{ datadir }})
524+getLibexecDir :: IO FilePath
525 getLibexecDir = catchIO (getEnv "{{ manglePkgName packageName }}_libexecdir") (\_ -> getPrefixDirReloc $ {{ libexecdir }})
526+getSysconfDir :: IO FilePath
527 getSysconfDir = catchIO (getEnv "{{ manglePkgName packageName }}_sysconfdir") (\_ -> getPrefixDirReloc $ {{ sysconfdir }})
528
529 {% useblock function_defs %}
530
531 {% elif absolute %}
532
533-bindir, libdir, dynlibdir, datadir, libexecdir, sysconfdir :: FilePath
534+bindir :: FilePath
535 bindir = {{ bindir }}
536-libdir = {{ libdir }}
537-dynlibdir = {{ dynlibdir }}
538-datadir = {{ datadir }}
539-libexecdir = {{ libexecdir }}
540-sysconfdir = {{ sysconfdir }}
541-
542+getBinDir :: IO FilePath
543 getBinDir = catchIO (getEnv "{{ manglePkgName packageName }}_bindir") (\_ -> return bindir)
544+
545+{% if shouldEmitLibDir %}
546+libdir :: FilePath
547+libdir = {{ libdir }}
548+getLibDir :: IO FilePath
549 getLibDir = catchIO (getEnv "{{ manglePkgName packageName }}_libdir") (\_ -> return libdir)
550+{% endif %}
551+
552+{% if shouldEmitDynLibDir %}
553+dynlibdir :: FilePath
554+dynlibdir = {{ dynlibdir }}
555+getDynLibDir :: IO FilePath
556 getDynLibDir = catchIO (getEnv "{{ manglePkgName packageName }}_dynlibdir") (\_ -> return dynlibdir)
557+{% endif %}
558+
559+{% if shouldEmitDataDir %}
560+datadir :: FilePath
561+datadir = {{ datadir }}
562+getDataDir :: IO FilePath
563 getDataDir = catchIO (getEnv "{{ manglePkgName packageName }}_datadir") (\_ -> return datadir)
564+{% endif %}
565+
566+{% if shouldEmitLibexecDir %}
567+libexecdir :: FilePath
568+libexecdir = {{ libexecdir }}
569+getLibexecDir :: IO FilePath
570 getLibexecDir = catchIO (getEnv "{{ manglePkgName packageName }}_libexecdir") (\_ -> return libexecdir)
571+{% endif %}
572+
573+{% if shouldEmitSysconfDir %}
574+sysconfdir :: FilePath
575+sysconfdir = {{ sysconfdir }}
576+getSysconfDir :: IO FilePath
577 getSysconfDir = catchIO (getEnv "{{ manglePkgName packageName }}_sysconfdir") (\_ -> return sysconfdir)
578+{% endif %}
579
580 {% elif isWindows %}
581
582+{# We are only trying to fix the problem for aarch64-darwin with this patch,
583+ so let's ignore Windows which we can reach via pkgsCross, for example.
584+#}
585+
586 prefix :: FilePath
587 prefix = {{ prefix }}
588
589+getBinDir :: IO FilePath
590 getBinDir = getPrefixDirRel $ {{ bindir }}
591+getLibDir :: IO FilePath
592 getLibDir = {{ libdir }}
593+getDynLibDir :: IO FilePath
594 getDynLibDir = {{ dynlibdir }}
595+getDataDir :: IO FilePath
596 getDataDir = catchIO (getEnv "{{ manglePkgName packageName }}_datadir") (\_ -> {{ datadir }})
597+getLibexecDir :: IO FilePath
598 getLibexecDir = {{ libexecdir }}
599+getSysconfDir :: IO FilePath
600 getSysconfDir = {{ sysconfdir }}
601
602 getPrefixDirRel :: FilePath -> IO FilePath