aboutsummaryrefslogtreecommitdiff
path: root/src/CabalHelper/Compiletime/Program/GHC.hs
blob: 4486d47fba4f13d877fe7c8526edfa61d02fc2e0 (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
-- cabal-helper: Simple interface to Cabal's configuration state
-- Copyright (C) 2018  Daniel Gröber <cabal-helper@dxld.at>
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-- GNU General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program.  If not, see <http://www.gnu.org/licenses/>.

{-|
Module      : CabalHelper.Compiletime.Program.GHC
Description : GHC program interface
License     : GPL-3
-}

module CabalHelper.Compiletime.Program.GHC where

import Control.Monad
import Control.Monad.Trans.Maybe
import Control.Monad.IO.Class
import Data.Char
import Data.List
import Data.Maybe
import Data.Version
import System.Exit
import System.FilePath
import System.Directory

import CabalHelper.Shared.Common
  (parseVer, trim, appCacheDir, parsePkgId)
import CabalHelper.Compiletime.Types
import CabalHelper.Compiletime.Cabal
  ( ResolvedCabalVersion, showResolvedCabalVersion, UnpackedCabalVersion
  , unpackedToResolvedCabalVersion, CabalVersion'(..) )
import CabalHelper.Compiletime.Process
import CabalHelper.Compiletime.Log

data GhcPackageSource
    = GPSAmbient
    | GPSPackageDBs ![PackageDbDir]
    | GPSPackageEnv !PackageEnvFile

data GhcInvocation = GhcInvocation
    { giOutDir          :: !FilePath
    , giOutput          :: !FilePath
    , giCPPOptions      :: ![String]
    , giPackageSource   :: !GhcPackageSource
    , giIncludeDirs     :: ![FilePath]
    , giHideAllPackages :: !Bool
    , giPackages        :: ![String]
    , giWarningFlags    :: ![String]
    , giInputs          :: ![String]
    }

newtype GhcVersion = GhcVersion { unGhcVersion :: Version }
    deriving (Eq, Ord, Read, Show)

showGhcVersion :: GhcVersion -> String
showGhcVersion (GhcVersion v) = showVersion v

ghcVersion :: (Verbose, Progs) => IO GhcVersion
ghcVersion = GhcVersion .
  parseVer . trim <$> readProcess' (ghcProgram ?progs) ["--numeric-version"] ""

ghcPkgVersion :: (Verbose, Progs) => IO Version
ghcPkgVersion =
  parseVer . trim . dropWhile (not . isDigit)
    <$> readProcess' (ghcPkgProgram ?progs) ["--version"] ""

createPkgDb :: (Verbose, Progs) => UnpackedCabalVersion -> IO PackageDbDir
createPkgDb cabalVer = do
  db@(PackageDbDir db_path)
    <- getPrivateCabalPkgDb $ unpackedToResolvedCabalVersion cabalVer
  exists <- doesDirectoryExist db_path
  when (not exists) $
       callProcessStderr Nothing [] (ghcPkgProgram ?progs) ["init", db_path]
  return db

getPrivateCabalPkgDb :: (Verbose, Progs) => ResolvedCabalVersion -> IO PackageDbDir
getPrivateCabalPkgDb cabalVer = do
  appdir <- appCacheDir
  ghcVer <- ghcVersion
  let db_path =
        appdir </> "ghc-" ++ showGhcVersion ghcVer ++ ".package-dbs"
               </> "Cabal-" ++ showResolvedCabalVersion cabalVer
  return $ PackageDbDir db_path

getPrivateCabalPkgEnv
    :: Verbose => GhcVersion -> ResolvedCabalVersion -> IO PackageEnvFile
getPrivateCabalPkgEnv ghcVer cabalVer = do
  appdir <- appCacheDir
  let env_path =
        appdir </> "ghc-" ++ showGhcVersion ghcVer ++ ".package-envs"
               </> "Cabal-" ++ showResolvedCabalVersion cabalVer ++ ".package-env"
  return $ PackageEnvFile env_path

listCabalVersions
    :: (Verbose, Progs) => Maybe PackageDbDir -> MaybeT IO [Version]
listCabalVersions mdb = do
  let mdb_path = unPackageDbDir <$> mdb
  exists <- fromMaybe True <$>
    traverse (liftIO . doesDirectoryExist) mdb_path
  case exists of
    True -> MaybeT $ logIOError "listCabalVersions" $ Just <$> do
      let mdbopt = ("--package-conf="++) <$> mdb_path
          args = ["list", "--simple-output", "Cabal"] ++ maybeToList mdbopt
      catMaybes . map (fmap snd . parsePkgId) . words
               <$> readProcess' (ghcPkgProgram ?progs) args ""
    _ -> mzero

cabalVersionExistsInPkgDb
    :: (Verbose, Progs) => CabalVersion' a -> PackageDbDir -> IO Bool
cabalVersionExistsInPkgDb cabalVer db@(PackageDbDir db_path) = do
  fromMaybe False <$> runMaybeT (do
    vers <- listCabalVersions (Just db)
    return $
      case (cabalVer, vers) of
        (CabalVersion ver, _) -> ver `elem` vers
        (CabalHEAD _, []) -> False
        (CabalHEAD _, [_headver]) -> True
        (CabalHEAD _, _) ->
          error $ msg ++ db_path)
  where
    msg = "\
\Multiple Cabal versions in a HEAD package-db!\n\
\This shouldn't happen. However you can manually delete the following\n\
\directory to resolve this:\n    "

invokeGhc :: Env => GhcInvocation -> IO (Either ExitCode FilePath)
invokeGhc GhcInvocation {..} = do
    rv <- callProcessStderr' (Just "/") [] (ghcProgram ?progs) $ concat
      [ [ "-outputdir", giOutDir
        , "-o", giOutput
        ]
      , map ("-optP"++) giCPPOptions
      , if giHideAllPackages then ["-hide-all-packages"] else []
      , let packageFlags = concatMap (\p -> ["-package", p]) giPackages in
        case giPackageSource of
          GPSAmbient -> packageFlags
          GPSPackageDBs dbs -> concat
            [ map ("-package-conf="++) $ unPackageDbDir <$> dbs
            , packageFlags
            ]
          GPSPackageEnv env -> [ "-package-env=" ++ unPackageEnvFile env ]
      , map ("-i"++) $ nub $ "" : giIncludeDirs
      , giWarningFlags
      , ["--make"]
      , giInputs
      ]
    return $
      case rv of
        ExitSuccess -> Right giOutput
        e@(ExitFailure _) -> Left e