From 58c2a8ad549496e32a4cf0fbeaa0d785daba3683 Mon Sep 17 00:00:00 2001 From: Ryan Scott Date: Sun, 2 Apr 2023 08:25:37 -0400 Subject: [PATCH 1/7] Whitespace only --- .../Verifier/SAW/Heapster/TypedCrucible.hs | 24 +++++++++---------- 1 file changed, 12 insertions(+), 12 deletions(-) diff --git a/heapster-saw/src/Verifier/SAW/Heapster/TypedCrucible.hs b/heapster-saw/src/Verifier/SAW/Heapster/TypedCrucible.hs index d91c3d3e8d..1bccc9b380 100644 --- a/heapster-saw/src/Verifier/SAW/Heapster/TypedCrucible.hs +++ b/heapster-saw/src/Verifier/SAW/Heapster/TypedCrucible.hs @@ -2009,7 +2009,7 @@ explore :: CruCtx args -> CruCtx ghosts -> MbValuePerms ((tops :++: args) :++: ghosts) -> - + (RAssign ExprVar tops -> RAssign ExprVar args -> RAssign ExprVar ghosts -> DistPerms ((tops :++: args) :++: ghosts) -> PermCheckM ext cblocks blocks tops ret r1 ps r2 ((tops :++: args) @@ -2029,7 +2029,7 @@ explore names entryID topCtx argCtx ghostCtx mb_perms_in m = (tops_ns, args_ns) = RL.split Proxy args_prxs tops_args st :: PermCheckState ext blocks tops ret ((tops :++: args) :++: ghosts) st = emptyPermCheckState (distPermSet perms_in) tops_ns entryID local_names in - + setVarTypes tops_ns topCtx >>> modify (\s->s{ stPPInfo = ppInfoApplyAllocation tops_ns topDbgs (stPPInfo st)}) >>> modify (\s->s{ stPPInfo = ppInfoApplyAllocation args_ns argDbgs (stPPInfo st)}) >>> @@ -2225,8 +2225,8 @@ getAtomicLLVMPerms r = Right ps -> pure ps Left e -> permGetPPInfo >>>= \ppinfo -> - stmtFailM $ AtomicPermError - (permPretty ppinfo r) + stmtFailM $ AtomicPermError + (permPretty ppinfo r) (permPretty ppinfo (ValPerm_Eq $ PExpr_LLVMWord e)) @@ -2344,7 +2344,7 @@ allocateDebugNames base (ds :>: Constant dbg) (CruCtxCons ts tp) ppi = (Just b,_) -> b ++ "_" ++ typeBaseName tp (Nothing,Nothing) -> typeBaseName tp - + allocateDebugNamesM :: Maybe String -> -- ^ The base name of the variable (e.g., "top", "arg", etc.) RAssign (Constant (Maybe String)) tps -> @@ -3184,7 +3184,7 @@ tcEmitLLVMSetExpr ctx loc (LLVM_PointerExpr w blk_reg off_reg) = emitLLVMStmt knownRepr name loc (ConstructLLVMWord toff_reg) >>>= \x -> stmtRecombinePerms >>> pure (addCtxName ctx x) - _ -> + _ -> permGetPPInfo >>>= \ppinfo -> stmtFailM $ NonZeroPointerBlockError (permPretty ppinfo tblk_reg) @@ -3503,8 +3503,8 @@ tcEmitLLVMStmt _arch ctx loc (LLVM_Alloca w _ sz_reg _ _) = stmtFailM $ AllocaError (AllocaNonConstantError $ permPretty ppinfo sz_treg) (Just fp, p, _) -> permGetPPInfo >>>= \ppinfo -> - stmtFailM $ AllocaError $ AllocaFramePermError - (permPretty ppinfo fp) + stmtFailM $ AllocaError $ AllocaFramePermError + (permPretty ppinfo fp) (permPretty ppinfo p) (Nothing, _, _) -> stmtFailM $ AllocaError AllocaFramePtrError @@ -3745,7 +3745,7 @@ tcEmitLLVMStmt _arch ctx loc (LLVM_PtrEq _ (r1 :: Reg ctx (LLVMPointerType wptr) -- fail, because there is no way to compare pointers in the translation _ -> permGetPPInfo >>>= \ppinfo -> - stmtFailM $ PointerComparisonError + stmtFailM $ PointerComparisonError (permPretty ppinfo x1) (permPretty ppinfo x2) @@ -4462,13 +4462,13 @@ instance ErrorPretty StmtError where pretty "Could not cast" <+> docx <+> pretty "from" <+> pretty (show tp1) <+> pretty "to" <+> pretty (show tp2) - ppError FailedAssertionError = + ppError FailedAssertionError = "Failed assertion" ppError (NonZeroPointerBlockError tblk_reg) = renderDoc $ pretty "LLVM_PointerExpr: Non-zero pointer block: " <> tblk_reg - ppError (UndefinedBehaviorError doc) = + ppError (UndefinedBehaviorError doc) = renderDoc doc - ppError X86ExprError = + ppError X86ExprError = "X86Expr not supported" ppError (AllocaError (AllocaNonConstantError sz_treg)) = renderDoc $ pretty "LLVM_Alloca: non-constant size for" <+> From 3d83e0d8af0fa29ddecd27c9fb4c90128b8ac179 Mon Sep 17 00:00:00 2001 From: Ryan Scott Date: Sun, 2 Apr 2023 07:08:00 -0400 Subject: [PATCH 2/7] Support building with GHC 9.4 This contains a variety of tweaks needed to build SAW with GHC 9.4: * GHC 9.4 is more conservative about inferring superclass constraints that arise from functional dependencies (see [this section](https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.4?version_id=b60e52482a666d25638d59cd7e86851ddf971dc1#constraints-derived-from-superclasses) of the GHC 9.4 Migration Guide), so we must add explicit `m ~ Identity` constraints to certain parts of `heapster-saw` to make it compile with GHC 9.4. * I raised the upper version bounds on `aeson` and `vector` to allow building them with GHC 9.4. * The following submodule changes were brought in to support building with GHC 9.4: * `argo`: #193 * `crucible`: GaloisInc/crucible#1073 (This also requires bumping the `llvm-pretty`, `llvm-pretty-bc-parser`, and `what4` submodules as a side effect) * `language-sally`: GaloisInc/language-sally#13 * `macaw`: GaloisInc/macaw#330 * `parameterized-utils`: GaloisInc/parameterized-utils#146 Fixes #1852. --- deps/crucible | 2 +- deps/language-sally | 2 +- deps/llvm-pretty | 2 +- deps/llvm-pretty-bc-parser | 2 +- deps/macaw | 2 +- deps/parameterized-utils | 2 +- deps/what4 | 2 +- heapster-saw/heapster-saw.cabal | 2 +- .../src/Verifier/SAW/Heapster/Implication.hs | 13 +++++-------- .../src/Verifier/SAW/Heapster/TypedCrucible.hs | 8 ++++---- saw-remote-api/saw-remote-api.cabal | 6 +++--- saw-script.cabal | 2 +- 12 files changed, 21 insertions(+), 24 deletions(-) diff --git a/deps/crucible b/deps/crucible index f4145fbed9..ad4a553487 160000 --- a/deps/crucible +++ b/deps/crucible @@ -1 +1 @@ -Subproject commit f4145fbed96245f385a91ef3a32e6737df1075ff +Subproject commit ad4a553487eeb5c6bbb5abf4bde26af905bf0254 diff --git a/deps/language-sally b/deps/language-sally index 24d53a963c..b218ac7d4f 160000 --- a/deps/language-sally +++ b/deps/language-sally @@ -1 +1 @@ -Subproject commit 24d53a963c2a2d11a118cfaa98956a69f5c8c6d5 +Subproject commit b218ac7d4f39b4d30cf7f2db584efa5ea926a024 diff --git a/deps/llvm-pretty b/deps/llvm-pretty index 64d43d9375..b13493fda7 160000 --- a/deps/llvm-pretty +++ b/deps/llvm-pretty @@ -1 +1 @@ -Subproject commit 64d43d9375a819dc2a2df99fb98df24f049dcfaa +Subproject commit b13493fda7276835a4e19bf13a9fb1b3e08083a9 diff --git a/deps/llvm-pretty-bc-parser b/deps/llvm-pretty-bc-parser index cbcf0954c2..d541adf5c1 160000 --- a/deps/llvm-pretty-bc-parser +++ b/deps/llvm-pretty-bc-parser @@ -1 +1 @@ -Subproject commit cbcf0954c23da0018df3cc6aae77290ae2efe53b +Subproject commit d541adf5c12e86058cbc1f211456b4ad4a7011a1 diff --git a/deps/macaw b/deps/macaw index 0686e5d86b..30fe405a39 160000 --- a/deps/macaw +++ b/deps/macaw @@ -1 +1 @@ -Subproject commit 0686e5d86bfd802e04dd94cf8836127127232f8f +Subproject commit 30fe405a3987fac3a886b66f4de9b9a7e1b25fac diff --git a/deps/parameterized-utils b/deps/parameterized-utils index a888f5862b..a58128337e 160000 --- a/deps/parameterized-utils +++ b/deps/parameterized-utils @@ -1 +1 @@ -Subproject commit a888f5862b73a1575d36fef9327fcbe3dbcbff51 +Subproject commit a58128337e2a795dd06dd3968b6a7e98dc1b27bf diff --git a/deps/what4 b/deps/what4 index 6c462cd46e..ffbad75b1c 160000 --- a/deps/what4 +++ b/deps/what4 @@ -1 +1 @@ -Subproject commit 6c462cd46e0ea9ebbfbd6b6ea237984eeb3dc72a +Subproject commit ffbad75b1ce65577422a19a30a39a5059be8b95f diff --git a/heapster-saw/heapster-saw.cabal b/heapster-saw/heapster-saw.cabal index 46a91108dc..1fb04c58b6 100644 --- a/heapster-saw/heapster-saw.cabal +++ b/heapster-saw/heapster-saw.cabal @@ -38,7 +38,7 @@ library filepath, language-rust, hobbits ^>= 1.4, - aeson >= 1.5 && < 2.1, + aeson >= 1.5 && < 2.2, th-abstraction, template-haskell, extra diff --git a/heapster-saw/src/Verifier/SAW/Heapster/Implication.hs b/heapster-saw/src/Verifier/SAW/Heapster/Implication.hs index 4aded72cb8..7315c6aae1 100644 --- a/heapster-saw/src/Verifier/SAW/Heapster/Implication.hs +++ b/heapster-saw/src/Verifier/SAW/Heapster/Implication.hs @@ -2972,7 +2972,7 @@ instance (NuMatching a, Substable PermVarSubst a Identity) => [nuMP| EqProofCons eqp' eq_step |] -> EqProofCons <$> genSubst s eqp' <*> genSubst s eq_step -instance SubstVar PermVarSubst m => +instance m ~ Identity => Substable PermVarSubst (SimplImpl ps_in ps_out) m where genSubst s mb_impl = case mbMatch mb_impl of [nuMP| SImpl_Drop x p |] -> @@ -3251,7 +3251,7 @@ instance SubstVar PermVarSubst m => [nuMP| SImpl_ElimAnyToPtr x fp |] -> SImpl_ElimAnyToPtr <$> genSubst s x <*> genSubst s fp -instance SubstVar PermVarSubst m => +instance m ~ Identity => Substable PermVarSubst (PermImpl1 ps_in ps_out) m where genSubst s mb_impl = case mbMatch mb_impl of [nuMP| Impl1_Fail err |] -> Impl1_Fail <$> genSubst s err @@ -3291,8 +3291,7 @@ instance SubstVar PermVarSubst m => Impl1_TryProveBVProp <$> genSubst s x <*> genSubst s prop <*> return (mbLift prop_str) --- FIXME: shouldn't need the SubstVar PermVarSubst m assumption... -instance (NuMatchingAny1 r, SubstVar PermVarSubst m, +instance (NuMatchingAny1 r, m ~ Identity, Substable1 PermVarSubst r m) => Substable PermVarSubst (PermImpl r ps) m where genSubst s mb_impl = case mbMatch mb_impl of @@ -3300,8 +3299,7 @@ instance (NuMatchingAny1 r, SubstVar PermVarSubst m, [nuMP| PermImpl_Step impl1 mb_impls |] -> PermImpl_Step <$> genSubst s impl1 <*> genSubst s mb_impls --- FIXME: shouldn't need the SubstVar PermVarSubst m assumption... -instance (NuMatchingAny1 r, SubstVar PermVarSubst m, +instance (NuMatchingAny1 r, m ~ Identity, Substable1 PermVarSubst r m) => Substable PermVarSubst (MbPermImpls r bs_pss) m where genSubst s mb_impls = case mbMatch mb_impls of @@ -3317,8 +3315,7 @@ instance SubstVar s m => Substable s (OrListDisj ps a disj) m where instance SubstVar s m => Substable1 s (OrListDisj ps a) m where genSubst1 = genSubst --- FIXME: shouldn't need the SubstVar PermVarSubst m assumption... -instance SubstVar PermVarSubst m => +instance m ~ Identity => Substable PermVarSubst (LocalPermImpl ps_in ps_out) m where genSubst s (mbMatch -> [nuMP| LocalPermImpl impl |]) = LocalPermImpl <$> genSubst s impl diff --git a/heapster-saw/src/Verifier/SAW/Heapster/TypedCrucible.hs b/heapster-saw/src/Verifier/SAW/Heapster/TypedCrucible.hs index 1bccc9b380..38c95b1e24 100644 --- a/heapster-saw/src/Verifier/SAW/Heapster/TypedCrucible.hs +++ b/heapster-saw/src/Verifier/SAW/Heapster/TypedCrucible.hs @@ -809,7 +809,7 @@ instance SubstVar PermVarSubst m => [nuMP| TypedRegsCons rs r |] -> TypedRegsCons <$> genSubst s rs <*> genSubst s r -instance (NuMatchingAny1 r, SubstVar PermVarSubst m, +instance (NuMatchingAny1 r, m ~ Identity, Substable1 PermVarSubst r m) => Substable PermVarSubst (AnnotPermImpl r ps) m where genSubst s (mbMatch -> [nuMP| AnnotPermImpl err impl |]) = @@ -1003,7 +1003,7 @@ instance SubstVar PermVarSubst m => Substable1 PermVarSubst (TypedJumpTarget blocks tops) m where genSubst1 = genSubst -instance SubstVar PermVarSubst m => +instance m ~ Identity => Substable PermVarSubst (TypedTermStmt blocks tops rets ps_in) m where genSubst s mb_x = case mbMatch mb_x of [nuMP| TypedJump impl_tgt |] -> TypedJump <$> genSubst s impl_tgt @@ -1015,7 +1015,7 @@ instance SubstVar PermVarSubst m => [nuMP| TypedErrorStmt str r |] -> TypedErrorStmt (mbLift str) <$> genSubst s r -instance (PermCheckExtC ext exprExt, SubstVar PermVarSubst m) => +instance (PermCheckExtC ext exprExt, m ~ Identity) => Substable PermVarSubst (TypedStmtSeq ext blocks tops rets ps_in) m where genSubst s mb_x = case mbMatch mb_x of [nuMP| TypedImplStmt impl_seq |] -> @@ -1027,7 +1027,7 @@ instance (PermCheckExtC ext exprExt, SubstVar PermVarSubst m) => TypedTermStmt (mbLift loc) <$> genSubst s term_stmt -instance (PermCheckExtC ext exprExt, SubstVar PermVarSubst m) => +instance (PermCheckExtC ext exprExt, m ~ Identity) => Substable1 PermVarSubst (TypedStmtSeq ext blocks tops rets) m where genSubst1 = genSubst diff --git a/saw-remote-api/saw-remote-api.cabal b/saw-remote-api/saw-remote-api.cabal index bf987df9e6..5623d8ae9f 100644 --- a/saw-remote-api/saw-remote-api.cabal +++ b/saw-remote-api/saw-remote-api.cabal @@ -34,8 +34,8 @@ common errors -Werror=overlapping-patterns common deps - build-depends: base >=4.11.1.0 && <4.17, - aeson >= 1.4.2 && < 2.1, + build-depends: base >=4.11.1.0 && <4.18, + aeson >= 1.4.2 && < 2.2, aig, argo, base64-bytestring, @@ -60,7 +60,7 @@ common deps silently, text, unordered-containers, - vector >= 0.12 && < 0.13, + vector >= 0.12 && < 0.14, cryptol-remote-api default-language: Haskell2010 diff --git a/saw-script.cabal b/saw-script.cabal index ed3b3257fc..5d02d4d94c 100644 --- a/saw-script.cabal +++ b/saw-script.cabal @@ -23,7 +23,7 @@ library default-language: Haskell2010 build-depends: base >= 4.9 - , aeson >= 2.0 && < 2.1 + , aeson >= 2.0 && < 2.2 , aig , array , binary From d54026de702e59e01d8bb79a8ea6ebec1e7a5f22 Mon Sep 17 00:00:00 2001 From: Ryan Scott Date: Sun, 2 Apr 2023 07:28:01 -0400 Subject: [PATCH 3/7] Fix -Wtype-equality-requires-operators warnings GHC 9.4 adds `-Wtype-equality-requires-operators` to `-Wall`, which warns about certain uses of type equalities that are not forward-compatible with planned changes in GHC. See [this section](https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.4?version_id=b60e52482a666d25638d59cd7e86851ddf971dc1#-is-now-a-type-operator) of the GHC 9.4 Migration Guide. These warnings are easily fixed by enabling the `TypeOperators` extension. --- crucible-mir-comp/src/Mir/Compositional/Builder.hs | 1 + crucible-mir-comp/src/Mir/Compositional/Clobber.hs | 1 + crux-mir-comp/src/Mir/Compositional.hs | 1 + crux-mir-comp/src/Mir/Cryptol.hs | 1 + heapster-saw/src/Verifier/SAW/Heapster/GenMonad.hs | 3 ++- saw-core/src/Verifier/SAW/Simulator/Prims.hs | 1 + src/SAWScript/Prover/What4.hs | 1 + 7 files changed, 8 insertions(+), 1 deletion(-) diff --git a/crucible-mir-comp/src/Mir/Compositional/Builder.hs b/crucible-mir-comp/src/Mir/Compositional/Builder.hs index b110198bde..d55f48b024 100644 --- a/crucible-mir-comp/src/Mir/Compositional/Builder.hs +++ b/crucible-mir-comp/src/Mir/Compositional/Builder.hs @@ -7,6 +7,7 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE TypeOperators #-} module Mir.Compositional.Builder where diff --git a/crucible-mir-comp/src/Mir/Compositional/Clobber.hs b/crucible-mir-comp/src/Mir/Compositional/Clobber.hs index f24a59b694..2686c4a25d 100644 --- a/crucible-mir-comp/src/Mir/Compositional/Clobber.hs +++ b/crucible-mir-comp/src/Mir/Compositional/Clobber.hs @@ -2,6 +2,7 @@ {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeOperators #-} module Mir.Compositional.Clobber where diff --git a/crux-mir-comp/src/Mir/Compositional.hs b/crux-mir-comp/src/Mir/Compositional.hs index d18053c046..774c8c7220 100644 --- a/crux-mir-comp/src/Mir/Compositional.hs +++ b/crux-mir-comp/src/Mir/Compositional.hs @@ -4,6 +4,7 @@ {-# Language DataKinds #-} {-# Language GADTs #-} {-# Language OverloadedStrings #-} +{-# Language TypeOperators #-} module Mir.Compositional where diff --git a/crux-mir-comp/src/Mir/Cryptol.hs b/crux-mir-comp/src/Mir/Cryptol.hs index 1db880a784..ffb3e00747 100644 --- a/crux-mir-comp/src/Mir/Cryptol.hs +++ b/crux-mir-comp/src/Mir/Cryptol.hs @@ -8,6 +8,7 @@ {-# Language RankNTypes #-} {-# Language ScopedTypeVariables #-} {-# Language TypeApplications #-} +{-# Language TypeOperators #-} {-# Language ViewPatterns #-} module Mir.Cryptol diff --git a/heapster-saw/src/Verifier/SAW/Heapster/GenMonad.hs b/heapster-saw/src/Verifier/SAW/Heapster/GenMonad.hs index f70a89cbae..47e14c81ac 100644 --- a/heapster-saw/src/Verifier/SAW/Heapster/GenMonad.hs +++ b/heapster-saw/src/Verifier/SAW/Heapster/GenMonad.hs @@ -3,6 +3,7 @@ {-# Language FlexibleInstances, MultiParamTypeClasses #-} -- MonadState {-# Language PolyKinds #-} -- gopenBinding {-# Language TypeFamilies #-} -- Equality constraints +{-# Language TypeOperators #-} -- Equality constraints {-# Language RankNTypes #-} module Verifier.SAW.Heapster.GenMonad ( -- * Core definitions @@ -61,7 +62,7 @@ instance (s1 ~ s2, r1 ~ r2) => MonadTrans (GenStateContT s1 r1 s2 r2) where -- | Capture the current continuation while preserving the state. gcaptureCC :: ((a -> m r1) -> m r2) -> GenStateContT s r1 s r2 m a -gcaptureCC f = GenStateContT \s k -> f (k s) +gcaptureCC f = GenStateContT \s k -> f (k s) -- | Run two generalized monad computations "in parallel" and combine their -- results diff --git a/saw-core/src/Verifier/SAW/Simulator/Prims.hs b/saw-core/src/Verifier/SAW/Simulator/Prims.hs index a226e66e30..6755757e53 100644 --- a/saw-core/src/Verifier/SAW/Simulator/Prims.hs +++ b/saw-core/src/Verifier/SAW/Simulator/Prims.hs @@ -9,6 +9,7 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE ViewPatterns #-} +{-# LANGUAGE TypeOperators #-} {- | Module : Verifier.SAW.Simulator.Prims diff --git a/src/SAWScript/Prover/What4.hs b/src/SAWScript/Prover/What4.hs index 73c4e11047..969a61f74a 100644 --- a/src/SAWScript/Prover/What4.hs +++ b/src/SAWScript/Prover/What4.hs @@ -1,6 +1,7 @@ {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} +{-# LANGUAGE TypeOperators #-} {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE GADTs #-} From d04c90158c25f3db9f37af5898d5b5198ec21953 Mon Sep 17 00:00:00 2001 From: Ryan Scott Date: Sun, 2 Apr 2023 07:56:46 -0400 Subject: [PATCH 4/7] Remove use of NoMonoLocalBinds after GADTs pragma This produces a `-Wgadt-mono-local-binds` warning with GHC 9.4, which has added the warning to `-Wall`. To avoid the warning, I have removed a use of `NoMonoLocalBinds` in `SAWScript.Crucible.JVM.BuiltinsJVM`. This required adding an explicit type signature to `failure` as a result. --- src/SAWScript/Crucible/JVM/BuiltinsJVM.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/SAWScript/Crucible/JVM/BuiltinsJVM.hs b/src/SAWScript/Crucible/JVM/BuiltinsJVM.hs index f8244ab6bc..0ea687e26f 100644 --- a/src/SAWScript/Crucible/JVM/BuiltinsJVM.hs +++ b/src/SAWScript/Crucible/JVM/BuiltinsJVM.hs @@ -7,7 +7,7 @@ Stability : provisional {-# LANGUAGE GADTs #-} -{-# LANGUAGE NoMonoLocalBinds #-} +{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE EmptyCase #-} {-# LANGUAGE PackageImports #-} @@ -176,7 +176,8 @@ jvm_extract c mname = do gp <- getGlobalPair opts pr let regval = gp^.Crucible.gpValue let regty = Crucible.regType regval - let failure = fail $ unwords ["Unexpected return type:", show regty] + let failure :: forall a. IO a + failure = fail $ unwords ["Unexpected return type:", show regty] t <- Crucible.asSymExpr regval (toSC sym st) failure cty <- case Crucible.asBaseType regty of From 3fe4fc80af91a918ac43b598b8c4442ec58b00da Mon Sep 17 00:00:00 2001 From: Ryan Scott Date: Sun, 2 Apr 2023 08:32:21 -0400 Subject: [PATCH 5/7] CI: Regenerate cabal.GHC-*.config files --- cabal.GHC-8.10.7.config | 98 ++++++++++++++++++++------------------- cabal.GHC-8.8.4.config | 98 ++++++++++++++++++++------------------- cabal.GHC-9.2.7.config | 100 +++++++++++++++++++++------------------- 3 files changed, 154 insertions(+), 142 deletions(-) diff --git a/cabal.GHC-8.10.7.config b/cabal.GHC-8.10.7.config index 84f07b3765..3818a165ee 100644 --- a/cabal.GHC-8.10.7.config +++ b/cabal.GHC-8.10.7.config @@ -16,21 +16,23 @@ constraints: any.BoundedChan ==1.0.3.0, QuickCheck -old-random +templatehaskell, any.StateVar ==1.2.2, any.adjunctions ==4.4.2, - any.aeson ==2.0.3.0, + any.aeson ==2.1.2.1, aeson -cffi +ordered-keymap, - any.aeson-typescript ==0.4.2.0, - any.alex ==3.2.7.1, - any.ansi-terminal ==0.11.4, + any.aeson-typescript ==0.5.0.0, + any.alex ==3.2.7.3, + any.ansi-terminal ==0.11.5, ansi-terminal -example, + any.ansi-terminal-types ==0.11.5, any.ansi-wl-pprint ==0.6.9, ansi-wl-pprint -example, any.appar ==0.1.8, - any.arithmoi ==0.12.0.2, + any.arithmoi ==0.12.1.0, any.array ==0.5.4.0, any.asn1-encoding ==0.9.6, any.asn1-parse ==0.9.5, any.asn1-types ==0.3.4, - any.assoc ==1.0.2, + any.assoc ==1.1, + assoc +tagged, any.async ==2.2.4, async -bench, any.attoparsec ==0.14.4, @@ -44,12 +46,12 @@ constraints: any.BoundedChan ==1.0.3.0, any.base16-bytestring ==1.0.2.0, any.base64-bytestring ==1.2.1.0, any.basement ==0.0.15, - any.bifunctors ==5.5.15, - bifunctors +semigroups +tagged, + any.bifunctors ==5.6.1, + bifunctors +tagged, any.bimap ==0.5.0, any.binary ==0.8.8.0, any.binary-orphans ==1.0.4.1, - any.bitvec ==1.1.3.0, + any.bitvec ==1.1.4.0, bitvec -libgmp, any.bitwise ==1.0.0.1, any.blaze-builder ==0.4.2.2, @@ -117,7 +119,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.doctest ==0.20.1, any.dotgen ==0.4.3, dotgen -devel, - any.easy-file ==0.2.2, + any.easy-file ==0.2.3, any.either ==5.0.2, any.entropy ==0.4.1.10, entropy -donotgetentropy, @@ -126,22 +128,25 @@ constraints: any.BoundedChan ==1.0.3.0, any.exceptions ==0.10.4, any.executable-path ==0.0.3.1, any.extensible-exceptions ==0.1.1.4, - any.extra ==1.7.12, + any.extra ==1.7.13, any.fast-logger ==3.2.1, any.fgl ==5.8.1.1, fgl +containers042, any.fgl-visualize ==0.1.0.1, - any.filelock ==0.1.1.5, + any.filelock ==0.1.1.6, any.filemanip ==0.3.6.3, any.filepath ==1.4.2.1, any.fingertree ==0.1.5.0, - any.free ==5.1.10, + any.foldable1-classes-compat ==0.1, + foldable1-classes-compat +tagged, + any.free ==5.2, any.generic-deriving ==1.14.3, generic-deriving +base-4-9, - any.generic-lens ==2.2.1.0, + any.generic-lens ==2.2.2.0, any.generic-lens-core ==2.2.1.0, any.generic-random ==1.5.0.1, generic-random -enable-inspect, + any.generically ==0.1.1, any.ghc ==8.10.7, any.ghc-boot ==8.10.7, any.ghc-boot-th ==8.10.7, @@ -154,14 +159,14 @@ constraints: any.BoundedChan ==1.0.3.0, any.graphviz ==2999.20.1.0, graphviz -test-parsing, any.happy ==1.20.1.1, - any.hashable ==1.3.5.0, + any.hashable ==1.4.2.0, hashable +integer-gmp -random-initial-seed, - any.hashtables ==1.2.4.2, + any.hashtables ==1.3.1, hashtables -bounds-checking -debug -detailed-profiling -portable -sse42 +unsafe-tricks, any.haskeline ==0.8.2, any.haskell-lexer ==1.1.1, any.haskell-src-exts ==1.23.1, - any.haskell-src-meta ==0.8.11, + any.haskell-src-meta ==0.8.12, any.hedgehog ==1.2, any.hedgehog-classes ==0.2.5.4, hedgehog-classes +aeson +comonad +primitive +semirings +vector, @@ -179,8 +184,8 @@ constraints: any.BoundedChan ==1.0.3.0, any.hspec-expectations ==0.8.2, any.http-date ==0.0.11, any.http-types ==0.12.3, - any.http2 ==4.0.0, - http2 -devel -doc -h2spec, + any.http2 ==4.1.2, + http2 -devel -h2spec, any.ieee754 ==0.8.0, any.indexed-profunctors ==0.1.1, any.indexed-traversable ==0.1.2.1, @@ -194,17 +199,17 @@ constraints: any.BoundedChan ==1.0.3.0, any.io-streams ==1.5.2.2, io-streams +network -nointeractivetests +zlib, any.iproute ==1.7.12, - any.itanium-abi ==0.1.1.1, + any.itanium-abi ==0.1.2, any.js-chart ==2.9.4.1, any.json ==0.10, json +generic -mapdict +parsec +pretty +split-base, any.kan-extensions ==5.2.5, - any.kvitable ==1.0.2.0, + any.kvitable ==1.0.2.1, any.language-c99 ==0.2.0, any.language-c99-simple ==0.2.2, any.language-c99-util ==0.2.0, language-rust +enablequasiquotes +usebytestrings, - any.lens ==5.1.1, + any.lens ==5.2.2, lens -benchmark-uniplate -dump-splices +inlining -j +test-hunit +test-properties +test-templates +trustworthy, any.libBF ==0.6.5.1, libBF -system-libbf, @@ -212,20 +217,20 @@ constraints: any.BoundedChan ==1.0.3.0, libffi +ghc-bundled-libffi, any.libyaml ==0.1.2, libyaml -no-unicode -system-libyaml, - any.lifted-async ==0.10.2.3, + any.lifted-async ==0.10.2.4, any.lifted-base ==0.2.3.12, llvm-pretty-bc-parser -fuzz -regressions, any.logict ==0.8.0.0, - any.lucid ==2.11.1, + any.lucid ==2.11.20230408, any.lumberjack ==1.0.2.0, any.math-functions ==0.3.4.2, math-functions +system-erf +system-expm1, - any.megaparsec ==9.0.1, + any.megaparsec ==9.2.1, megaparsec -dev, any.memory ==0.18.0, memory +support_bytestring +support_deepseq, any.microlens ==0.4.13.1, - any.microlens-th ==0.4.3.11, + any.microlens-th ==0.4.3.12, any.microstache ==1.0.2.3, any.mmorph ==1.2.0, any.mod ==0.1.2.2, @@ -264,7 +269,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.prettyprinter ==1.7.1, prettyprinter -buildreadme +text, any.prettyprinter-ansi-terminal ==1.1.3, - any.primitive ==0.7.4.0, + any.primitive ==0.8.0.0, any.process ==1.6.13.2, any.profunctors ==5.6.2, any.psqueues ==0.2.7.3, @@ -280,9 +285,9 @@ constraints: any.BoundedChan ==1.0.3.0, any.regex-compat ==0.95.2.1, any.regex-posix ==0.96.0.1, regex-posix -_regex-posix-clib, - any.resourcet ==1.2.6, + any.resourcet ==1.3.0, any.rts ==1.0.1, - any.s-cargot ==0.1.5.0, + any.s-cargot ==0.1.6.0, s-cargot -build-example, any.safe ==0.3.19, any.safe-exceptions ==0.1.7.3, @@ -290,7 +295,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.scientific ==0.3.7.0, scientific -bytestring-builder -integer-simple, any.scotty ==0.12.1, - any.semialign ==1.2.0.1, + any.semialign ==1.3, semialign +semigroupoids, any.semigroupoids ==5.3.7, semigroupoids +comonad +containers +contravariant +distributive +tagged +unordered-containers, @@ -308,30 +313,29 @@ constraints: any.BoundedChan ==1.0.3.0, any.split ==0.2.3.5, any.splitmix ==0.1.0.4, splitmix -optimised-mixer, - any.statistics ==0.16.1.2, + any.statistics ==0.16.2.0, any.stm ==2.5.0.1, - any.streaming-commons ==0.2.2.5, + any.streaming-commons ==0.2.2.6, streaming-commons -use-bytestring-builder, - any.strict ==0.4.0.1, - strict +assoc, + any.strict ==0.5, any.string-interpolate ==0.3.2.0, string-interpolate -bytestring-builder -extended-benchmarks -text-builder, - any.syb ==0.7.2.2, + any.syb ==0.7.2.3, any.tagged ==0.8.7, tagged +deepseq +transformers, any.tasty ==1.4.3, tasty +unix, any.tasty-ant-xml ==1.1.8, - any.tasty-checklist ==1.0.5.0, + any.tasty-checklist ==1.0.6.0, any.tasty-expected-failure ==0.12.3, any.tasty-golden ==2.3.5, tasty-golden -build-example, - any.tasty-hedgehog ==1.4.0.0, + any.tasty-hedgehog ==1.4.0.1, any.tasty-hspec ==1.2.0.3, any.tasty-hunit ==0.10.0.3, any.tasty-quickcheck ==0.10.2, any.tasty-smallcheck ==0.8.2, - any.tasty-sugar ==2.0.1.0, + any.tasty-sugar ==2.1.0.0, any.template-haskell ==2.16.0.0, any.temporary ==1.3, any.terminal-size ==0.3.3, @@ -351,8 +355,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.th-lift-instances ==0.1.20, any.th-orphans ==0.13.14, any.th-reify-many ==0.1.10, - any.these ==1.1.1.1, - these +assoc, + any.these ==1.2, any.time ==1.9.3, any.time-compat ==1.9.6.1, time-compat -old-locale, @@ -370,9 +373,9 @@ constraints: any.BoundedChan ==1.0.3.0, any.unbounded-delays ==0.1.1.1, any.uniplate ==1.6.13, any.unix ==2.7.2.2, - any.unix-compat ==0.6, + any.unix-compat ==0.7, unix-compat -old-time, - any.unix-time ==0.4.8, + any.unix-time ==0.4.9, any.unliftio ==0.2.24.0, any.unliftio-core ==0.2.1.0, any.unordered-containers ==0.2.19.1, @@ -382,22 +385,23 @@ constraints: any.BoundedChan ==1.0.3.0, any.uuid-types ==1.0.5, any.vault ==0.3.1.5, vault +useghc, - any.vector ==0.12.3.1, + any.vector ==0.13.0.0, vector +boundschecks -internalchecks -unsafechecks -wall, any.vector-algorithms ==0.9.0.1, vector-algorithms +bench +boundschecks -internalchecks -llvm +properties -unsafechecks, any.vector-binary-instances ==0.2.5.2, + any.vector-stream ==0.1.0.0, any.vector-th-unbox ==0.2.2, - any.versions ==5.0.4, + any.versions ==5.0.5, any.void ==0.7.3, void -safe, any.wai ==3.2.3, any.wai-extra ==3.1.13.0, wai-extra -build-example, any.wai-logger ==2.4.0, - any.warp ==3.3.24, + any.warp ==3.3.25, warp +allow-sendfilefd -network-bytestring -warp-debug +x509, - any.warp-tls ==3.3.5, + any.warp-tls ==3.3.6, any.weigh ==0.0.16, what4 -drealtestdisable -solvertests -stptestdisable, any.witherable ==0.4.2, @@ -414,4 +418,4 @@ constraints: any.BoundedChan ==1.0.3.0, any.zlib ==0.6.3.0, zlib -bundled-c-zlib -non-blocking-ffi -pkg-config, any.zlib-bindings ==0.1.1.5 -index-state: hackage.haskell.org 2023-03-13T12:18:58Z +index-state: hackage.haskell.org 2023-04-18T11:48:49Z diff --git a/cabal.GHC-8.8.4.config b/cabal.GHC-8.8.4.config index e2415ba6fc..fc70e41d30 100644 --- a/cabal.GHC-8.8.4.config +++ b/cabal.GHC-8.8.4.config @@ -16,21 +16,23 @@ constraints: any.BoundedChan ==1.0.3.0, QuickCheck -old-random +templatehaskell, any.StateVar ==1.2.2, any.adjunctions ==4.4.2, - any.aeson ==2.0.3.0, + any.aeson ==2.1.2.1, aeson -cffi +ordered-keymap, - any.aeson-typescript ==0.4.2.0, - any.alex ==3.2.7.1, - any.ansi-terminal ==0.11.4, + any.aeson-typescript ==0.5.0.0, + any.alex ==3.2.7.3, + any.ansi-terminal ==0.11.5, ansi-terminal -example, + any.ansi-terminal-types ==0.11.5, any.ansi-wl-pprint ==0.6.9, ansi-wl-pprint -example, any.appar ==0.1.8, - any.arithmoi ==0.12.0.2, + any.arithmoi ==0.12.1.0, any.array ==0.5.4.0, any.asn1-encoding ==0.9.6, any.asn1-parse ==0.9.5, any.asn1-types ==0.3.4, - any.assoc ==1.0.2, + any.assoc ==1.1, + assoc +tagged, any.async ==2.2.4, async -bench, any.attoparsec ==0.14.4, @@ -44,12 +46,12 @@ constraints: any.BoundedChan ==1.0.3.0, any.base16-bytestring ==1.0.2.0, any.base64-bytestring ==1.2.1.0, any.basement ==0.0.14, - any.bifunctors ==5.5.15, - bifunctors +semigroups +tagged, + any.bifunctors ==5.6.1, + bifunctors +tagged, any.bimap ==0.5.0, any.binary ==0.8.7.0, any.binary-orphans ==1.0.4.1, - any.bitvec ==1.1.3.0, + any.bitvec ==1.1.4.0, bitvec -libgmp, any.bitwise ==1.0.0.1, any.blaze-builder ==0.4.2.2, @@ -117,7 +119,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.doctest ==0.20.1, any.dotgen ==0.4.3, dotgen -devel, - any.easy-file ==0.2.2, + any.easy-file ==0.2.3, any.either ==5.0.2, any.entropy ==0.4.1.10, entropy -donotgetentropy, @@ -127,22 +129,25 @@ constraints: any.BoundedChan ==1.0.3.0, exceptions +transformers-0-4, any.executable-path ==0.0.3.1, any.extensible-exceptions ==0.1.1.4, - any.extra ==1.7.12, + any.extra ==1.7.13, any.fast-logger ==3.2.1, any.fgl ==5.8.1.1, fgl +containers042, any.fgl-visualize ==0.1.0.1, - any.filelock ==0.1.1.5, + any.filelock ==0.1.1.6, any.filemanip ==0.3.6.3, any.filepath ==1.4.2.1, any.fingertree ==0.1.5.0, - any.free ==5.1.10, + any.foldable1-classes-compat ==0.1, + foldable1-classes-compat +tagged, + any.free ==5.2, any.generic-deriving ==1.14.3, generic-deriving +base-4-9, - any.generic-lens ==2.2.1.0, + any.generic-lens ==2.2.2.0, any.generic-lens-core ==2.2.1.0, any.generic-random ==1.5.0.1, generic-random -enable-inspect, + any.generically ==0.1.1, any.ghc ==8.8.4, any.ghc-boot ==8.8.4, any.ghc-boot-th ==8.8.4, @@ -155,14 +160,14 @@ constraints: any.BoundedChan ==1.0.3.0, any.graphviz ==2999.20.1.0, graphviz -test-parsing, any.happy ==1.20.1.1, - any.hashable ==1.3.5.0, + any.hashable ==1.4.2.0, hashable +integer-gmp -random-initial-seed, - any.hashtables ==1.2.4.2, + any.hashtables ==1.3.1, hashtables -bounds-checking -debug -detailed-profiling -portable -sse42 +unsafe-tricks, any.haskeline ==0.7.5.0, any.haskell-lexer ==1.1.1, any.haskell-src-exts ==1.23.1, - any.haskell-src-meta ==0.8.11, + any.haskell-src-meta ==0.8.12, any.hedgehog ==1.2, any.hedgehog-classes ==0.2.5.4, hedgehog-classes +aeson +comonad +primitive +semirings +vector, @@ -180,8 +185,8 @@ constraints: any.BoundedChan ==1.0.3.0, any.hspec-expectations ==0.8.2, any.http-date ==0.0.11, any.http-types ==0.12.3, - any.http2 ==4.0.0, - http2 -devel -doc -h2spec, + any.http2 ==4.1.2, + http2 -devel -h2spec, any.ieee754 ==0.8.0, any.indexed-profunctors ==0.1.1, any.indexed-traversable ==0.1.2.1, @@ -195,17 +200,17 @@ constraints: any.BoundedChan ==1.0.3.0, any.io-streams ==1.5.2.2, io-streams +network -nointeractivetests +zlib, any.iproute ==1.7.12, - any.itanium-abi ==0.1.1.1, + any.itanium-abi ==0.1.2, any.js-chart ==2.9.4.1, any.json ==0.10, json +generic -mapdict +parsec +pretty +split-base, any.kan-extensions ==5.2.5, - any.kvitable ==1.0.2.0, + any.kvitable ==1.0.2.1, any.language-c99 ==0.2.0, any.language-c99-simple ==0.2.2, any.language-c99-util ==0.2.0, language-rust +enablequasiquotes +usebytestrings, - any.lens ==5.1.1, + any.lens ==5.2.2, lens -benchmark-uniplate -dump-splices +inlining -j +test-hunit +test-properties +test-templates +trustworthy, any.libBF ==0.6.5.1, libBF -system-libbf, @@ -213,20 +218,20 @@ constraints: any.BoundedChan ==1.0.3.0, libffi +ghc-bundled-libffi, any.libyaml ==0.1.2, libyaml -no-unicode -system-libyaml, - any.lifted-async ==0.10.2.3, + any.lifted-async ==0.10.2.4, any.lifted-base ==0.2.3.12, llvm-pretty-bc-parser -fuzz -regressions, any.logict ==0.8.0.0, - any.lucid ==2.11.1, + any.lucid ==2.11.20230408, any.lumberjack ==1.0.2.0, any.math-functions ==0.3.4.2, math-functions +system-erf +system-expm1, - any.megaparsec ==9.0.1, + any.megaparsec ==9.2.1, megaparsec -dev, any.memory ==0.18.0, memory +support_bytestring +support_deepseq, any.microlens ==0.4.13.1, - any.microlens-th ==0.4.3.11, + any.microlens-th ==0.4.3.12, any.microstache ==1.0.2.3, any.mmorph ==1.2.0, any.mod ==0.1.2.2, @@ -265,7 +270,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.prettyprinter ==1.7.1, prettyprinter -buildreadme +text, any.prettyprinter-ansi-terminal ==1.1.3, - any.primitive ==0.7.4.0, + any.primitive ==0.8.0.0, any.process ==1.6.9.0, any.profunctors ==5.6.2, any.psqueues ==0.2.7.3, @@ -281,9 +286,9 @@ constraints: any.BoundedChan ==1.0.3.0, any.regex-compat ==0.95.2.1, any.regex-posix ==0.96.0.1, regex-posix -_regex-posix-clib, - any.resourcet ==1.2.6, + any.resourcet ==1.3.0, any.rts ==1.0, - any.s-cargot ==0.1.5.0, + any.s-cargot ==0.1.6.0, s-cargot -build-example, any.safe ==0.3.19, any.safe-exceptions ==0.1.7.3, @@ -291,7 +296,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.scientific ==0.3.7.0, scientific -bytestring-builder -integer-simple, any.scotty ==0.12.1, - any.semialign ==1.2.0.1, + any.semialign ==1.3, semialign +semigroupoids, any.semigroupoids ==5.3.7, semigroupoids +comonad +containers +contravariant +distributive +tagged +unordered-containers, @@ -309,30 +314,29 @@ constraints: any.BoundedChan ==1.0.3.0, any.split ==0.2.3.5, any.splitmix ==0.1.0.4, splitmix -optimised-mixer, - any.statistics ==0.16.1.2, + any.statistics ==0.16.2.0, any.stm ==2.5.0.0, - any.streaming-commons ==0.2.2.5, + any.streaming-commons ==0.2.2.6, streaming-commons -use-bytestring-builder, - any.strict ==0.4.0.1, - strict +assoc, + any.strict ==0.5, any.string-interpolate ==0.3.2.0, string-interpolate -bytestring-builder -extended-benchmarks -text-builder, - any.syb ==0.7.2.2, + any.syb ==0.7.2.3, any.tagged ==0.8.7, tagged +deepseq +transformers, any.tasty ==1.4.3, tasty +unix, any.tasty-ant-xml ==1.1.8, - any.tasty-checklist ==1.0.5.0, + any.tasty-checklist ==1.0.6.0, any.tasty-expected-failure ==0.12.3, any.tasty-golden ==2.3.5, tasty-golden -build-example, - any.tasty-hedgehog ==1.4.0.0, + any.tasty-hedgehog ==1.4.0.1, any.tasty-hspec ==1.2.0.3, any.tasty-hunit ==0.10.0.3, any.tasty-quickcheck ==0.10.2, any.tasty-smallcheck ==0.8.2, - any.tasty-sugar ==2.0.1.0, + any.tasty-sugar ==2.1.0.0, any.template-haskell ==2.15.0.0, any.temporary ==1.3, any.terminal-size ==0.3.3, @@ -352,8 +356,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.th-lift-instances ==0.1.20, any.th-orphans ==0.13.14, any.th-reify-many ==0.1.10, - any.these ==1.1.1.1, - these +assoc, + any.these ==1.2, any.time ==1.9.3, any.time-compat ==1.9.6.1, time-compat -old-locale, @@ -371,9 +374,9 @@ constraints: any.BoundedChan ==1.0.3.0, any.unbounded-delays ==0.1.1.1, any.uniplate ==1.6.13, any.unix ==2.7.2.2, - any.unix-compat ==0.6, + any.unix-compat ==0.7, unix-compat -old-time, - any.unix-time ==0.4.8, + any.unix-time ==0.4.9, any.unliftio ==0.2.24.0, any.unliftio-core ==0.2.1.0, any.unordered-containers ==0.2.19.1, @@ -383,22 +386,23 @@ constraints: any.BoundedChan ==1.0.3.0, any.uuid-types ==1.0.5, any.vault ==0.3.1.5, vault +useghc, - any.vector ==0.12.3.1, + any.vector ==0.13.0.0, vector +boundschecks -internalchecks -unsafechecks -wall, any.vector-algorithms ==0.9.0.1, vector-algorithms +bench +boundschecks -internalchecks -llvm +properties -unsafechecks, any.vector-binary-instances ==0.2.5.2, + any.vector-stream ==0.1.0.0, any.vector-th-unbox ==0.2.2, - any.versions ==5.0.4, + any.versions ==5.0.5, any.void ==0.7.3, void -safe, any.wai ==3.2.3, any.wai-extra ==3.1.13.0, wai-extra -build-example, any.wai-logger ==2.4.0, - any.warp ==3.3.24, + any.warp ==3.3.25, warp +allow-sendfilefd -network-bytestring -warp-debug +x509, - any.warp-tls ==3.3.5, + any.warp-tls ==3.3.6, any.weigh ==0.0.16, what4 -drealtestdisable -solvertests -stptestdisable, any.witherable ==0.4.2, @@ -415,4 +419,4 @@ constraints: any.BoundedChan ==1.0.3.0, any.zlib ==0.6.3.0, zlib -bundled-c-zlib -non-blocking-ffi -pkg-config, any.zlib-bindings ==0.1.1.5 -index-state: hackage.haskell.org 2023-03-13T12:18:58Z +index-state: hackage.haskell.org 2023-04-18T11:48:49Z diff --git a/cabal.GHC-9.2.7.config b/cabal.GHC-9.2.7.config index 461fe2cb89..81c75892c2 100644 --- a/cabal.GHC-9.2.7.config +++ b/cabal.GHC-9.2.7.config @@ -10,27 +10,29 @@ constraints: any.BoundedChan ==1.0.3.0, any.MemoTrie ==0.6.10, MemoTrie -examples, any.MonadRandom ==0.6, - any.OneTuple ==0.3.1, + any.OneTuple ==0.4.1.1, any.Only ==0.1, any.QuickCheck ==2.14.2, QuickCheck -old-random +templatehaskell, any.StateVar ==1.2.2, any.adjunctions ==4.4.2, - any.aeson ==2.0.3.0, + any.aeson ==2.1.2.1, aeson -cffi +ordered-keymap, - any.aeson-typescript ==0.4.2.0, - any.alex ==3.2.7.1, - any.ansi-terminal ==0.11.4, + any.aeson-typescript ==0.5.0.0, + any.alex ==3.2.7.3, + any.ansi-terminal ==0.11.5, ansi-terminal -example, + any.ansi-terminal-types ==0.11.5, any.ansi-wl-pprint ==0.6.9, ansi-wl-pprint -example, any.appar ==0.1.8, - any.arithmoi ==0.12.0.2, + any.arithmoi ==0.12.1.0, any.array ==0.5.4.0, any.asn1-encoding ==0.9.6, any.asn1-parse ==0.9.5, any.asn1-types ==0.3.4, - any.assoc ==1.0.2, + any.assoc ==1.1, + assoc +tagged, any.async ==2.2.4, async -bench, any.attoparsec ==0.14.4, @@ -44,12 +46,12 @@ constraints: any.BoundedChan ==1.0.3.0, any.base16-bytestring ==1.0.2.0, any.base64-bytestring ==1.2.1.0, any.basement ==0.0.15, - any.bifunctors ==5.5.15, - bifunctors +semigroups +tagged, + any.bifunctors ==5.6.1, + bifunctors +tagged, any.bimap ==0.5.0, any.binary ==0.8.9.0, any.binary-orphans ==1.0.4.1, - any.bitvec ==1.1.3.0, + any.bitvec ==1.1.4.0, bitvec -libgmp, any.bitwise ==1.0.0.1, any.blaze-builder ==0.4.2.2, @@ -117,7 +119,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.doctest ==0.20.1, any.dotgen ==0.4.3, dotgen -devel, - any.easy-file ==0.2.2, + any.easy-file ==0.2.3, any.either ==5.0.2, any.entropy ==0.4.1.10, entropy -donotgetentropy, @@ -126,22 +128,25 @@ constraints: any.BoundedChan ==1.0.3.0, any.exceptions ==0.10.4, any.executable-path ==0.0.3.1, any.extensible-exceptions ==0.1.1.4, - any.extra ==1.7.12, + any.extra ==1.7.13, any.fast-logger ==3.2.1, any.fgl ==5.8.1.1, fgl +containers042, any.fgl-visualize ==0.1.0.1, - any.filelock ==0.1.1.5, + any.filelock ==0.1.1.6, any.filemanip ==0.3.6.3, any.filepath ==1.4.2.2, any.fingertree ==0.1.5.0, - any.free ==5.1.10, + any.foldable1-classes-compat ==0.1, + foldable1-classes-compat +tagged, + any.free ==5.2, any.generic-deriving ==1.14.3, generic-deriving +base-4-9, - any.generic-lens ==2.2.1.0, + any.generic-lens ==2.2.2.0, any.generic-lens-core ==2.2.1.0, any.generic-random ==1.5.0.1, generic-random -enable-inspect, + any.generically ==0.1.1, any.ghc ==9.2.7, any.ghc-bignum ==1.2, any.ghc-boot ==9.2.7, @@ -155,14 +160,14 @@ constraints: any.BoundedChan ==1.0.3.0, any.graphviz ==2999.20.1.0, graphviz -test-parsing, any.happy ==1.20.1.1, - any.hashable ==1.3.5.0, + any.hashable ==1.4.2.0, hashable +integer-gmp -random-initial-seed, - any.hashtables ==1.2.4.2, + any.hashtables ==1.3.1, hashtables -bounds-checking -debug -detailed-profiling -portable -sse42 +unsafe-tricks, any.haskeline ==0.8.2, any.haskell-lexer ==1.1.1, any.haskell-src-exts ==1.23.1, - any.haskell-src-meta ==0.8.11, + any.haskell-src-meta ==0.8.12, any.hedgehog ==1.2, any.hedgehog-classes ==0.2.5.4, hedgehog-classes +aeson +comonad +primitive +semirings +vector, @@ -180,8 +185,8 @@ constraints: any.BoundedChan ==1.0.3.0, any.hspec-expectations ==0.8.2, any.http-date ==0.0.11, any.http-types ==0.12.3, - any.http2 ==4.0.0, - http2 -devel -doc -h2spec, + any.http2 ==4.1.2, + http2 -devel -h2spec, any.ieee754 ==0.8.0, any.indexed-profunctors ==0.1.1, any.indexed-traversable ==0.1.2.1, @@ -195,17 +200,17 @@ constraints: any.BoundedChan ==1.0.3.0, any.io-streams ==1.5.2.2, io-streams +network -nointeractivetests +zlib, any.iproute ==1.7.12, - any.itanium-abi ==0.1.1.1, + any.itanium-abi ==0.1.2, any.js-chart ==2.9.4.1, any.json ==0.10, json +generic -mapdict +parsec +pretty +split-base, any.kan-extensions ==5.2.5, - any.kvitable ==1.0.2.0, + any.kvitable ==1.0.2.1, any.language-c99 ==0.2.0, any.language-c99-simple ==0.2.2, any.language-c99-util ==0.2.0, language-rust +enablequasiquotes +usebytestrings, - any.lens ==5.1.1, + any.lens ==5.2.2, lens -benchmark-uniplate -dump-splices +inlining -j +test-hunit +test-properties +test-templates +trustworthy, any.libBF ==0.6.5.1, libBF -system-libbf, @@ -213,20 +218,20 @@ constraints: any.BoundedChan ==1.0.3.0, libffi +ghc-bundled-libffi, any.libyaml ==0.1.2, libyaml -no-unicode -system-libyaml, - any.lifted-async ==0.10.2.3, + any.lifted-async ==0.10.2.4, any.lifted-base ==0.2.3.12, llvm-pretty-bc-parser -fuzz -regressions, any.logict ==0.8.0.0, - any.lucid ==2.11.1, + any.lucid ==2.11.20230408, any.lumberjack ==1.0.2.0, any.math-functions ==0.3.4.2, math-functions +system-erf +system-expm1, - any.megaparsec ==9.0.1, + any.megaparsec ==9.3.0, megaparsec -dev, any.memory ==0.18.0, memory +support_bytestring +support_deepseq, any.microlens ==0.4.13.1, - any.microlens-th ==0.4.3.11, + any.microlens-th ==0.4.3.12, any.microstache ==1.0.2.3, any.mmorph ==1.2.0, any.mod ==0.2.0.1, @@ -265,7 +270,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.prettyprinter ==1.7.1, prettyprinter -buildreadme +text, any.prettyprinter-ansi-terminal ==1.1.3, - any.primitive ==0.7.4.0, + any.primitive ==0.8.0.0, any.process ==1.6.16.0, any.profunctors ==5.6.2, any.psqueues ==0.2.7.3, @@ -281,9 +286,9 @@ constraints: any.BoundedChan ==1.0.3.0, any.regex-compat ==0.95.2.1, any.regex-posix ==0.96.0.1, regex-posix -_regex-posix-clib, - any.resourcet ==1.2.6, + any.resourcet ==1.3.0, any.rts ==1.0.2, - any.s-cargot ==0.1.5.0, + any.s-cargot ==0.1.6.0, s-cargot -build-example, any.safe ==0.3.19, any.safe-exceptions ==0.1.7.3, @@ -291,7 +296,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.scientific ==0.3.7.0, scientific -bytestring-builder -integer-simple, any.scotty ==0.12.1, - any.semialign ==1.2.0.1, + any.semialign ==1.3, semialign +semigroupoids, any.semigroupoids ==5.3.7, semigroupoids +comonad +containers +contravariant +distributive +tagged +unordered-containers, @@ -309,30 +314,29 @@ constraints: any.BoundedChan ==1.0.3.0, any.split ==0.2.3.5, any.splitmix ==0.1.0.4, splitmix -optimised-mixer, - any.statistics ==0.16.1.2, + any.statistics ==0.16.2.0, any.stm ==2.5.0.2, - any.streaming-commons ==0.2.2.5, + any.streaming-commons ==0.2.2.6, streaming-commons -use-bytestring-builder, - any.strict ==0.4.0.1, - strict +assoc, + any.strict ==0.5, any.string-interpolate ==0.3.2.0, string-interpolate -bytestring-builder -extended-benchmarks -text-builder, - any.syb ==0.7.2.2, + any.syb ==0.7.2.3, any.tagged ==0.8.7, tagged +deepseq +transformers, any.tasty ==1.4.3, tasty +unix, any.tasty-ant-xml ==1.1.8, - any.tasty-checklist ==1.0.5.0, + any.tasty-checklist ==1.0.6.0, any.tasty-expected-failure ==0.12.3, any.tasty-golden ==2.3.5, tasty-golden -build-example, - any.tasty-hedgehog ==1.4.0.0, + any.tasty-hedgehog ==1.4.0.1, any.tasty-hspec ==1.2.0.3, any.tasty-hunit ==0.10.0.3, any.tasty-quickcheck ==0.10.2, any.tasty-smallcheck ==0.8.2, - any.tasty-sugar ==2.0.1.0, + any.tasty-sugar ==2.1.0.0, any.template-haskell ==2.18.0.0, any.temporary ==1.3, any.terminal-size ==0.3.3, @@ -352,8 +356,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.th-lift-instances ==0.1.20, any.th-orphans ==0.13.14, any.th-reify-many ==0.1.10, - any.these ==1.1.1.1, - these +assoc, + any.these ==1.2, any.time ==1.11.1.1, any.time-compat ==1.9.6.1, time-compat -old-locale, @@ -371,9 +374,9 @@ constraints: any.BoundedChan ==1.0.3.0, any.unbounded-delays ==0.1.1.1, any.uniplate ==1.6.13, any.unix ==2.7.2.2, - any.unix-compat ==0.6, + any.unix-compat ==0.7, unix-compat -old-time, - any.unix-time ==0.4.8, + any.unix-time ==0.4.9, any.unliftio ==0.2.24.0, any.unliftio-core ==0.2.1.0, any.unordered-containers ==0.2.19.1, @@ -383,22 +386,23 @@ constraints: any.BoundedChan ==1.0.3.0, any.uuid-types ==1.0.5, any.vault ==0.3.1.5, vault +useghc, - any.vector ==0.12.3.1, + any.vector ==0.13.0.0, vector +boundschecks -internalchecks -unsafechecks -wall, any.vector-algorithms ==0.9.0.1, vector-algorithms +bench +boundschecks -internalchecks -llvm +properties -unsafechecks, any.vector-binary-instances ==0.2.5.2, + any.vector-stream ==0.1.0.0, any.vector-th-unbox ==0.2.2, - any.versions ==5.0.4, + any.versions ==5.0.5, any.void ==0.7.3, void -safe, any.wai ==3.2.3, any.wai-extra ==3.1.13.0, wai-extra -build-example, any.wai-logger ==2.4.0, - any.warp ==3.3.24, + any.warp ==3.3.25, warp +allow-sendfilefd -network-bytestring -warp-debug +x509, - any.warp-tls ==3.3.5, + any.warp-tls ==3.3.6, any.weigh ==0.0.16, what4 -drealtestdisable -solvertests -stptestdisable, any.witherable ==0.4.2, @@ -415,4 +419,4 @@ constraints: any.BoundedChan ==1.0.3.0, any.zlib ==0.6.3.0, zlib -bundled-c-zlib -non-blocking-ffi -pkg-config, any.zlib-bindings ==0.1.1.5 -index-state: hackage.haskell.org 2023-03-13T12:18:58Z +index-state: hackage.haskell.org 2023-04-18T11:48:49Z From eaaec0010acf589e3a8ab405a009dcd0166e0431 Mon Sep 17 00:00:00 2001 From: Ryan Scott Date: Sun, 2 Apr 2023 08:39:11 -0400 Subject: [PATCH 6/7] CI: Test GHC 9.4.4, drop 8.8.4 --- .github/workflows/ci.yml | 13 +--- README.md | 2 +- ...GHC-8.8.4.config => cabal.GHC-9.4.4.config | 68 +++++++++---------- saw-remote-api/Dockerfile | 10 +-- saw/Dockerfile | 10 +-- 5 files changed, 46 insertions(+), 57 deletions(-) rename cabal.GHC-8.8.4.config => cabal.GHC-9.4.4.config (92%) diff --git a/.github/workflows/ci.yml b/.github/workflows/ci.yml index 77515d6453..dfe38459f8 100644 --- a/.github/workflows/ci.yml +++ b/.github/workflows/ci.yml @@ -69,7 +69,7 @@ jobs: matrix: os: [ubuntu-22.04, macos-12, windows-latest] cabal: ["3.10.1.0"] - ghc: ["8.8.4", "8.10.7", "9.2.7"] + ghc: ["8.10.7", "9.2.7", "9.4.4"] run-tests: [true] include: # We include one job from an older Ubuntu LTS release to increase our @@ -79,17 +79,6 @@ jobs: ghc: "8.10.7" cabal: "3.10.1.0" run-tests: false - exclude: - # Exclude 8.8 on macOS 12 due to - # https://gitlab.haskell.org/ghc/ghc/-/issues/18446 - - os: macos-12 - ghc: "8.8.4" - cabal: "3.10.1.0" - run-tests: true - - os: windows-latest - ghc: "8.8.4" - cabal: "3.10.1.0" - run-tests: true outputs: cabal-test-suites-json: ${{ steps.cabal-test-suites.outputs.targets-json }} steps: diff --git a/README.md b/README.md index c8748ad3db..e53dfc7bda 100644 --- a/README.md +++ b/README.md @@ -43,7 +43,7 @@ To build SAWScript and related utilities from source: * Ensure that you have the `cabal` and `ghc` executables in your `PATH`. If you don't already have them, we recommend using `ghcup` to install them: . We recommend - Cabal 3.4 or newer, and GHC 8.8, 8.10, or 9.2. + Cabal 3.4 or newer, and GHC 8.10, 9.2, or 9.4. * Ensure that you have the C libraries and header files for `terminfo`, which generally comes as part of `ncurses` on most diff --git a/cabal.GHC-8.8.4.config b/cabal.GHC-9.4.4.config similarity index 92% rename from cabal.GHC-8.8.4.config rename to cabal.GHC-9.4.4.config index fc70e41d30..241bb28fce 100644 --- a/cabal.GHC-8.8.4.config +++ b/cabal.GHC-9.4.4.config @@ -1,6 +1,7 @@ active-repositories: hackage.haskell.org:merge constraints: any.BoundedChan ==1.0.3.0, - any.Cabal ==3.0.1.0, + any.Cabal ==3.8.1.0, + any.Cabal-syntax ==3.8.1.0, any.Glob ==0.10.2, any.GraphSCC ==1.0.4, GraphSCC -use-maps, @@ -10,7 +11,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.MemoTrie ==0.6.10, MemoTrie -examples, any.MonadRandom ==0.6, - any.OneTuple ==0.3.1, + any.OneTuple ==0.4.1.1, any.Only ==0.1, any.QuickCheck ==2.14.2, QuickCheck -old-random +templatehaskell, @@ -39,17 +40,17 @@ constraints: any.BoundedChan ==1.0.3.0, attoparsec -developer, any.auto-update ==0.1.6, any.barbies ==2.0.4.0, - any.base ==4.13.0.0, + any.base ==4.17.0.0, any.base-compat ==0.12.2, any.base-compat-batteries ==0.12.2, any.base-orphans ==0.8.8.2, any.base16-bytestring ==1.0.2.0, any.base64-bytestring ==1.2.1.0, - any.basement ==0.0.14, + any.basement ==0.0.15, any.bifunctors ==5.6.1, bifunctors +tagged, any.bimap ==0.5.0, - any.binary ==0.8.7.0, + any.binary ==0.8.9.1, any.binary-orphans ==1.0.4.1, any.bitvec ==1.1.4.0, bitvec -libgmp, @@ -61,7 +62,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.bsb-http-chunked ==0.0.0.4, any.bv-sized ==1.0.5, any.byteorder ==1.0.4, - any.bytestring ==0.10.10.1, + any.bytestring ==0.11.3.1, any.cabal-doctest ==1.0.9, any.call-stack ==0.4.0, any.case-insensitive ==1.2.1.0, @@ -84,7 +85,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.config-schema ==1.3.0.0, any.config-value ==0.8.3, any.constraints ==0.13.4, - any.containers ==0.6.2.1, + any.containers ==0.6.6, any.contravariant ==1.5.5, contravariant +semigroups +statevar +tagged, any.cookie ==0.4.6, @@ -102,16 +103,15 @@ constraints: any.BoundedChan ==1.0.3.0, any.cryptonite-conduit ==0.2.2, any.data-accessor ==0.2.3.1, data-accessor +category +monadfail +splitbase, - any.data-array-byte ==0.1.0.1, any.data-default-class ==0.1.2.0, any.data-fix ==0.3.2, any.data-inttrie ==0.1.4, any.data-ref ==0.1, - any.deepseq ==1.4.4.0, + any.deepseq ==1.4.8.0, any.dense-linear-algebra ==0.1.0.0, any.deriving-compat ==0.6.3, deriving-compat +base-4-9 +new-functor-classes +template-haskell-2-11, - any.directory ==1.3.6.0, + any.directory ==1.3.7.1, any.distributive ==0.6.2.1, distributive +semigroups +tagged, any.dlist ==1.0, @@ -125,8 +125,7 @@ constraints: any.BoundedChan ==1.0.3.0, entropy -donotgetentropy, any.erf ==2.0.0.0, any.exact-pi ==0.5.0.2, - any.exceptions ==0.10.7, - exceptions +transformers-0-4, + any.exceptions ==0.10.5, any.executable-path ==0.0.3.1, any.extensible-exceptions ==0.1.1.4, any.extra ==1.7.13, @@ -136,7 +135,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.fgl-visualize ==0.1.0.1, any.filelock ==0.1.1.6, any.filemanip ==0.3.6.3, - any.filepath ==1.4.2.1, + any.filepath ==1.4.2.2, any.fingertree ==0.1.5.0, any.foldable1-classes-compat ==0.1, foldable1-classes-compat +tagged, @@ -148,13 +147,14 @@ constraints: any.BoundedChan ==1.0.3.0, any.generic-random ==1.5.0.1, generic-random -enable-inspect, any.generically ==0.1.1, - any.ghc ==8.8.4, - any.ghc-boot ==8.8.4, - any.ghc-boot-th ==8.8.4, - any.ghc-heap ==8.8.4, + any.ghc ==9.4.4, + any.ghc-bignum ==1.3, + any.ghc-boot ==9.4.4, + any.ghc-boot-th ==9.4.4, + any.ghc-heap ==9.4.4, any.ghc-paths ==0.1.0.12, - any.ghc-prim ==0.5.3, - any.ghci ==8.8.4, + any.ghc-prim ==0.9.0, + any.ghci ==9.4.4, any.githash ==0.1.6.3, any.gitrev ==1.3.1, any.graphviz ==2999.20.1.0, @@ -164,7 +164,7 @@ constraints: any.BoundedChan ==1.0.3.0, hashable +integer-gmp -random-initial-seed, any.hashtables ==1.3.1, hashtables -bounds-checking -debug -detailed-profiling -portable -sse42 +unsafe-tricks, - any.haskeline ==0.7.5.0, + any.haskeline ==0.8.2, any.haskell-lexer ==1.1.1, any.haskell-src-exts ==1.23.1, any.haskell-src-meta ==0.8.12, @@ -176,7 +176,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.hobbits ==1.4, any.hostname ==1.0, any.hourglass ==0.2.12, - any.hpc ==0.6.0.3, + any.hpc ==0.6.1.0, any.hsc2hs ==0.68.9, hsc2hs -in-ghc-tree, any.hspec ==2.10.10, @@ -191,7 +191,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.indexed-profunctors ==0.1.1, any.indexed-traversable ==0.1.2.1, any.indexed-traversable-instances ==0.1.1.2, - any.integer-gmp ==1.0.2.0, + any.integer-gmp ==1.1, any.integer-logarithms ==1.0.3.1, integer-logarithms -check-bounds +integer-gmp, any.integer-roots ==1.0.2.0, @@ -226,7 +226,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.lumberjack ==1.0.2.0, any.math-functions ==0.3.4.2, math-functions +system-erf +system-expm1, - any.megaparsec ==9.2.1, + any.megaparsec ==9.3.0, megaparsec -dev, any.memory ==0.18.0, memory +support_bytestring +support_deepseq, @@ -234,9 +234,9 @@ constraints: any.BoundedChan ==1.0.3.0, any.microlens-th ==0.4.3.12, any.microstache ==1.0.2.3, any.mmorph ==1.2.0, - any.mod ==0.1.2.2, + any.mod ==0.2.0.1, mod +semirings +vector, - any.modern-uri ==0.3.4.4, + any.modern-uri ==0.3.6.0, modern-uri -dev, any.monad-control ==1.0.3.1, any.monadLib ==3.10.1, @@ -259,7 +259,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.panic ==0.4.0.1, any.parallel ==3.2.2.0, parameterized-utils +unsafe-operations, - any.parsec ==3.1.14.0, + any.parsec ==3.1.15.0, any.parser-combinators ==1.3.0, parser-combinators -dev, any.pem ==0.2.4, @@ -271,7 +271,7 @@ constraints: any.BoundedChan ==1.0.3.0, prettyprinter -buildreadme +text, any.prettyprinter-ansi-terminal ==1.1.3, any.primitive ==0.8.0.0, - any.process ==1.6.9.0, + any.process ==1.6.16.0, any.profunctors ==5.6.2, any.psqueues ==0.2.7.3, any.quickcheck-instances ==0.3.29.1, @@ -287,7 +287,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.regex-posix ==0.96.0.1, regex-posix -_regex-posix-clib, any.resourcet ==1.3.0, - any.rts ==1.0, + any.rts ==1.0.2, any.s-cargot ==0.1.6.0, s-cargot -build-example, any.safe ==0.3.19, @@ -315,7 +315,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.splitmix ==0.1.0.4, splitmix -optimised-mixer, any.statistics ==0.16.2.0, - any.stm ==2.5.0.0, + any.stm ==2.5.1.0, any.streaming-commons ==0.2.2.6, streaming-commons -use-bytestring-builder, any.strict ==0.5, @@ -337,14 +337,14 @@ constraints: any.BoundedChan ==1.0.3.0, any.tasty-quickcheck ==0.10.2, any.tasty-smallcheck ==0.8.2, any.tasty-sugar ==2.1.0.0, - any.template-haskell ==2.15.0.0, + any.template-haskell ==2.19.0.0, any.temporary ==1.3, any.terminal-size ==0.3.3, - any.terminfo ==0.4.1.4, + any.terminfo ==0.4.1.5, any.test-framework ==0.8.2.0, any.test-framework-hunit ==0.3.0.2, test-framework-hunit -base3 +base4, - any.text ==1.2.4.0, + any.text ==2.0.1, any.text-conversions ==0.3.1.1, any.text-short ==0.1.5, text-short -asserts, @@ -357,7 +357,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.th-orphans ==0.13.14, any.th-reify-many ==0.1.10, any.these ==1.2, - any.time ==1.9.3, + any.time ==1.12.2, any.time-compat ==1.9.6.1, time-compat -old-locale, any.time-manager ==0.0.0, @@ -373,7 +373,7 @@ constraints: any.BoundedChan ==1.0.3.0, any.typed-process ==0.2.11.0, any.unbounded-delays ==0.1.1.1, any.uniplate ==1.6.13, - any.unix ==2.7.2.2, + any.unix ==2.7.3, any.unix-compat ==0.7, unix-compat -old-time, any.unix-time ==0.4.9, diff --git a/saw-remote-api/Dockerfile b/saw-remote-api/Dockerfile index 2cef115912..4edb29eddd 100644 --- a/saw-remote-api/Dockerfile +++ b/saw-remote-api/Dockerfile @@ -14,16 +14,16 @@ USER saw WORKDIR /home/saw ENV LANG=C.UTF-8 \ LC_ALL=C.UTF-8 -COPY cabal.GHC-8.8.4.config cabal.project.freeze +COPY cabal.GHC-8.10.7.config cabal.project.freeze ENV PATH=/home/saw/ghcup-download/bin:/home/saw/.ghcup/bin:$PATH RUN mkdir -p /home/saw/ghcup-download/bin && \ - curl -L https://downloads.haskell.org/~ghcup/0.1.17.7/x86_64-linux-ghcup-0.1.17.7 -o /home/saw/ghcup-download/bin/ghcup && \ + curl -L https://downloads.haskell.org/~ghcup/0.1.19.2/x86_64-linux-ghcup-0.1.19.2 -o /home/saw/ghcup-download/bin/ghcup && \ chmod +x /home/saw/ghcup-download/bin/ghcup RUN mkdir -p /home/saw/.ghcup && \ ghcup --version && \ - ghcup install cabal 3.6.2.0 && \ - ghcup install ghc 8.8.4 && \ - ghcup set ghc 8.8.4 + ghcup install cabal 3.8.1.0 && \ + ghcup install ghc 8.10.7 && \ + ghcup set ghc 8.10.7 RUN cabal v2-update && cabal v2-build -j exe:saw-remote-api RUN mkdir -p /home/saw/rootfs/usr/local/bin RUN cp $(cabal v2-exec which saw-remote-api) /home/saw/rootfs/usr/local/bin/saw-remote-api diff --git a/saw/Dockerfile b/saw/Dockerfile index 13998eda67..db0f05e4a6 100644 --- a/saw/Dockerfile +++ b/saw/Dockerfile @@ -14,16 +14,16 @@ USER saw WORKDIR /home/saw ENV LANG=C.UTF-8 \ LC_ALL=C.UTF-8 -COPY cabal.GHC-8.8.4.config cabal.project.freeze +COPY cabal.GHC-8.10.7.config cabal.project.freeze ENV PATH=/home/saw/ghcup-download/bin:/home/saw/.ghcup/bin:$PATH RUN mkdir -p /home/saw/ghcup-download/bin && \ - curl -L https://downloads.haskell.org/~ghcup/0.1.17.7/x86_64-linux-ghcup-0.1.17.7 -o /home/saw/ghcup-download/bin/ghcup && \ + curl -L https://downloads.haskell.org/~ghcup/0.1.19.2/x86_64-linux-ghcup-0.1.19.2 -o /home/saw/ghcup-download/bin/ghcup && \ chmod +x /home/saw/ghcup-download/bin/ghcup RUN mkdir -p /home/saw/.ghcup && \ ghcup --version && \ - ghcup install cabal 3.6.2.0 && \ - ghcup install ghc 8.8.4 && \ - ghcup set ghc 8.8.4 + ghcup install cabal 3.8.1.0 && \ + ghcup install ghc 8.10.7 && \ + ghcup set ghc 8.10.7 RUN cabal v2-update RUN cabal v2-build RUN mkdir -p /home/saw/rootfs/usr/local/bin From e19c9cb4bae511026ff9dbca866f78bce989c2ca Mon Sep 17 00:00:00 2001 From: Andrei Date: Fri, 26 May 2023 08:21:34 +0000 Subject: [PATCH 7/7] Bump aws-lc-verification. --- s2nTests/docker/awslc.dockerfile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/s2nTests/docker/awslc.dockerfile b/s2nTests/docker/awslc.dockerfile index 2bbecd6093..863f5ea385 100644 --- a/s2nTests/docker/awslc.dockerfile +++ b/s2nTests/docker/awslc.dockerfile @@ -10,7 +10,7 @@ WORKDIR /saw-script RUN mkdir -p /saw-script && \ git clone https://github.com/GaloisInc/aws-lc-verification.git && \ cd aws-lc-verification && \ - git checkout 1dcf4258305ce17592fb5b90a1c7b638e6bdff9e && \ + git checkout 9b966bcc4b902298f51372782923716faa7c738a && \ git config --file=.gitmodules submodule.src.url https://github.com/awslabs/aws-lc && \ git submodule sync && \ git submodule update --init