Skip to content

Commit

Permalink
Support for weeder step
Browse files Browse the repository at this point in the history
  • Loading branch information
kostmo committed Jul 18, 2024
1 parent 5e5b27d commit 2f58ce8
Show file tree
Hide file tree
Showing 7 changed files with 53 additions and 13 deletions.
2 changes: 1 addition & 1 deletion cabal.haskell-ci
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ ghc-head: False
-- remove cabal noise from test output
-- cabal-noise: False

-- Build tests. In addition to True and False you may specify
-- Build tests. Alternatively to True and False you may specify
-- a version range, e.g. >= 8.0 to build tests only in some jobs.
tests: True

Expand Down
3 changes: 3 additions & 0 deletions src/HaskellCI/Auxiliary.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,7 @@ data Auxiliary = Auxiliary
, anyJobUsesPreviewGHC :: Bool
, runHaddock :: Bool
, haddockFlags :: String
, runWeeder :: Bool
}

auxiliary :: Config -> Project URI Void Package -> JobVersions -> Auxiliary
Expand Down Expand Up @@ -84,6 +85,8 @@ auxiliary Config {..} prj JobVersions {..} = Auxiliary {..}
ComponentsAll -> " --haddock-all"
ComponentsLibs -> ""

runWeeder = not (equivVersionRanges C.noVersion cfgWeeder)

