Skip to content

Commit

Permalink
Make it build with ghc 9.10
Browse files Browse the repository at this point in the history
  • Loading branch information
erikd committed Jun 19, 2024
1 parent a94bffd commit 1cf0419
Show file tree
Hide file tree
Showing 17 changed files with 72 additions and 13 deletions.
23 changes: 21 additions & 2 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -14,9 +14,9 @@ repository cardano-haskell-packages
-- update either of these.
index-state:
-- Bump both the following dates if you need newer packages from Hackage
, hackage.haskell.org 2024-01-08T22:38:30Z
, hackage.haskell.org 2024-06-19T00:51:44Z
-- Bump this if you need newer packages from CHaP
, cardano-haskell-packages 2024-01-16T11:00:00Z
, cardano-haskell-packages 2024-06-18T12:42:43Z

packages: doc/read-the-docs-site
plutus-benchmark
Expand Down Expand Up @@ -82,3 +82,22 @@ allow-newer:
, inline-r:bytestring
, inline-r:containers
, inline-r:primitive


-- -------------------------------------------------------------------------------------------------
-- Following currently required for building with ghc-9.10.
-- Everything below should be removed before this is merged.
-- The following git commits are changed often enough that it is not even worth adding
-- the Nix SHA hashes.
-- Currently building this with ghc-9.6 and ghc-9.10.

constraints:
-- The API has changed for version 2.2, and there is no intention to change to that
-- version until after Conway.
, cardano-crypto-class ^>= 2.1
-- API chnages require this.
, nothunks ^>= 0.1.5

allow-newer:
, nothunks:containers

2 changes: 1 addition & 1 deletion plutus-benchmark/plutus-benchmark.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -471,7 +471,7 @@ library marlowe-internal
build-depends:
, base
, bytestring
, cardano-crypto-class >=2.0.0.1 && <2.3
, cardano-crypto-class >=2.0.0.1 && <2.2
, directory
, filepath
, mtl
Expand Down
3 changes: 3 additions & 0 deletions plutus-core/cost-model/budgeting-bench/Generators.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{- | Generators for various types of data for benchmarking built-in functions -}

module Generators where
Expand All @@ -10,7 +11,9 @@ import Control.Monad
import Data.Bits
import Data.ByteString (ByteString)
import Data.Int (Int64)
#if !MIN_VERSION_base(4,20,0)
import Data.List (foldl')
#endif
import Data.Text (Text)
import Data.Word (Word64)

Expand Down
2 changes: 1 addition & 1 deletion plutus-core/plutus-core.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -291,7 +291,7 @@ library
, bytestring
, bytestring-strict-builder
, cardano-crypto
, cardano-crypto-class ^>=2.1.2
, cardano-crypto-class ^>= 2.1
, cassava
, cborg
, composition-prelude >=1.1.0.1
Expand Down
5 changes: 4 additions & 1 deletion plutus-core/plutus-core/src/PlutusCore/Name/UniqueMap.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{- | A type for maps (key-value associations), where the key type can be
identified by 'Unique's. In practice, these types are usually names.
This approach is preferred when it is more efficient to compare the associated
Expand All @@ -23,7 +24,9 @@ module PlutusCore.Name.UniqueMap (
import Control.Lens (view)
import Control.Lens.Getter ((^.))
import Data.Coerce (Coercible, coerce)
import Data.Foldable (foldl')
#if ! MIN_VERSION_base(4,20,0)
import Data.List (foldl')
#endif
import Data.IntMap.Strict qualified as IM
import PlutusCore.Name.Unique (HasText (..), HasUnique (..), Named (Named), Unique (Unique))
import PlutusCore.Name.UniqueSet (UniqueSet (UniqueSet))
Expand Down
5 changes: 4 additions & 1 deletion plutus-core/plutus-core/src/PlutusCore/Name/UniqueSet.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{- | A type for sets of things identified by 'Unique's, usually names.
This approach is preferred when it is more efficient to compare the associated
'Unique's instead of the underlying type.
Expand All @@ -23,7 +24,9 @@ module PlutusCore.Name.UniqueSet (
import Control.Lens (Getting, view)
import Control.Lens.Getter (views)
import Data.Coerce (Coercible, coerce)
import Data.Foldable (foldl')
#if ! MIN_VERSION_base(4,20,0)
import Data.List (foldl')
#endif
import Data.IntSet qualified as IS
import Data.IntSet.Lens qualified as IS
import PlutusCore.Name.Unique (HasUnique (..), Unique (Unique))
Expand Down
11 changes: 5 additions & 6 deletions plutus-core/plutus-core/src/Universe/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -547,13 +547,12 @@ these constraints on arguments do not get used in the polymorphic case only mean
get ignored.
-}
type Permits :: forall k. (Type -> Constraint) -> k -> Constraint
type family Permits
type family Permits constr

-- Implicit pattern matching on the kind.
type instance Permits = Permits0
type instance Permits = Permits1
type instance Permits = Permits2
type instance Permits = Permits3
type instance Permits @Type constr = Permits0 constr
type instance Permits @(Type -> Type) constr = Permits1 constr
type instance Permits @(Type -> Type -> Type) constr = Permits2 constr
type instance Permits @(Type -> Type -> Type -> Type) constr = Permits3 constr

-- We can't use @All (Everywhere uni) constrs@, because 'Everywhere' is an associated type family
-- and can't be partially applied, so we have to inline the definition here.
Expand Down
3 changes: 3 additions & 0 deletions plutus-core/plutus-ir/src/PlutusIR/Compiler/Definitions.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
Expand Down Expand Up @@ -56,7 +57,9 @@ import Algebra.Graph.NonEmpty.AdjacencyMap qualified as NAM
import Algebra.Graph.ToGraph qualified as Graph

import Data.Bifunctor (first, second)
#if !MIN_VERSION_base(4,20,0)
import Data.Foldable
#endif
import Data.Map qualified as Map
import Data.Maybe
import Data.Set qualified as Set
Expand Down
3 changes: 3 additions & 0 deletions plutus-core/plutus-ir/src/PlutusIR/Compiler/Names.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,14 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module PlutusIR.Compiler.Names (safeFreshName, safeFreshTyName) where

import PlutusCore qualified as PLC
import PlutusCore.Name.Unique (isQuotedIdentifierChar)
import PlutusCore.Quote

#if !MIN_VERSION_base(4,20,0)
import Data.List
#endif
import Data.Text qualified as T

{- Note [PLC names]
Expand Down
3 changes: 3 additions & 0 deletions plutus-core/plutus-ir/src/PlutusIR/Transform/RecSplit.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
-- editorconfig-checker-disable-file
{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
Expand All @@ -15,7 +16,9 @@ import Algebra.Graph.NonEmpty.AdjacencyMap qualified as AMN
import Algebra.Graph.ToGraph (isAcyclic)
import Control.Lens
import Data.Either
#if !MIN_VERSION_base(4,20,0)
import Data.Foldable (foldl')
#endif
import Data.List (nub)
import Data.List.NonEmpty qualified as NE
import Data.Map qualified as M
Expand Down
2 changes: 2 additions & 0 deletions plutus-core/prelude/PlutusPrelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -119,7 +119,9 @@ import Data.Either (fromRight, isLeft, isRight)
import Data.Foldable (fold, for_, toList, traverse_)
import Data.Function (on)
import Data.Functor (($>))
#if ! MIN_VERSION_base(4,20,0)
import Data.List (foldl')
#endif
import Data.List.Extra (enumerate)
import Data.List.NonEmpty (NonEmpty (..))
import Data.Maybe (fromMaybe, isJust, isNothing)
Expand Down
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeApplications #-}

Expand All @@ -22,7 +23,9 @@ import UntypedPlutusCore.Transform.ForceDelay (forceDelay)
import UntypedPlutusCore.Transform.Inline (InlineHints (..), inline)

import Control.Monad
#if !MIN_VERSION_base(4,20,0)
import Data.List
#endif
import Data.Typeable

simplifyProgram ::
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
Expand All @@ -18,7 +19,9 @@ import Control.Monad (join, void)
import Control.Monad.Trans.Class (MonadTrans (lift))
import Control.Monad.Trans.Reader (ReaderT (runReaderT), ask, local)
import Control.Monad.Trans.State.Strict (State, evalState, get, put)
#if !MIN_VERSION_base(4,20,0)
import Data.Foldable (Foldable (foldl'))
#endif
import Data.Hashable (Hashable)
import Data.HashMap.Strict (HashMap)
import Data.HashMap.Strict qualified as Map
Expand Down
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{- Note [Cancelling interleaved Force-Delay pairs]
The 'ForceDelay' optimisation pushes 'Force' inside its direct 'Apply' subterms,
Expand Down Expand Up @@ -139,7 +140,9 @@ import UntypedPlutusCore.Core

import Control.Lens (transformOf)
import Control.Monad (guard)
#if !MIN_VERSION_base(4,20,0)
import Data.Foldable (foldl')
#endif

{- | Traverses the term, for each node applying the optimisation
detailed above. For implementation details see 'optimisationProcedure'.
Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
-- editorconfig-checker-disable
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
Expand All @@ -18,7 +19,11 @@ import UntypedPlutusCore qualified as UPLC
import Cardano.Crypto.EllipticCurve.BLS12_381 (scalarPeriod)
import Control.Monad (replicateM)
import Data.ByteString as BS (empty, length, pack)
import Data.List as List (foldl', genericReplicate, length, nub)
import Data.List as List (
#if !MIN_VERSION_base(4,20,0)
foldl',
#endif
genericReplicate, length, nub)
import Text.Printf (printf)

import Test.QuickCheck
Expand Down
5 changes: 5 additions & 0 deletions plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
Expand All @@ -22,6 +23,10 @@ import Data.String (IsString (..))
import Data.Text qualified as Text
import GHC.Magic qualified as Magic
import Prelude qualified as Haskell (String)
#if MIN_VERSION_base(4,20,0)
import Prelude (type (~))
#endif


{- Note [noinline hack]
For some functions we have two conflicting desires:
Expand Down
2 changes: 2 additions & 0 deletions plutus-tx/src/PlutusTx/IsData/TH.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,9 @@ module PlutusTx.IsData.TH (
mkUnsafeConstrPartsMatchPattern,
) where

#if !MIN_VERSION_base(4,20,0)
import Data.Foldable (foldl')
#endif
import Data.Functor ((<&>))
import Data.Traversable (for)

Expand Down

0 comments on commit 1cf0419

Please sign in to comment.