aboutsummaryrefslogtreecommitdiff
path: root/lib/Distribution/Helper.hs
blob: 4696590a02ae7675dc7efe99dc70078d31520ada (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
-- cabal-helper: Simple interface to Cabal's configuration state
-- Copyright (C) 2015-2019  Daniel Gröber <cabal-helper@dxld.at>
--
-- SPDX-License-Identifier: Apache-2.0
--
-- Licensed under the Apache License, Version 2.0 (the "License");
-- you may not use this file except in compliance with the License.
-- You may obtain a copy of the License at
--
--     http://www.apache.org/licenses/LICENSE-2.0

{-# LANGUAGE RecordWildCards, FlexibleContexts, ConstraintKinds,
  GeneralizedNewtypeDeriving, DeriveDataTypeable, DeriveGeneric, DeriveFunctor,
  StandaloneDeriving, NamedFieldPuns, OverloadedStrings, ViewPatterns,
  TupleSections, TypeFamilies, DataKinds, GADTs, ScopedTypeVariables,
  ImplicitParams, RankNTypes, MultiWayIf #-}

{-# OPTIONS_GHC -fno-warn-name-shadowing #-}

{-|
Module      : Distribution.Helper
License     : Apache-2.0
Maintainer  : cabal-helper@dxld.at
Portability : POSIX
-}

module Distribution.Helper (
  -- * Type Variable Naming Conventions
  -- $type-conventions

  -- * Running Queries
    Query
  , runQuery

  -- * Queries against Cabal\'s on disk state

  -- ** Project queries
  , compilerVersion
  , projectPackages

  -- ** 'Package' queries
  , Package -- abstract
  , pPackageName
  , pSourceDir
  , pUnits

  -- ** 'Unit' queries
  , Unit -- abstract
  , uComponentName
  , UnitId -- abstract
  , UnitInfo(..)
  , unitInfo

  -- ** Convenience Queries
  , allUnits

  -- * Query environment
  , QueryEnv
  , QueryEnvI -- abstract
  , mkQueryEnv
  , qeReadProcess
  , qeCallProcess
  , qePrograms
  , qeProjLoc
  , qeDistDir

  -- * GADTs
  , ProjType(..)
  , CabalProjType(..)
  , ProjLoc(..)
  , DistDir(..)
  , SProjType(..)
  , demoteSProjType
  , projTypeOfDistDir
  , projTypeOfProjLoc
  , SCabalProjType(..)
  , Ex(..)

  -- * Programs
  , Programs(..)
  , defaultPrograms
  , EnvOverride(..)

  -- * Query result types
  , ChComponentInfo(..)
  , ChComponentName(..)
  , ChLibraryName(..)
  , ChModuleName(..)
  , ChPkgDb(..)
  , ChEntrypoint(..)

  -- * General information
  , Distribution.Helper.buildPlatform

  -- * Legacy v1-build helpers
  , Distribution.Helper.getSandboxPkgDb

  -- * Build actions
  , prepare
  , writeAutogenFiles
  , buildProject
  , buildUnits
  ) where

import Cabal.Plan hiding (Unit, UnitId, uDistDir)
import Control.Applicative
import Control.Monad
import Control.Monad.Trans.Maybe
import Control.Monad.IO.Class
import Control.Exception as E
import qualified Data.ByteString.Char8 as BS8
import qualified Data.ByteString.UTF8 as BSU
import Data.IORef
import Data.List hiding (filter)
import Data.String
import qualified Data.Text as Text
import Data.Maybe
import Data.Either
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Set (Set)
import qualified Data.Set as Set
import qualified Data.Traversable as T
import Data.List.NonEmpty (NonEmpty(..))
import qualified Data.List.NonEmpty as NonEmpty
import Data.Version
import Data.Function
import System.Clock as Clock
import System.IO
import System.Environment
import System.FilePath
import System.Directory
import System.Process
import System.Posix.Types
import System.PosixCompat.Files
import Text.Printf
import Text.Read
import Prelude

import CabalHelper.Compiletime.Compile
import qualified CabalHelper.Compiletime.Program.Stack as Stack
import qualified CabalHelper.Compiletime.Program.GHC as GHC
import qualified CabalHelper.Compiletime.Program.CabalInstall as CabalInstall
import CabalHelper.Compiletime.Cabal
import CabalHelper.Compiletime.CompPrograms
import CabalHelper.Compiletime.Log
import CabalHelper.Compiletime.Process
import CabalHelper.Compiletime.Sandbox
import CabalHelper.Compiletime.Types
import CabalHelper.Compiletime.Types.Cabal
import CabalHelper.Compiletime.Types.RelativePath
import CabalHelper.Shared.InterfaceTypes
import CabalHelper.Shared.Common
import CabalHelper.Runtime.HelperMain (helper_main)

import CabalHelper.Compiletime.Compat.Version

import Distribution.System (buildPlatform)
import Distribution.Text (display)

-- $type-conventions
-- Throughout the API we use the following conventions for type variables:
--
-- * @pt@ stands for "project type", when instantiated it is always of kind
--   'ProjType'.
--
-- * @c@ stands for "cache". It is used internally to make the cache
--   inaccessible for some parts of the implementation. Users of the API may
--   completely ignore this parameter. See the internal 'qeCacheRef' field
--   accessor of 'QueryEnv' for details.


-- | A query against a package's Cabal configuration. Use 'runQuery' to
-- execute it.
newtype Query pt a = Query
    { unQuery :: QueryEnv pt -> IO a
    -- ^ @runQuery env query@. Run a 'Query' under a given 'QueryEnv.
    }

instance Functor (Query pt) where
    fmap = liftM

instance Applicative (Query pt) where
    (<*>) = ap
    pure = return

instance Monad (Query pt) where
    (Query ma) >>= amb = Query $ \qe -> ma qe >>= \a -> unQuery (amb a) qe
    return a = Query $ const $ return a

runQuery :: Query pt a -> QueryEnv pt -> IO a
runQuery (Query action) qe = do
  ckr <- newIORef $ CacheKeyCache Nothing
  let qe' = qe { qeCacheKeys = ckr }
  conf_progs <- getConfProgs qe'
  action qe' { qePrograms = conf_progs }

-- | @mkQueryEnv projdir distdir@. Smart constructor for 'QueryEnv'.
-- Sets fields 'qeProjLoc' and 'qeDistDir' to @projdir@ and @distdir@
-- respectively and provides sensible defaults for the other fields.
mkQueryEnv
    :: ProjLoc pt
    -- ^ Location of the project.
    -> DistDir pt
    -- ^ Path to the @dist/@ or @dist-newstyle/@ directory, called
    -- /builddir/ in Cabal terminology.
    -> IO (QueryEnv pt)
mkQueryEnv projloc distdir = do
  cr <- newIORef $ QueryCache Nothing Nothing Nothing Map.empty
  return $ QueryEnv
    { qeReadProcess = \stdin mcwd env exe args -> do
        withVerbosity $ readProcessStderr mcwd env exe args ""
    , qeCallProcess  = \mcwd env exe args ->
        withVerbosity $ callProcessStderr mcwd env exe args
    , qePrograms     = defaultPrograms
    , qeProjLoc      = projloc
    , qeDistDir      = distdir
    , qeCacheRef     = cr
    , qeCacheKeys    = error "mkQuery: qeCacheKeys is uninitialized!"
    }

-- | Construct paths to project configuration files given where the project is.
projConf :: ProjLoc pt -> IO (ProjConf pt)
projConf (ProjLocV1Dir pkgdir) =
  ProjConfV1 <$> (complainIfNoCabalFile pkgdir =<< findCabalFile pkgdir)
projConf (ProjLocV1CabalFile cabal_file _) = return $
  ProjConfV1 cabal_file
projConf (ProjLocV2Dir projdir_path) =
  projConf $ ProjLocV2File (projdir_path </> "cabal.project") projdir_path
projConf (ProjLocV2File proj_file _) = return $
  ProjConfV2
    { pcV2CabalProjFile       = proj_file
    , pcV2CabalProjLocalFile  = proj_file <.> "local"
    , pcV2CabalProjFreezeFile = proj_file <.> "freeze"
    }
projConf (ProjLocStackYaml stack_yaml) = return $
  ProjConfStack
    { pcStackYaml = stack_yaml }

-- | Get the current modification-time for each file involved in configuring a
-- project. Optional files in 'ProjConf' are handled by not including them in
-- the result list in 'ProjConfModTimes' if they don\'t exist. This causes the
-- lists to be different if the files end up existing later, which is all we
-- need for cache invalidation.
getProjConfModTime :: ProjConf pt -> IO ProjConfModTimes
getProjConfModTime ProjConfV1{pcV1CabalFile} =
  fmap ProjConfModTimes $ mapM getFileModTime
    [ pcV1CabalFile
    ]
getProjConfModTime ProjConfV2{..} = do
  fmap (ProjConfModTimes . catMaybes) $
    mapM (traverse getFileModTime <=< mightExist)
      [ pcV2CabalProjFile
      , pcV2CabalProjLocalFile
      , pcV2CabalProjFreezeFile
      ]
getProjConfModTime ProjConfStack{..} =
  fmap ProjConfModTimes $ mapM getFileModTime
    [ pcStackYaml
    ]

getUnitModTimes :: Unit pt -> IO UnitModTimes
getUnitModTimes
  Unit
    { uDistDir=DistDirLib distdirv1
    , uPackage=Package
      { pCabalFile=CabalFile cabal_file_path
      , pSourceDir
      }
    , uImpl
    }
  = do
    umtPkgYaml <-
        case uImpl of
          UnitImplStack{}
            -> traverse getFileModTime =<< mightExist package_yaml_path
          _ -> return Nothing
    umtCabalFile <- getFileModTime cabal_file_path
    umtSetupConfig <- (traverse getFileModTime <=< mightExist) setup_config_path
    return UnitModTimes {..}
  where
    package_yaml_path = pSourceDir  </> "package.yaml"
    setup_config_path = distdirv1 </> "setup-config"

-- | Get a random unit from the project. Sometimes we need to get info we
-- can only get after configuring _any_ unit but we do assume that this
-- info is uniform across units.
someUnit :: ProjInfo pt -> Unit pt
someUnit proj_info =
    NonEmpty.head $ pUnits $
    NonEmpty.head $ piPackages proj_info

-- | The version of GHC the project is configured to use for compilation.
compilerVersion :: Query pt (String, Version)
compilerVersion = Query $ \qe ->
  getProjInfo qe >>= \proj_info ->
    let unit = someUnit proj_info in
    --  ^ ASSUMPTION: Here we assume the compiler version is uniform across all
    --  units so we just pick any one.
    case piImpl proj_info of
      ProjInfoV1 {} -> uiCompilerId <$> getUnitInfo qe unit
      ProjInfoV2 { piV2CompilerId } -> return piV2CompilerId
      ProjInfoStack {} -> uiCompilerId <$> getUnitInfo qe unit

-- | All local packages currently active in a project\'s build plan.
projectPackages :: Query pt (NonEmpty (Package pt))
projectPackages = Query $ \qe -> piPackages <$> getProjInfo qe

-- | Get the 'UnitInfo' for a given 'Unit'. To get a 'Unit' see 'projectUnits'.
unitInfo :: Unit pt -> Query pt UnitInfo
unitInfo u = Query $ \qe -> getUnitInfo qe u

-- | Get information on all units in a project.
allUnits :: (UnitInfo -> a) -> Query pt (NonEmpty a)
allUnits f =
  fmap f <$> (T.mapM unitInfo =<< join . fmap pUnits <$> projectPackages)


data Cached c ckc k v = Cached
  { cGet      :: !(c -> Maybe (k, v))
  , cSet      :: !(c -> (k, v) -> c)

  , cGetKey   :: !(ckc -> Maybe k)
  , cSetKey   :: !(ckc -> k -> ckc)

  , cCheckKey :: !(IO k)
  , cKeyValid :: !(k -> k -> Bool)
  -- ^ @cKeyValid old new@ should return 'True' if 'old' is still valid
  -- relative to the value of 'new'.

  , cRegen    :: !(k -> IO v)
  }

-- | Simple caching scheme. Invalidation is based on equality of a "cache
-- key" the current value of which can be got with the IO action 'cGetKey'.
--
-- Note that we only check the actual value of the cache key once per
-- 'runQuery' call by saving the cache key in an ephemeral map.
cached :: QueryEnvI (QueryCacheI a b c d) pt
       -> Cached (QueryCacheI a b c d pt) (CacheKeyCache pt) k v
       -> IO v
cached qe Cached{..} = do
  c <- readIORef (qeCacheRef qe)
  (c', v) <- checkUpdate c (cGet c)
  writeIORef (qeCacheRef qe) c'
  return v
 where
  checkUpdate c m = do
    ckc <- readIORef (qeCacheKeys qe)
    let regen ck = (ck,) <$> cRegen ck
    n <- case m of
      Nothing -> do
        ck <- cCheckKey
        writeIORef (qeCacheKeys qe) (cSetKey ckc ck)
        regen ck
      Just old@(old_ck, old_v) -> do
        ck <- case cGetKey ckc of
          Just cck ->
            return cck -- TODO: skip valid check below in this case
          Nothing -> do
            ck <- cCheckKey
            writeIORef (qeCacheKeys qe) (cSetKey ckc ck)
            return ck
        if
          | cKeyValid old_ck ck -> return old
          | otherwise -> regen ck
    return (cSet c n, snd n)

getProjConfAndModTime :: QueryEnvI c pt -> IO (ProjConf pt, ProjConfModTimes)
getProjConfAndModTime qe = do
  proj_conf <- projConf (qeProjLoc qe)
  mtime <- getProjConfModTime proj_conf
  return (proj_conf, mtime)

getPreInfo :: QueryEnvI (QCPreInfo a b c) pt -> IO (PreInfo pt)
getPreInfo qe =
  cached qe $ Cached
    { cGet = qcPreInfo
    , cSet = \a b -> a { qcPreInfo = Just b }
    , cGetKey = ckcProjConf
    , cSetKey = \a b -> a { ckcProjConf = Just b }
    , cCheckKey = getProjConfAndModTime qe
    , cKeyValid = (==) `on` snd
    , cRegen = \_k -> readPreInfo qe
    }

readPreInfo :: QueryEnvI c pt -> IO (PreInfo pt)
readPreInfo qe = do
  case projTypeOfQueryEnv qe of
    SStack -> do
      piStackProjPaths <- Stack.projPaths qe
      return PreInfoStack
        { piStackProjPaths
        }
    (SCabal _) ->
      return PreInfoCabal

getProjInfo :: QueryEnv pt -> IO (ProjInfo pt)
getProjInfo qe = do
  pre_info <- getPreInfo qe
  cached qe $ Cached
    { cGet = qcProjInfo
    , cSet = \c n@(_, proj_info) ->
        let active_units = NonEmpty.toList $ join $
              fmap pUnits $ piPackages proj_info in
        c { qcProjInfo = Just n
          , qcUnitInfos =
               discardInactiveUnitInfos active_units (qcUnitInfos c)
          }
    , cGetKey = ckcProjConf
    , cSetKey = \a b -> a { ckcProjConf = Just b }
    , cCheckKey = getProjConfAndModTime qe
    , cKeyValid = (==) `on` snd
    , cRegen = \(proj_conf, mtime) -> do
        shallowReconfigureProject qe
        readProjInfo qe proj_conf mtime pre_info
    }


-- | Get the cabal version we need to build for this project.
getCabalLibVersion :: QueryEnv pt -> Reconfigured pt -> ProjInfo pt -> IO CabalVersion
getCabalLibVersion _ _ ProjInfo{piImpl=ProjInfoV1 {piV1CabalVersion}} =
  return piV1CabalVersion
getCabalLibVersion qe reconf proj_info = do
  unit <- case reconf of
    AlreadyReconfigured unit ->
        return unit
    Haven'tReconfigured -> do
        let unit = someUnit proj_info
        reconfigureUnit qe unit
        return unit
  let DistDirLib distdir = uDistDir $ unit
  hdr <- readSetupConfigHeader $ distdir </> "setup-config"
  let ("Cabal", cabalVer) = uhSetupId hdr
  return $ CabalVersion cabalVer


getUnitInfo :: QueryEnv pt -> Unit pt -> IO UnitInfo
getUnitInfo qe@QueryEnv{..} unit@Unit{uDistDir} = do
  pre_info <- getPreInfo qe
  proj_info <- getProjInfo qe
  cached qe $ Cached
    { cGet = \c -> do
        ui <- Map.lookup uDistDir (qcUnitInfos c)
        return (uiModTimes ui, ui)
    , cSet = \c (_mtimes, unit_info) -> c { qcUnitInfos =
        Map.insert uDistDir unit_info (qcUnitInfos c) }

    , cGetKey = const Nothing
    , cSetKey = const
    , cCheckKey = getUnitModTimes unit
    , cKeyValid = (==)

    , cRegen = \mtimes -> do
        reconf <- reconfigureUnit qe unit
        cabal_ver <- getCabalLibVersion qe reconf proj_info
        helper <- getHelper qe pre_info proj_info cabal_ver
        readUnitInfo helper unit mtimes
    }

-- | Restrict 'UnitInfo' cache to units that are still active
discardInactiveUnitInfos
    :: [Unit pt]
    -> Map DistDirLib UnitInfo
    -> Map DistDirLib UnitInfo
discardInactiveUnitInfos active_units uis0 =
    restrictKeysMap uis0 $ Set.fromList $ map uDistDir active_units
  where
    restrictKeysMap :: Ord k => Map k a -> Set k -> Map k a
    restrictKeysMap m s = Map.filterWithKey (\k _ -> Set.member k s) m


-- | Regenerate project-level information by calling the appropriate build
-- system.
shallowReconfigureProject :: QueryEnvI (QCProgs a b) pt -> IO ()
shallowReconfigureProject QueryEnv
  { qeProjLoc = ProjLocStackYaml _stack_yaml, .. } = do
    -- Stack's dry-run only generates the cabal file from package.yaml (or
    -- well that's the only thing we would care about). reconfigureUnit
    -- will take care of this though and we don't need the cabal files
    -- before the Unit stage anyways.
    return ()
shallowReconfigureProject qe = do
  buildProjectTarget qe Nothing DryRun

data Reconfigured pt = AlreadyReconfigured (Unit pt) | Haven'tReconfigured
reconfigureUnit :: QueryEnvI c pt -> Unit pt -> IO (Reconfigured pt)
reconfigureUnit qe u = do
  buildProjectTarget qe (Just u) OnlyCfg
  return (AlreadyReconfigured u)

buildUnits :: [Unit pt] -> Query pt ()
buildUnits units = Query $ \qe -> do
  conf_progs <- getConfProgs qe
  forM_ units $ \u ->
    buildProjectTarget qe { qePrograms = conf_progs } (Just u) DoBuild

buildProject :: Query pt ()
buildProject = Query $ \qe -> do
  conf_progs <- getConfProgs qe
  buildProjectTarget qe { qePrograms = conf_progs } Nothing DoBuild

data BuildStage = DryRun | OnlyCfg | DoBuild

buildProjectTarget
    :: QueryEnvI c pt -> Maybe (Unit pt) -> BuildStage -> IO ()
buildProjectTarget qe mu stage = do
  -- Stack and cabal just happen to have the same stage options, totally by
  -- accident :)
  stage_opts :: [String] <- return $ case stage of
    DryRun  -> ["--dry-run"]
    OnlyCfg -> ["--only-configure"]
    DoBuild -> []
  -- TODO: version check for cabal's --only-configure
  case qe of
    QueryEnv { qeDistDir = DistDirCabal cpt distdir, qeProjLoc } -> do
      let projdir = plCabalProjectDir qeProjLoc
      cmd <- return $ case stage of
        DryRun | SCV1 <- cpt ->
          CabalInstall.CIConfigure
          -- TODO: in v1 we configure twice because we do configure for
          -- DryRun and OnlyCfg.
        OnlyCfg ->
          CabalInstall.CIConfigure
        _ ->
          CabalInstall.CIBuild
      CabalInstall.callCabalInstallCmd qe (Just projdir) cmd $
        case cpt of
          SCV1 ->
            [ "--builddir="++distdir ]
          SCV2 -> do
            targets <- return $ case mu of
              Nothing -> ["all"]
              Just Unit{uImpl} -> concat
                [ if uiV2OnlyDependencies uImpl
                    then ["--only-dependencies"] else []
                , map snd $ filter ((/= ChSetupHsName) . fst) $ uiV2Components uImpl
                ]
            case qeProjLoc of
              ProjLocV2File {plCabalProjectFile} ->
                [ "--project-file="++plCabalProjectFile
                , "--builddir="++distdir
                ] ++ stage_opts ++ targets
              ProjLocV2Dir {} ->
                [ "--builddir="++distdir
                ] ++ stage_opts ++ targets

    QueryEnv { qeDistDir = DistDirStack mworkdir
             , qeProjLoc = qeProjLoc@ProjLocStackYaml {plStackYaml}
             } -> do
      let projdir = plStackProjectDir qeProjLoc
      let workdir_opts = Stack.workdirArg qe
      case mu of
        Just Unit{uPackage=Package{pSourceDir}} ->
          Stack.callStackCmd qe (Just pSourceDir) $
            workdir_opts ++
            [ "--stack-yaml="++plStackYaml, "build", "."
            ] ++ stage_opts
        Nothing ->
          Stack.callStackCmd qe (Just projdir) $
            workdir_opts ++
            [ "--stack-yaml="++plStackYaml, "build"
            ] ++ stage_opts

getFileModTime :: FilePath -> IO (FilePath, EpochTime)
getFileModTime f = do
  t <- modificationTime <$> getFileStatus f
  return (f, t)

readProjInfo
    :: QueryEnvI c pt -> ProjConf pt -> ProjConfModTimes -> PreInfo pt -> IO (ProjInfo pt)
readProjInfo qe pc pcm _pi = withVerbosity $ do
  let projloc = qeProjLoc qe
  case (qeDistDir qe, pc) of
    (DistDirCabal SCV1 distdir, ProjConfV1{pcV1CabalFile}) -> do
      setup_config_path <- canonicalizePath (distdir </> "setup-config")
      hdr@(UnitHeader (pkg_name_bs, _pkg_ver) ("Cabal", hdrCabalVersion) _)
          <- readSetupConfigHeader setup_config_path
      let
        v3_0_0_0 = makeVersion [3,0,0,0]
        pkg_name
          | hdrCabalVersion >= v3_0_0_0 = BSU.toString pkg_name_bs
          | otherwise = BS8.unpack pkg_name_bs
        pkg = Package
          { pPackageName = pkg_name
          , pSourceDir = plCabalProjectDir projloc
          , pCabalFile = CabalFile pcV1CabalFile
          , pFlags = []
          , pUnits = (:|[]) Unit
            { uUnitId = UnitId pkg_name
            , uPackage = pkg { pUnits = () }
            , uDistDir = DistDirLib distdir
            , uImpl = UnitImplV1
            }
          }
        piImpl = ProjInfoV1
          { piV1SetupHeader = hdr
          , piV1CabalVersion = CabalVersion hdrCabalVersion
          }
      return ProjInfo
        { piProjConfModTimes = pcm
        , piPackages = pkg :| []
        , piImpl
        }

    (DistDirCabal SCV2 distdirv2, _) -> do
      let plan_path = distdirv2 </> "cache" </> "plan.json"
      plan_mtime <- modificationTime <$> getFileStatus plan_path
      plan@PlanJson { pjCabalLibVersion=Ver pjCabalLibVersion
                    , pjCabalVersion
                    , pjCompilerId=PkgId (PkgName compName) (Ver compVer)
                    }
          <- decodePlanJson plan_path
      when (pjCabalVersion < Ver [2,4,1,0]) $
        panicIO $ "plan.json was produced by too-old a version of\
                  \cabal-install. The 'dist-dir' keys will be missing. \
                  \Please upgrade to at least cabal-instal-2.4.1.0"

      Just pkgs <- NonEmpty.nonEmpty <$> CabalInstall.planPackages plan
      return ProjInfo
        { piProjConfModTimes = pcm
        , piPackages = NonEmpty.sortWith pPackageName pkgs
        , piImpl = ProjInfoV2
          { piV2Plan = plan
          , piV2PlanModTime = plan_mtime
          , piV2CompilerId = (Text.unpack compName, makeDataVersion compVer)
          }
        }
    (DistDirStack{}, _) -> do
      Just cabal_files <- NonEmpty.nonEmpty <$> Stack.listPackageCabalFiles qe
      pkgs <- mapM (Stack.getPackage qe) cabal_files
      return ProjInfo
        { piProjConfModTimes = pcm
        , piPackages = NonEmpty.sortWith pPackageName pkgs
        , piImpl = ProjInfoStack
        }

readUnitInfo :: Helper pt -> Unit pt -> UnitModTimes -> IO UnitInfo
readUnitInfo helper u@Unit{uImpl=ui@UnitImplV2{uiV2Components}} umt
    | ChSetupHsName `elem` map fst uiV2Components = do
        let unit' = u {
          uImpl = ui
            { uiV2Components = filter ((/= ChSetupHsName) . fst) uiV2Components
            }
          }
        -- TODO: Add a synthetic UnitInfo for the setup executable. Cabal
        -- doesn't allow building it via a target on the cmdline and it
        -- doesn't really exist as far as setup-config is concerned but
        -- plan.json has the dependency versions for custom-setup so we
        -- should be able to represet that as a UnitInfo.
        readUnitInfo helper unit' umt
readUnitInfo helper unit@Unit {uUnitId=uiUnitId} uiModTimes = do
    res <- runHelper helper unit
           [ "package-id"
           , "compiler-id"
           , "flags"
           , "config-flags"
           , "non-default-config-flags"
           , "component-info"
           ]
    let [ Just (ChResponseVersion        uiPackageId),
          Just (ChResponseVersion        uiCompilerId),
          Just (ChResponseFlags          uiPackageFlags),
          Just (ChResponseFlags          uiConfigFlags),
          Just (ChResponseFlags          uiNonDefaultConfigFlags),
          Just (ChResponseComponentsInfo uiComponents)
          ] = res
    return $ UnitInfo {..}

readHelper
    :: QueryEnvI c pt
    -> FilePath
    -> CabalFile
    -> DistDirLib
    -> [String]
    -> IO [Maybe ChResponse]
readHelper qe exe cabal_file distdir args = do
  out <- invokeHelper qe exe cabal_file distdir args
  let res :: [Maybe ChResponse]
      res = read out
  liftIO $ evaluate res `E.catch` \ex@ErrorCall{} -> do
      md <- lookupEnv' "CABAL_HELPER_DEBUG"
      let msg = "readHelper: exception: '" ++ show ex ++ "'"
      panicIO $ msg ++ case md of
        Nothing -> "\n  for more information set the environment variable CABAL_HELPER_DEBUG and try again"
        Just _ -> "\n  output:\n'"++ out ++"'"

invokeHelper
    :: QueryEnvI c pt
    -> FilePath
    -> CabalFile
    -> DistDirLib
    -> [String]
    -> IO String
invokeHelper
  QueryEnv {..}
  exe
  (CabalFile cabal_file_path)
  (DistDirLib distdir)
  args0
  = do
    let args1 = cabal_file_path : distdir : args0
    evaluate =<< qeReadProcess "" Nothing [] exe args1 `E.catch`
      \(_ :: E.IOException) ->
        panicIO $ concat
          ["invokeHelper", ": ", exe, " "
          , intercalate " " (map show args1)
          , " failed!"
          ]

-- | Make sure the appropriate helper executable for the given project is
-- installed and ready to run queries.
--
-- The idea is you can run this at a convinient time instead of having the
-- helper compilation happen during a time-sensitive user interaction. This
-- will however happen automatically as needed if you don't run it first.
prepare :: Query pt ()
prepare = Query $ \qe -> do
  pre_info <- getPreInfo qe
  proj_info <- getProjInfo qe
  cabal_ver <- getCabalLibVersion qe Haven'tReconfigured proj_info
  void $ getHelper qe pre_info proj_info cabal_ver

-- | Create @cabal_macros.h@, @Paths_\<pkg\>.hs@ and other generated files
-- in the usual place. See 'Distribution.Simple.Build.initialBuildSteps'.
--
-- This is usually only needed on the first load of a unit or after the
-- cabal file changes.
writeAutogenFiles :: Unit pt -> Query pt ()
writeAutogenFiles unit = Query $ \qe -> do
  pre_info <- getPreInfo qe
  proj_info <- getProjInfo qe
  cabal_ver <- getCabalLibVersion qe Haven'tReconfigured proj_info
  helper <- getHelper qe pre_info proj_info cabal_ver
  void $ runHelper helper unit ["write-autogen-files"]

-- | Get the path to the sandbox package-db in a project
getSandboxPkgDb
    :: String
    -- ^ Cabal build platform, i.e. @buildPlatform@
    -> GHC.GhcVersion
    -- ^ GHC version (@cProjectVersion@ is your friend)
    -> FilePath
    -- ^ Path to the project directory, i.e. a directory containing a
    -- @cabal.sandbox.config@ file
    -> IO (Maybe FilePath)
getSandboxPkgDb buildPlat ghcVer projdir =
  CabalHelper.Compiletime.Sandbox.getSandboxPkgDb buildPlat ghcVer projdir

buildPlatform :: String
buildPlatform = display Distribution.System.buildPlatform

lookupEnv' :: String -> IO (Maybe String)
lookupEnv' k = lookup k <$> getEnvironment

withVerbosity :: (Verbose => IO a) -> IO a
withVerbosity act = do
  x <- lookup  "CABAL_HELPER_DEBUG" <$> getEnvironment
  let ?verbose = \level ->
        case x >>= readMaybe of
          Just x | x >= level -> True
          _ -> False
  act

getConfProgs :: QueryEnvI (QCProgs a b) pt -> IO Programs
getConfProgs qe = do
  pre_info <- getPreInfo qe
  cached qe $ Cached
    { cGet = qcConfProgs
    , cSet = \a b -> a { qcConfProgs = Just b }
    , cGetKey = const Nothing
    , cSetKey = const
    , cCheckKey = return (qePrograms qe)
    , cKeyValid = (==)
    , cRegen = \_k -> configurePrograms qe pre_info
    }

-- | Fixup program paths as appropriate for current project-type and bring
-- 'Programs' into scope as an implicit parameter.
configurePrograms :: QueryEnvI c pt -> PreInfo pt -> IO Programs
configurePrograms qe@QueryEnv{..} pre_info = withVerbosity $ do
  patchBuildToolProgs (projTypeOfQueryEnv qe) <=< guessCompProgramPaths $
    case pre_info of
      PreInfoStack projPaths ->
        Stack.patchCompPrograms projPaths qePrograms
      _ -> qePrograms

newtype Helper pt
  = Helper { runHelper :: Unit pt -> [String] -> IO [Maybe ChResponse] }

getHelper :: QueryEnvI c pt -> PreInfo pt -> ProjInfo pt -> CabalVersion -> IO (Helper pt)
getHelper qe@QueryEnv{..} _pre_info _proj_info cabal_ver
  | cabal_ver == bultinCabalVersion = return $ Helper $
      \Unit{ uDistDir=DistDirLib distdir
           , uPackage=Package{pCabalFile=CabalFile cabal_file}
           } args ->
        let pt = dispHelperProjectType (projTypeOfQueryEnv qe) in
        helper_main $ cabal_file : distdir : pt : args
getHelper qe@QueryEnv{..} pre_info proj_info cabal_ver = do
  withVerbosity $ do
    let ?progs = qePrograms
    t0 <- Clock.getTime Monotonic
    eexe <- compileHelper $ mkCompHelperEnv qeProjLoc qeDistDir pre_info proj_info cabal_ver
    t1 <- Clock.getTime Monotonic
    let dt = (/10^9) $ fromInteger $ Clock.toNanoSecs $ Clock.diffTimeSpec t0 t1
        dt :: Float
    vLog $ printf "compileHelper took %.5fs" dt
    case eexe of
      Left rv ->
        panicIO $ "compileHelper': compiling helper failed! exit code "++ show rv
      Right exe ->
        let pt = dispHelperProjectType (projTypeOfQueryEnv qe) in
        return $ Helper $ \Unit{uDistDir, uPackage=Package{pCabalFile}} args ->
          readHelper qe exe pCabalFile uDistDir (pt : args)

dispHelperProjectType :: SProjType pt -> String
dispHelperProjectType (SCabal SCV1) = "v1"
--  ^ v1-build needs a last minute addition of the inplace package-db
-- beyond what lbi has
dispHelperProjectType (SCabal SCV2) = "v2"
dispHelperProjectType SStack        = "v2"
--  ^ stack also embeds all necessary options into lbi like v2

mkCompHelperEnv
    :: Verbose
    => ProjLoc pt
    -> DistDir pt
    -> PreInfo pt
    -> ProjInfo pt
    -> CabalVersion
    -> CompHelperEnv
mkCompHelperEnv
  projloc
  (DistDirCabal SCV1 distdir)
  PreInfoCabal
  ProjInfo {}
  cabal_ver
  = CompHelperEnv
    { cheCabalVer = cabal_ver
    , cheProjDir  = plCabalProjectDir projloc
    , cheProjLocalCacheDir = distdir
    , chePkgDb    = []
    , chePjUnits = Nothing
    , cheDistV2 = Nothing
    }
mkCompHelperEnv
  projloc
  (DistDirCabal SCV2 distdir)
  PreInfoCabal
  ProjInfo{piImpl=ProjInfoV2{piV2Plan=plan}}
  cabal_ver
  = CompHelperEnv {..}
  where
    cheProjDir  = plCabalProjectDir projloc
    cheCabalVer = cabal_ver
    cheProjLocalCacheDir = distdir </> "cache"
    chePkgDb    = []
    chePjUnits  = Just $ pjUnits plan
    cheDistV2   = Just distdir
mkCompHelperEnv
  (ProjLocStackYaml stack_yaml)
  (DistDirStack mworkdir)
  PreInfoStack
    { piStackProjPaths=StackProjPaths
      { sppGlobalPkgDb, sppSnapPkgDb, sppLocalPkgDb }
    }
  ProjInfo {}
  cabal_ver
  = let workdir = fromMaybe ".stack-work" $ unRelativePath <$> mworkdir in
    let projdir = takeDirectory stack_yaml in
    CompHelperEnv
    { cheCabalVer = cabal_ver
    , cheProjDir  = projdir
    , cheProjLocalCacheDir = projdir </> workdir
    , chePkgDb    = [sppGlobalPkgDb, sppSnapPkgDb, sppLocalPkgDb]
    , chePjUnits = Nothing
    , cheDistV2 = Nothing
    }