aboutsummaryrefslogtreecommitdiff
path: root/tests/CompileTest.hs
blob: de9b6abe36dc4e3f96ff25666674e2c44104435c (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
{-# LANGUAGE ScopedTypeVariables #-}

import System.Process
import System.Exit
import System.IO
import Control.Exception as E
import Data.List
import Data.Maybe
import Data.Version
import Data.Functor
import Data.Function
import qualified Distribution.Compat.ReadP as Dist
import Distribution.Version (VersionRange, withinRange)
import Distribution.Text
import Control.Arrow
import Control.Monad
import Prelude

import CabalHelper.Compiletime.Compat.Environment
import CabalHelper.Compiletime.Compat.Version
import CabalHelper.Compiletime.Compile
import CabalHelper.Compiletime.Types
import CabalHelper.Shared.Common

runReadP'Dist :: Dist.ReadP t t -> String -> t
runReadP'Dist p i = case filter ((=="") . snd) $ Dist.readP_to_S p i of
                 (a,""):[] -> a
                 _ -> error $ "Error parsing: " ++ show i

withinRange'CH :: Either HEAD Version -> VersionRange -> Bool
withinRange'CH v r =
    withinRange (fromDataVersion v') r
  where
    v' = either (const $ parseVer "1000000000") id v

main :: IO ()
main = do
  setEnv "HOME" =<< fromMaybe "/tmp" <$> lookupEnv "TMPDIR"
  _ <- rawSystem "cabal" ["update"]

  let parseVer' "HEAD" = Left HEAD
      parseVer' v      = Right $ parseVer v

  let cabal_versions :: [Either HEAD Version]
      cabal_versions = map parseVer'
           -- "1.14.0" -- not supported at runtime
           [ "1.16.0"
           , "1.16.0.1"
           , "1.16.0.2"
           , "1.16.0.3"
           , "1.18.0"
           , "1.18.1"
           , "1.18.1.1"
           , "1.18.1.2"
           , "1.18.1.3"
           , "1.18.1.4"
           , "1.18.1.5"
           , "1.18.1.6"
           , "1.18.1.7"
           , "1.20.0.0"
           , "1.20.0.1"
           , "1.20.0.2"
           , "1.20.0.3"
           , "1.20.0.4"
           , "1.22.0.0"
           , "1.22.1.0"
           , "1.22.1.1"
           , "1.22.2.0"
           , "1.22.3.0"
           , "1.22.4.0"
           , "1.22.5.0"
           , "1.22.6.0"
           , "1.22.7.0"
           , "1.22.8.0"
           , "1.24.0.0"
           , "1.24.1.0"
           , "1.24.2.0"
           , "2.0.0.2"
           , "HEAD"
           ]

  ghc_ver <- ghcVersion defaultOptions

  let constraint :: VersionRange
      constraint =
          fromMaybe (snd $ last constraint_table) $
          fmap snd $
          find (and . (zipWith (==) `on` versionBranch) ghc_ver . fst) $
          constraint_table

      constraint_table =
          map (parseVer *** runReadP'Dist parse) $
              [ ("7.4"  , ">= 1.14    && < 2")
              , ("7.6"  , ">= 1.16    && < 2")
              , ("7.8"  , ">= 1.18    && < 2")
              , ("7.10" , ">= 1.22.2  && < 2")
              , ("8.0.1", ">= 1.24          ")
              , ("8.0.2", ">= 1.24.2        ")
              , ("8.2.1", ">= 2.0.0.2       ")
              ]

      relevant_cabal_versions =
          reverse $ filter (flip withinRange'CH constraint) cabal_versions

  rvs <- forM relevant_cabal_versions $ \ver -> do
           let sver = either show showVersion ver
           hPutStrLn stderr $ "\n\n\n\n\n\n====== Compiling with Cabal-" ++ sver
           compilePrivatePkgDb ver

  let printStatus (cv, rv) = putStrLn $ "- Cabal "++ver++" "++status
        where  ver = case cv of Left _ -> "HEAD"; Right v -> showVersion v
               status = case rv of
                         Right _ ->
                             "succeeded"
                         Left rvc ->
                             "failed (exit code "++show rvc++")"

  let drvs = relevant_cabal_versions `zip` rvs

  mapM_ printStatus (relevant_cabal_versions `zip` rvs)
  if any isLeft' $ map snd $ filter ((/=Left HEAD) . fst) drvs
     then exitFailure
     else exitSuccess

 where
   isLeft' (Left _) = True
   isLeft' (Right _) = False

compilePrivatePkgDb :: Either HEAD Version -> IO (Either ExitCode FilePath)
compilePrivatePkgDb eCabalVer = do
    res <- E.try $ installCabal defaultOptions { verbose = True } eCabalVer
    case res of
      Right (db, e_commit_ver) ->
          compileWithPkg (Just db) e_commit_ver
      Left (ioe :: IOException) -> do
          print ioe
          return $ Left (ExitFailure 1)

compileWithPkg :: Maybe PackageDbDir
               -> Either String Version
               -> IO (Either ExitCode FilePath)
compileWithPkg mdb eCabalVer =
    compile "/does-not-exist" defaultOptions { verbose = True } $
      Compile Nothing mdb eCabalVer [cabalPkgId eCabalVer]

cabalPkgId :: Either String Version -> String
cabalPkgId (Left _commitid) = "Cabal"
cabalPkgId (Right v) = "Cabal-" ++ showVersion v