Skip to content

Commit

Permalink
history
Browse files Browse the repository at this point in the history
  • Loading branch information
phadej committed Jul 1, 2024
1 parent 7ef192a commit 4c76c46
Show file tree
Hide file tree
Showing 4 changed files with 26 additions and 10 deletions.
3 changes: 0 additions & 3 deletions src/HaskellCI/Cabal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,6 @@ import HaskellCI.Prelude

import qualified Distribution.Version as C

defaultCabalInstallVersion :: Maybe Version
defaultCabalInstallVersion = Just (C.mkVersion [3,10])

-- | Convert cabal-install version to a version ghcup understands.
cabalGhcupVersion :: Version -> Version
cabalGhcupVersion ver = case C.versionNumbers ver of
Expand Down
14 changes: 11 additions & 3 deletions src/HaskellCI/Config/History.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,11 +7,19 @@ import HaskellCI.Config.Type
import HaskellCI.Config.Ubuntu
import HaskellCI.Prelude

history :: [(Int, Config -> Config)]
history :: [([Int], Config -> Config)]
history =
[ 20241020 := \cfg -> cfg
[ ver 0 19 20240414 := \cfg -> cfg
-- https://github.com/haskell-CI/haskell-ci/pull/713/files (docspec)
, ver 0 19 20240420 := \cfg -> cfg
& field @"cfgUbuntu" .~ Jammy
, ver 0 19 20240513 := \cfg -> cfg
-- defaultHeadHackage = C.orLaterVersion (C.mkVersion [9,11])
]
where
ver x y z = [x, y, z]

defaultConfig :: Config
defaultConfig = initialConfig
defaultConfig = foldl' f initialConfig history
where
f !cfg (_, g) = g cfg
8 changes: 5 additions & 3 deletions src/HaskellCI/Config/Initial.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module HaskellCI.Config.Initial where

import HaskellCI.Prelude

import qualified Distribution.Types.VersionRange as C
import qualified Distribution.Version as C

import HaskellCI.Config.Components
import HaskellCI.Config.CopyFields
Expand All @@ -17,11 +17,13 @@ import HaskellCI.Ghcup
import HaskellCI.HeadHackage
import HaskellCI.TestedWith

-- | This is an "initial" configuration. It's meant to stay immutable.
-- All changes to defaults should be done in History.
initialConfig :: Config
initialConfig = Config
{ cfgCabalInstallVersion = Nothing
{ cfgCabalInstallVersion = Just (C.mkVersion [3,10])
, cfgJobs = Nothing
, cfgUbuntu = Focal -- change to xenial
, cfgUbuntu = Bionic
, cfgTestedWith = TestedWithUniform
, cfgEnabledJobs = anyVersion
, cfgCopyFields = CopyFieldsSome
Expand Down
11 changes: 10 additions & 1 deletion src/HaskellCI/Config/Ubuntu.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,13 +6,20 @@ import qualified Distribution.Parsec as C
import qualified Distribution.Pretty as C
import qualified Text.PrettyPrint as PP

data Ubuntu = Focal | Jammy | Noble
data Ubuntu
= Xenial
| Bionic
| Focal
| Jammy
| Noble
deriving (Eq, Ord, Show, Enum, Bounded)

instance C.Parsec Ubuntu where
parsec = do
t <- C.parsecToken
case t of
"xenial" -> return Xenial
"bionic" -> return Bionic
"focal" -> return Focal
"jammy" -> return Jammy
"noble" -> return Noble
Expand All @@ -22,6 +29,8 @@ instance C.Pretty Ubuntu where
pretty = PP.text . showUbuntu

showUbuntu :: Ubuntu -> String
showUbuntu Xenial = "xenial"
showUbuntu Bionic = "bionic"
showUbuntu Focal = "focal"
showUbuntu Jammy = "jammy"
showUbuntu Noble = "noble"

0 comments on commit 4c76c46

Please sign in to comment.