summaryrefslogtreecommitdiff
path: root/hadrian/src/Hadrian/Oracles/Cabal/Rules.hs
blob: b7f0f93526c9b88655bbb9cf3594bd3438afe7f0 (plain)
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
-----------------------------------------------------------------------------
-- |
-- Module     : Hadrian.Oracles.Cabal.Rules
-- Copyright  : (c) Andrey Mokhov 2014-2018
-- License    : MIT (see the file LICENSE)
-- Maintainer : andrey.mokhov@gmail.com
-- Stability  : experimental
--
-- This module defines Shake rules corresponing to the /Cabal oracle/; see
-- the module "Hadrian.Oracles.Cabal" for various supported queries.
-----------------------------------------------------------------------------
module Hadrian.Oracles.Cabal.Rules where

import Control.Monad
import Data.Maybe
import Development.Shake
import Distribution.Simple.GHC
import Distribution.Simple.Program.Db
import Distribution.Verbosity

import Builder
import Context
import Hadrian.Haskell.Cabal.Parse
import Hadrian.Oracles.Cabal.Type
import Hadrian.Package
import Hadrian.Utilities

-- | These oracle rules are used to cache and track answers to the following
-- queries, which are implemented via the Cabal library:
--
-- 1) 'Hadrian.Oracles.Cabal.readPackageData' that reads Cabal package data.
--
-- 2) 'Hadrian.Oracles.Cabal.readContextData' that reads 'Context'-dependent
--    Cabal package data.
--
-- 3) 'Hadrian.Oracles.Cabal.configurePackageGHC' that configures a package.
cabalOracle :: Rules ()
cabalOracle = do
    void $ addOracleCache $ \(PackageDataKey package) -> do
        let file = pkgCabalFile package
        need [file]
        putLoud $ "| PackageData oracle: parsing " ++ quote file ++ "..."
        parsePackageData package

    void $ addOracleCache $ \(ContextDataKey context@Context {..}) -> do
        putLoud $ "| ContextData oracle: resolving data for "
               ++ quote (pkgName package) ++ " (" ++ show stage
               ++ ", " ++ show way ++ ")..."
        -- Calling 'need' on @setup-config@ triggers 'configurePackage'. Why
        -- this indirection? Going via @setup-config@ allows us to cache the
        -- configuration step, i.e. not to repeat it if it's already been done.
        setupConfig <- pkgSetupConfigFile context
        need [setupConfig]
        resolveContextData context

    void $ addOracleCache $ \(PackageConfigurationKey (pkg, stage)) -> do
        putLoud $ "| PackageConfiguration oracle: configuring "
               ++ quote (pkgName pkg) ++ " (" ++ show stage ++ ")..."
        -- Configure the package with the GHC corresponding to the given stage
        hcPath <- builderPath (Ghc CompileHs stage)
        (compiler, maybePlatform, _pkgdb) <- liftIO $
            configure silent (Just hcPath) Nothing emptyProgramDb
        let platform = fromMaybe (error msg) maybePlatform
            msg      = "PackageConfiguration oracle: cannot detect platform"
        return $ PackageConfiguration (compiler, platform)