extraCabalProjectFields :: FilePath -> [C.PrettyField ()]
extraCabalProjectFields rootdir = buildList $ do
-- generate package fields for URI packages.
Expand Down
2 changes: 2 additions & 0 deletions src/HaskellCI/Config/Grammar.hs
Original file line number Diff line number Diff line change
Expand Up @@ -90,6 +90,8 @@ configGrammar = Config
^^^ metahelp "RANGE" "Haddock step"
<*> optionalFieldDef "haddock-components" (field @"cfgHaddockComponents") defaultConfig
^^^ metahelp "all|libs" "Haddock components"
<*> rangeField "weeder" (field @"cfgWeeder") defaultConfig
^^^ metahelp "RANGE" "Weeder step"
<*> rangeField "no-tests-no-benchmarks" (field @"cfgNoTestsNoBench") defaultConfig
^^^ metahelp "RANGE" "Build without tests and benchmarks"
<*> rangeField "unconstrained" (field @"cfgUnconstrainted") defaultConfig
Expand Down
1 change: 1 addition & 0 deletions src/HaskellCI/Config/Initial.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,7 @@ initialConfig = Config
, cfgBenchmarks = anyVersion
, cfgHaddock = anyVersion
, cfgHaddockComponents = ComponentsAll
, cfgWeeder = anyVersion
, cfgNoTestsNoBench = anyVersion
, cfgUnconstrainted = anyVersion
, cfgHeadHackage = defaultHeadHackage
Expand Down
1 change: 1 addition & 0 deletions src/HaskellCI/Config/Type.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,7 @@ data Config = Config
, cfgBenchmarks :: !VersionRange
, cfgHaddock :: !VersionRange
, cfgHaddockComponents :: !Components
, cfgWeeder :: !VersionRange
, cfgNoTestsNoBench :: !VersionRange
, cfgUnconstrainted :: !VersionRange
, cfgHeadHackage :: !VersionRange
Expand Down
31 changes: 25 additions & 6 deletions src/HaskellCI/GitHub.hs
Original file line number Diff line number Diff line change
Expand Up @@ -101,9 +101,9 @@ makeGitHub
-> Either HsCiError GitHub
makeGitHub _argv config@Config {..} gitconfig prj jobs@JobVersions {..} = do
let envEnv = Map.fromList
[ ("HCNAME", "${{ matrix.compiler }}") -- e.g. ghc-8.8.4
, ("HCKIND", "${{ matrix.compilerKind }}") -- ghc
, ("HCVER", "${{ matrix.compilerVersion }}") -- 8.8.4
[ ("HCNAME", ghWrapExpr "matrix.compiler") -- e.g. ghc-8.8.4
, ("HCKIND", ghWrapExpr "matrix.compilerKind") -- ghc
, ("HCVER", ghWrapExpr "matrix.compilerVersion") -- 8.8.4
]

-- Validity checks
Expand Down Expand Up @@ -536,6 +536,15 @@ makeGitHub _argv config@Config {..} gitconfig prj jobs@JobVersions {..} = do
-- disable-documentation disables docs in deps: https://github.com/haskell/cabal/issues/7462
sh_if range $ "$CABAL v2-haddock --disable-documentation" ++ haddockFlags ++ " $ARG_COMPILER --with-haddock $HADDOCK $ARG_TESTS $ARG_BENCH all"

when runWeeder $
let range = RangeGHC /\ Range cfgWeeder in
let ifCond = ghCompilerVersionArithPredicate allVersions range in
for_ pkgs $ \Pkg{pkgName} -> do
githubUsesIf "weeder" "freckle/weeder-action@v2" ifCond $ buildList $ do
item ("ghc-version", ghWrapExpr "matrix.compilerVersion")
item ("weeder-arguments", "--config $GITHUB_WORKSPACE/source/weeder.toml")
item ("working-directory", ghWrapExpr $ ghEnvContext $ pkgNameDirVariable' pkgName)

-- unconstrained build
unless (equivVersionRanges C.noVersion cfgUnconstrainted) $ githubRun "unconstrained build" $ do
let range = Range cfgUnconstrainted
Expand Down Expand Up @@ -590,7 +599,7 @@ makeGitHub _argv config@Config {..} gitconfig prj jobs@JobVersions {..} = do
, ghjSteps = steps
, ghjIf = Nothing
, ghjContainer = Just $ "buildpack-deps:" ++ ubuntuVer
, ghjContinueOnError = Just "${{ matrix.allow-failure }}"
, ghjContinueOnError = Just $ ghWrapExpr "matrix.allow-failure"
, ghjServices = mconcat
[ Map.singleton "postgres" postgresService | cfgPostgres ]
, ghjTimeout = max 10 cfgTimeoutMinutes
Expand Down Expand Up @@ -764,10 +773,10 @@ ircJob actionName mainJobName projectName cfg gitconfig = item ("irc", GitHubJob
, Just repo <- parseGitHubRepo url

= Just
$ "${{ always() && (github.repository == '" ++ T.unpack repo ++ "') }}"
$ ghWrapExpr "always() && (github.repository == '" ++ T.unpack repo ++ "')"

| otherwise
= Just "${{ always() }}"
= Just $ ghWrapExpr "always()"
-- Use always() above to ensure that the IRC job will still run even if
-- the build job itself fails (see #437).

Expand Down Expand Up @@ -855,3 +864,13 @@ parseGitHubRepo t =
-- runners support.
ghcRunsOnVer :: String
ghcRunsOnVer = "ubuntu-20.04"

ghWrapExpr :: String -> String
ghWrapExpr expr = "${{ " ++ expr ++ " }}"

ghEnvContext :: String -> String
ghEnvContext = ("env." ++)

ghCompilerVersionArithPredicate :: Set CompilerVersion -> CompilerRange -> String
ghCompilerVersionArithPredicate = compilerVersionPredicateImpl $
freeToArith $ ExprConfig ghWrapExpr ghEnvContext
26 changes: 20 additions & 6 deletions src/HaskellCI/ShVersionRange.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,9 @@
module HaskellCI.ShVersionRange (
compilerVersionPredicate,
compilerVersionArithPredicate,
compilerVersionPredicateImpl,
freeToArith,
ExprConfig (..),
roundDown,
) where

Expand All @@ -21,11 +24,11 @@ import HaskellCI.Compiler
-- >>> import qualified Distribution.Version as C

compilerVersionPredicate :: Set CompilerVersion -> CompilerRange -> String
compilerVersionPredicate = compilerVersionPredicateImpl (toTest . freeToArith) where
compilerVersionPredicate = compilerVersionPredicateImpl (toTest . shFreeToArith) where
toTest expr = "[ " ++ expr ++ " -ne 0 ]"

compilerVersionArithPredicate :: Set CompilerVersion -> CompilerRange -> String
compilerVersionArithPredicate = compilerVersionPredicateImpl freeToArith
compilerVersionArithPredicate = compilerVersionPredicateImpl shFreeToArith

compilerVersionPredicateImpl
:: (Free String -> String)
Expand Down Expand Up @@ -197,14 +200,25 @@ roundDown = go S.empty . S.toList where
-- Arithmetic expression
-------------------------------------------------------------------------------

freeToArith :: Free String -> String
freeToArith z
shWrapExpr :: String -> String
shWrapExpr expr = "$((" ++ expr ++ "))"

shFreeToArith :: Free String -> String
shFreeToArith = freeToArith $ ExprConfig shWrapExpr id

data ExprConfig = ExprConfig {
_exprWrap :: String -> String
, _varWrap :: String -> String
}

freeToArith :: ExprConfig -> Free String -> String
freeToArith (ExprConfig exprWrap varWrap) z
| z == top = "1"
| z == bottom = "0"
| otherwise = "$((" ++ go 0 z ++ "))"
| otherwise = exprWrap $ go 0 z
where
go :: Int -> Free String -> String
go _ (Var x) = x
go _ (Var x) = varWrap x
go _ F.Bottom = "1"
go _ F.Top = "0"

Expand Down

0 comments on commit 2f58ce8

Please sign in to comment.