Skip to content
Snippets Groups Projects
Commit 45e2533a authored by Sylvain Henry's avatar Sylvain Henry
Browse files

Add test script

parent b40dc9e7
No related branches found
No related tags found
No related merge requests found
test.hs 0 → 100644
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE BlockArguments #-}
module Main where
import qualified Data.List as List
import System.Process
import Control.Monad
import Data.Version
import Text.ParserCombinators.ReadP
main :: IO ()
main = do
callCommand "ghcup upgrade"
let toVersion x = fst $ head $ filter (null . snd) $ readP_to_S (parseVersion) x
let show_versions = concatMap (\v -> "\n - " ++ showVersion v)
-- get available GHC versions via ghcup
avails <- readCreateProcess (shell "ghcup list -r -t ghc") ""
let fix_avail = toVersion . takeWhile (/= ' ') . drop 4
let avail_ghc_versions = fmap fix_avail (lines avails)
putStrLn $ "Available GHC versions: " ++ show_versions avail_ghc_versions
let
-- only test the recent ones
test_pred = (>= makeVersion [8,8])
prefiltered = filter test_pred avail_ghc_versions
-- take only the latest version per major release
major = take 2 . versionBranch
same_major x y = major x == major y
test_ghc_versions = fmap (last . List.sort) $ List.groupBy same_major prefiltered
putStrLn $ "We will test the following GHC versions: " ++ show_versions test_ghc_versions
forM_ test_ghc_versions \version -> do
let v = showVersion version
let ghc = "ghc-"++v
putStrLn "#######################################"
putStrLn $ "Testing " ++ ghc
putStrLn "#######################################"
putStrLn "# Installing GHC..."
callCommand $ "ghcup install ghc " ++ v
putStrLn "# Trying to build with cabal-install..."
callCommand "cabal clean"
callCommand $ "cabal build -w " ++ ghc
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment