Skip to content

Commit

Permalink
Tweaks to allow 9.8.2 compilation
Browse files Browse the repository at this point in the history
  • Loading branch information
paolino authored and Github Action committed Jul 1, 2024
1 parent db7724b commit 859e8b1
Show file tree
Hide file tree
Showing 42 changed files with 69 additions and 9 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}

{-# OPTIONS_GHC -Wno-x-partial #-}
-- |
-- Copyright: © 2018-2020 IOHK
-- License: Apache-2.0
Expand Down
1 change: 1 addition & 0 deletions lib/api/src/Cardano/Wallet/Api/Client.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}

{-# OPTIONS_GHC -fno-warn-orphans #-}
-- |
-- Copyright: © 2018-2020 IOHK
-- License: Apache-2.0
Expand Down
6 changes: 2 additions & 4 deletions lib/api/src/Cardano/Wallet/Api/Http/Shelley/Server.hs
Original file line number Diff line number Diff line change
Expand Up @@ -233,8 +233,7 @@ import Cardano.Wallet.Address.Derivation
, stakeDerivationPath
)
import Cardano.Wallet.Address.Derivation.Byron
( ByronKey
, mkByronKeyFromMasterKey
( mkByronKeyFromMasterKey
)
import Cardano.Wallet.Address.Derivation.Icarus
( IcarusKey
Expand Down Expand Up @@ -1734,10 +1733,9 @@ mkLegacyWallet ctx wid cp meta _ pending progress = do
W.withRootKey @s db wid mempty Prelude.id (\_ _ -> pure ())

postRandomWallet
:: forall ctx s k n.
:: forall ctx s n.
( ctx ~ ApiLayer s
, s ~ RndState n
, k ~ ByronKey
)
=> ctx
-> ByronWalletPostData '[12,15,18,21,24]
Expand Down
1 change: 1 addition & 0 deletions lib/balance-tx/lib/main/Cardano/Write/Tx.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE DuplicateRecordFields #-}
-- |
-- Copyright: © 2023 Cardano Foundation
-- License: Apache-2.0
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,8 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ViewPatterns #-}

{-# OPTIONS_GHC -Wno-x-partial #-}
{- HLINT ignore "Use null" -}
{- HLINT ignore "Use camelCase" -}

Expand Down
1 change: 1 addition & 0 deletions lib/benchmarks/exe/db-bench.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@

{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
{-# OPTIONS_GHC -Wno-x-partial #-}

{-# OPTIONS_GHC -Wno-ambiguous-fields #-}

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -196,13 +196,13 @@ data TxSummary = TxSummary
, blockHeaderBody :: Read.BHBody
, transfer :: ValueTransfer
}
deriving (Eq, Ord, Show)
deriving (Eq, Show)

data ValueTransfer = ValueTransfer
{ spent :: Read.Value
, received :: Read.Value
}
deriving (Eq, Ord, Show)
deriving (Eq, Show)

getCustomerHistory :: Customer -> WalletState -> [TxSummary]
getCustomerHistory = undefined
Expand Down
2 changes: 2 additions & 0 deletions lib/delta-store/src/Test/Store.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,8 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ViewPatterns #-}

{-# OPTIONS_GHC -Wno-x-partial #-}

-- |
-- Copyright: © 2023 IOHK
-- License: Apache-2.0
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,8 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}

{-# OPTIONS_GHC -Wno-x-partial #-}

module Test.Integration.Framework.DSL.Wallet
( createARandomWalletWithMnemonics
, createWalletFromMnemonics
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,8 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}

{-# OPTIONS_GHC -Wno-x-partial #-}

module Test.Integration.Scenario.API.Byron.Migrations
( spec
) where
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeSynonymInstances #-}

{-# OPTIONS_GHC -Wno-x-partial #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeSynonymInstances #-}

{-# OPTIONS_GHC -Wno-x-partial #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}

Expand Down
Original file line number Diff line number Diff line change
@@ -1,14 +1,17 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}

{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
{-# OPTIONS_GHC -Wno-x-partial #-}

module Test.Integration.Scenario.API.Shelley.Addresses
( spec
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,8 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}

{-# OPTIONS_GHC -Wno-x-partial #-}

module Test.Integration.Scenario.API.Shelley.Migrations
( spec
) where
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,8 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}

{-# OPTIONS_GHC -Wno-x-partial #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}

module Test.Integration.Scenario.API.Shelley.StakePools (spec) where
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,8 @@
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}

{-# OPTIONS_GHC -Wno-x-partial #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}

{- HLINT ignore "Use head" -}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}

{-# OPTIONS_GHC -Wno-x-partial #-}
{-# OPTIONS_GHC -Wno-unused-imports #-} -- temportary, until addRequiredSigners is fixed
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,8 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}

{-# OPTIONS_GHC -Wno-x-partial #-}

module Test.Integration.Scenario.API.Shelley.Wallets
( spec
) where
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,8 @@
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE ScopedTypeVariables #-}

{-# OPTIONS_GHC -Wno-x-partial #-}

module Cardano.Wallet.Launch.Cluster.CommandLine
( CommandLineOptions (..)
, WalletPresence (..)
Expand Down
2 changes: 2 additions & 0 deletions lib/network-layer/src/Cardano/Wallet/Network/Light.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,8 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}

{-# OPTIONS_GHC -Wno-x-partial #-}

module Cardano.Wallet.Network.Light
( -- * Interface
LightSyncSource (..)
Expand Down
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-x-partial #-}

module Cardano.Wallet.Primitive.Types.Address.Gen
(
-- * Generators and shrinkers
Expand Down
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-x-partial #-}

module Cardano.Wallet.Primitive.Types.AssetName.Gen
(
-- * Generators and shrinkers
Expand Down
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-x-partial #-}

module Cardano.Wallet.Primitive.Types.RewardAccount.Gen
( genRewardAccount
, shrinkRewardAccount
Expand Down
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-x-partial #-}

module Cardano.Wallet.Primitive.Types.TokenPolicyId.Gen
(
-- * Generators and shrinkers
Expand Down
2 changes: 1 addition & 1 deletion lib/primitive/lib/Cardano/Wallet/Primitive/Types/Tx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -185,7 +185,7 @@ data TxChange derivationPath = TxChange
, amount :: Coin
, assets :: TokenMap
, derivationPath :: derivationPath
} deriving (Show, Generic, Eq, Ord)
} deriving (Show, Generic, Eq)

{-------------------------------------------------------------------------------
Conversions (Unsafe)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# OPTIONS_GHC -fno-warn-partial-type-signatures #-}
{-# OPTIONS_GHC -Wno-x-partial #-}

module Cardano.Wallet.Primitive.Types.Tx.TxIn.Gen
( genTxHash
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -Wno-x-partial #-}

module Cardano.Wallet.Primitive.SlottingSpec
( spec
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
{-# LANGUAGE ScopedTypeVariables #-}

{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -Wno-x-partial #-}

module Cardano.Wallet.Primitive.Types.RangeSpec
( spec
Expand Down
2 changes: 2 additions & 0 deletions lib/test-utils/test/Test/Hspec/ExtraSpec.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

{-# OPTIONS_GHC -Wno-x-partial #-}

module Test.Hspec.ExtraSpec (spec) where

import Prelude
Expand Down
2 changes: 2 additions & 0 deletions lib/unit/test/unit/Cardano/Pool/DB/Properties.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,8 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeSynonymInstances #-}

{-# OPTIONS_GHC -Wno-x-partial #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -Wno-x-partial #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

{-# OPTIONS_GHC -Wno-x-partial #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}

Expand Down
1 change: 1 addition & 0 deletions lib/unit/test/unit/Cardano/Wallet/Api/Server/TlsSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
{-# LANGUAGE TemplateHaskell #-}

{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
{-# OPTIONS_GHC -Wno-x-partial #-}

module Cardano.Wallet.Api.Server.TlsSpec
( spec
Expand Down
3 changes: 3 additions & 0 deletions lib/unit/test/unit/Cardano/Wallet/CheckpointsSpec.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,7 @@
{-# LANGUAGE DataKinds #-}

{-# OPTIONS_GHC -Wno-x-partial #-}

module Cardano.Wallet.CheckpointsSpec
( spec
) where
Expand Down
5 changes: 3 additions & 2 deletions lib/unit/test/unit/Cardano/Wallet/DB/LayerSpec.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
Expand All @@ -14,14 +15,14 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}

{-# OPTIONS_GHC -Wno-x-partial #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE StandaloneDeriving #-}

-- |
-- Copyright: © 2018-2020 IOHK
Expand Down
1 change: 1 addition & 0 deletions lib/unit/test/unit/Cardano/Wallet/DB/StateMachine.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -Wno-x-partial #-}
{-# OPTIONS_GHC -Wno-unused-foralls #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

Expand Down
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}

{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_GHC -Wno-x-partial #-}

module Cardano.Wallet.DB.Store.Delegations.Migrations.V5Spec where

Expand Down
2 changes: 2 additions & 0 deletions lib/unit/test/unit/Cardano/Wallet/Primitive/ModelSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,8 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -Wno-x-partial #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{- HLINT ignore "Move brackets to avoid $" -}

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@
{- HLINT ignore "Use camelCase" -}

{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -Wno-x-partial #-}

-- TODO: https://cardanofoundation.atlassian.net/browse/ADP-2841
{-# LANGUAGE CPP #-}
Expand Down
1 change: 1 addition & 0 deletions lib/unit/test/unit/Cardano/WalletSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -Wno-x-partial #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

module Cardano.WalletSpec
Expand Down
2 changes: 2 additions & 0 deletions lib/wallet/src/Cardano/Wallet/DB/Pure/Implementation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,8 @@
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -Wno-x-partial #-}

-- TODO: https://cardanofoundation.atlassian.net/browse/ADP-2841
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 902
Expand Down
1 change: 1 addition & 0 deletions lib/wallet/src/Cardano/Wallet/Primitive/Types/Tx/TxSeq.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}

{-# OPTIONS_GHC -Wno-x-partial #-}
-- |
-- Copyright: © 2022 IOHK
-- License: Apache-2.0
Expand Down

0 comments on commit 859e8b1

Please sign in to comment.