Skip to content

Commit

Permalink
Bump to ghc-8.10.4
Browse files Browse the repository at this point in the history
  • Loading branch information
Anviking committed Mar 10, 2021
1 parent 63eb2fc commit 8937133
Show file tree
Hide file tree
Showing 40 changed files with 336 additions and 134 deletions.
157 changes: 157 additions & 0 deletions cardano-1.25.1.yaml
Original file line number Diff line number Diff line change
@@ -0,0 +1,157 @@
name: cardano-1.25.1-new-stack

resolver: lts-17.4

packages:
- base16-0.1.2.1
- base16-bytestring-1.0.1.0
- base58-bytestring-0.1.0
- base64-0.4.2
- bech32-1.1.0
- bech32-th-1.0.2
- binary-0.8.7.0
- bimap-0.4.0
- canonical-json-0.6.0.0
- cborg-0.2.4.0
- clock-0.8
- config-ini-0.2.4.0
- connection-0.3.1
- containers-0.5.11.0
- data-clist-0.1.2.2
- dns-3.0.4
- generic-monoid-0.1.0.0
- generics-sop-0.5.1.0
- ghc-byteorder-4.11.0.0.10
- gray-code-0.3.1
- hedgehog-1.0.2
- hedgehog-corpus-0.2.0
- hedgehog-quickcheck-0.1.1
- hspec-2.7.0
- hspec-core-2.7.0
- hspec-discover-2.7.0
- io-streams-1.5.1.0
- io-streams-haproxy-1.0.1.0
- katip-0.8.4.0
- libsystemd-journal-1.4.4
- micro-recursion-schemes-5.0.2.2
- moo-1.2
- network-3.1.2.1
- partial-order-0.2.0.0
- prettyprinter-1.7.0
- primitive-0.7.1.0
- prometheus-2.1.2
- protolude-0.3.0
- quiet-0.2
- semialign-1.1.0.1
- snap-core-1.0.4.1
- snap-server-1.1.1.1
- sop-core-0.5.0.1
- statistics-linreg-0.3
- streaming-binary-0.2.2.0
- streaming-bytestring-0.2.0
- systemd-2.3.0
- tasty-hedgehog-1.0.0.2
- text-1.2.4.0
- text-ansi-0.1.0
- text-conversions-0.3.1
- text-zipper-0.10.1
- th-lift-instances-0.1.14
- these-1.1.1.1
- time-units-1.0.0
- transformers-except-0.1.1
- unordered-containers-0.2.12.0
- Unique-0.4.7.6
- word-wrap-0.4.1
- websockets-0.12.6.1
- Win32-2.6.2.0
- nothunks-0.1.2

- git: https://github.com/input-output-hk/cardano-base
commit: b364d925e0a72689ecba40dd1f4899f76170b894
subdirs:
- binary
- binary/test
- cardano-crypto-class
- cardano-crypto-tests
- cardano-crypto-praos
- slotting

- git: https://github.com/input-output-hk/cardano-crypto
commit: f73079303f663e028288f9f4a9e08bcca39a923e

- git: https://github.com/input-output-hk/cardano-ledger-specs
commit: 097890495cbb0e8b62106bcd090a5721c3f4b36f
subdirs:
- byron/chain/executable-spec
- byron/crypto
- byron/crypto/test
- byron/ledger/executable-spec
- byron/ledger/impl
- byron/ledger/impl/test
- semantics/executable-spec
- semantics/small-steps-test
- shelley/chain-and-ledger/dependencies/non-integer
- shelley/chain-and-ledger/executable-spec
- shelley/chain-and-ledger/shelley-spec-ledger-test
- shelley-ma/impl

- git: https://github.com/input-output-hk/cardano-node
commit: 9a7331cce5e8bc0ea9c6bfa1c28773f4c5a7000f
subdirs:
- cardano-api
- cardano-api/test
- cardano-cli
- cardano-config
- cardano-node
- cardano-node-chairman
- hedgehog-extras

- git: https://github.com/input-output-hk/cardano-prelude
commit: ee4e7b547a991876e6b05ba542f4e62909f4a571
subdirs:
- cardano-prelude
- cardano-prelude-test

- git: https://github.com/input-output-hk/cardano-sl-x509
commit: 43a036c5bbe68ca2e9cbe611eab7982e2348fe49

- git: https://github.com/input-output-hk/goblins
commit: cde90a2b27f79187ca8310b6549331e59595e7ba

# NOTE: Bumped
- git: https://github.com/input-output-hk/iohk-monitoring-framework
commit: 42778ad2041dd9ba236a60c35e1f936fcc1339ae
subdirs:
- contra-tracer
- iohk-monitoring
- plugins/backend-aggregation
- plugins/backend-ekg
- plugins/backend-monitoring
- plugins/backend-trace-forwarder
- plugins/scribe-systemd
- tracer-transformers

- git: https://github.com/input-output-hk/ouroboros-network
commit: 6cb9052bde39472a0555d19ade8a42da63d3e904
subdirs:
- io-sim
- io-sim-classes
- network-mux
- ouroboros-consensus
- ouroboros-consensus-byron
- ouroboros-consensus-cardano
- ouroboros-consensus-shelley
- ouroboros-network
- ouroboros-network-framework
- typed-protocols
- typed-protocols-examples
- Win32-network
# Extra packages not used by cardano-node
- cardano-client
- ntp-client
- ouroboros-consensus-mock

- git: https://github.com/snoyberg/http-client.git
commit: 1a75bdfca014723dd5d40760fad854b3f0f37156
subdirs:
- http-client
2 changes: 1 addition & 1 deletion lib/cli/src/Cardano/CLI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1308,7 +1308,7 @@ parseLoggingSeverity :: String -> Either String Severity
parseLoggingSeverity arg =
case lookup (map toLower arg) loggingSeverities of
Just sev -> pure sev
Nothing -> fail $ "unknown logging severity: " ++ arg
Nothing -> Left $ "unknown logging severity: " ++ arg

loggingSeverityReader :: ReadM Severity
loggingSeverityReader = eitherReader parseLoggingSeverity
Expand Down
2 changes: 0 additions & 2 deletions lib/cli/test/unit/Cardano/CLISpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,8 +45,6 @@ import Cardano.Wallet.Primitive.Types
( PoolMetadataSource )
import Cardano.Wallet.Primitive.Types.Tx
( TxMetadata (..), TxMetadataValue (..) )
import Control.Monad
( mapM_ )
import Data.Proxy
( Proxy (..) )
import Data.Quantity
Expand Down
2 changes: 1 addition & 1 deletion lib/core-integration/src/Cardano/Wallet/BenchShared.hs
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@ import Cardano.Wallet.Network.Ports
import Control.DeepSeq
( NFData, rnf )
import Control.Monad
( forM, mapM_, void )
( forM, void )
import Criterion.Measurement
( getTime, initializeTime, secs )
import Data.Aeson
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ import Cardano.BM.Data.Severity
import Cardano.BM.Setup
( setupTrace_, shutdown )
import Control.Monad
( mapM_, replicateM_ )
( replicateM_ )
import Data.Maybe
( mapMaybe )
import Data.Time
Expand Down
2 changes: 0 additions & 2 deletions lib/core-integration/src/Test/Integration/Framework/DSL.hs
Original file line number Diff line number Diff line change
Expand Up @@ -310,8 +310,6 @@ import Data.Generics.Product.Typed
( HasType, typed )
import Data.IORef
( newIORef, readIORef, writeIORef )
import Data.List
( (!!) )
import Data.List.NonEmpty
( NonEmpty )
import Data.Maybe
Expand Down
2 changes: 0 additions & 2 deletions lib/core/src/Cardano/Byron/Codec/Cbor.hs
Original file line number Diff line number Diff line change
Expand Up @@ -67,8 +67,6 @@ import Cardano.Wallet.Primitive.Types.Tx
( TxIn (..), TxOut (..) )
import Control.Monad
( replicateM, when )
import Control.Monad.Fail
( MonadFail )
import Crypto.Error
( CryptoError (..), CryptoFailable (..) )
import Crypto.Hash
Expand Down
2 changes: 1 addition & 1 deletion lib/core/src/Cardano/DB/Sqlite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -59,7 +59,7 @@ import Cardano.BM.Data.Tracer
import Cardano.Wallet.Logging
( BracketLog, bracketTracer )
import Control.Monad
( join, mapM_, void, when )
( join, void, when )
import Control.Monad.IO.Unlift
( MonadUnliftIO (..) )
import Control.Monad.Logger
Expand Down
2 changes: 0 additions & 2 deletions lib/core/src/Cardano/Pool/DB.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,8 +37,6 @@ import Cardano.Wallet.Primitive.Types
, StakePoolMetadataHash
, StakePoolMetadataUrl
)
import Control.Monad.Fail
( MonadFail )
import Control.Monad.IO.Class
( MonadIO )
import Control.Monad.Trans.Except
Expand Down
5 changes: 3 additions & 2 deletions lib/core/src/Cardano/Pool/DB/Sqlite/TH.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,12 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
Expand Down Expand Up @@ -32,8 +35,6 @@ import Data.Time.Clock.POSIX
( POSIXTime )
import Data.Word
( Word32, Word64, Word8 )
import Database.Persist.Class
( AtLeastOneUniqueKey (..), OnlyOneUniqueKey (..) )
import Database.Persist.TH
( mkDeleteCascade, mkMigrate, mkPersist, persistLowerCase, share )
import GHC.Generics
Expand Down
8 changes: 5 additions & 3 deletions lib/core/src/Cardano/Wallet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -383,6 +383,8 @@ import Data.Generics.Labels
()
import Data.Generics.Product.Typed
( HasType, typed )
import Data.Kind
( Type )
import Data.List
( scanl' )
import Data.List.NonEmpty
Expand Down Expand Up @@ -473,7 +475,7 @@ import qualified Data.Vector as V
--
-- __Fix__: Add type-applications at the call-site "@myFunction \@ctx \@s \\@k@"

data WalletLayer s (k :: Depth -> * -> *)
data WalletLayer s (k :: Depth -> Type -> Type)
= WalletLayer
(Tracer IO WalletLog)
(Block, NetworkParameters, SyncTolerance)
Expand Down Expand Up @@ -1856,7 +1858,7 @@ attachPrivateKeyFromPwd
-> WalletId
-> (k 'RootK XPrv, Passphrase "encryption")
-> ExceptT ErrNoSuchWallet IO ()
attachPrivateKeyFromPwd ctx wid (xprv, pwd) = db & \DBLayer{..} -> do
attachPrivateKeyFromPwd ctx wid (xprv, pwd) = db & \_ -> do
hpwd <- liftIO $ encryptPassphrase pwd
-- NOTE Only new wallets are constructed through this function, so the
-- passphrase is encrypted with the new scheme (i.e. PBKDF2)
Expand Down Expand Up @@ -1890,7 +1892,7 @@ attachPrivateKeyFromPwdHash
-> WalletId
-> (k 'RootK XPrv, Hash "encryption")
-> ExceptT ErrNoSuchWallet IO ()
attachPrivateKeyFromPwdHash ctx wid (xprv, hpwd) = db & \DBLayer{..} ->
attachPrivateKeyFromPwdHash ctx wid (xprv, hpwd) = db & \_ ->
-- NOTE Only legacy wallets are imported through this function, passphrase
-- were encrypted with the legacy scheme (Scrypt).
attachPrivateKey db wid (xprv, hpwd) EncryptWithScrypt
Expand Down
6 changes: 4 additions & 2 deletions lib/core/src/Cardano/Wallet/Api.hs
Original file line number Diff line number Diff line change
Expand Up @@ -213,6 +213,8 @@ import Data.Generics.Labels
()
import Data.Generics.Product.Typed
( HasType, typed )
import Data.Kind
( Type )
import GHC.Generics
( Generic )
import Servant.API
Expand Down Expand Up @@ -844,7 +846,7 @@ type PostExternalTransaction = "proxy"
Api Layer
-------------------------------------------------------------------------------}

data ApiLayer s (k :: Depth -> * -> *)
data ApiLayer s (k :: Depth -> Type -> Type)
= ApiLayer
(Tracer IO (WorkerLog WalletId WalletLog))
(Block, NetworkParameters, SyncTolerance)
Expand Down Expand Up @@ -898,6 +900,6 @@ tokenMetadataClient =
Type Families
-------------------------------------------------------------------------------}

type family PostData wallet :: * where
type family PostData wallet :: Type where
PostData ApiWallet = WalletOrAccountPostData
PostData ApiByronWallet = SomeByronWalletPostData
7 changes: 4 additions & 3 deletions lib/core/src/Cardano/Wallet/Api/Client.hs
Original file line number Diff line number Diff line change
Expand Up @@ -330,9 +330,10 @@ addressClient =
fmap unApiAddressInspect
. _inspectAddress
. ApiAddressInspectData
, postRandomAddress = \_ _ -> fail "feature unavailable."
, putRandomAddress = \_ _ -> fail "feature unavailable."
, putRandomAddresses = \_ _ -> fail "feature unavailable."
, postRandomAddress = \_ _ -> error "feature unavailable."
-- TODO: Fix. Do we want a JSON error response?
, putRandomAddress = \_ _ -> error "feature unavailable."
, putRandomAddresses = \_ _ -> error "feature unavailable."
}

-- | Produces an 'AddressClient n' working against the /wallets API
Expand Down
22 changes: 12 additions & 10 deletions lib/core/src/Cardano/Wallet/Api/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -303,6 +303,8 @@ import Data.Generics.Internal.VL.Lens
( view, (^.) )
import Data.Hashable
( Hashable )
import Data.Kind
( Type )
import Data.List
( intercalate )
import Data.List.NonEmpty
Expand Down Expand Up @@ -2300,7 +2302,7 @@ instance FromText (AddressAmount Text) where
instance FromText PostExternalTransactionData where
fromText text = case convertFromBase Base16 (T.encodeUtf8 text) of
Left _ ->
fail "Parse error. Expecting hex-encoded format."
Left $ TextDecodingError "Parse error. Expecting hex-encoded format."
Right load ->
pure $ PostExternalTransactionData load

Expand Down Expand Up @@ -2466,15 +2468,15 @@ instance DecodeStakeAddress 'Mainnet => DecodeStakeAddress ('Staging pm) where
-- having to actually rewrite any of the API definition.
--
-- We use an open type family so it can be extended by other module in places.
type family ApiAddressT (n :: k) :: *
type family ApiAddressIdT (n :: k) :: *
type family ApiCoinSelectionT (n :: k) :: *
type family ApiSelectCoinsDataT (n :: k) :: *
type family ApiTransactionT (n :: k) :: *
type family PostTransactionDataT (n :: k) :: *
type family PostTransactionFeeDataT (n :: k) :: *
type family ApiWalletMigrationPostDataT (n :: k1) (s :: k2) :: *
type family ApiPutAddressesDataT (n :: k) :: *
type family ApiAddressT (n :: k) :: Type
type family ApiAddressIdT (n :: k) :: Type
type family ApiCoinSelectionT (n :: k) :: Type
type family ApiSelectCoinsDataT (n :: k) :: Type
type family ApiTransactionT (n :: k) :: Type
type family PostTransactionDataT (n :: k) :: Type
type family PostTransactionFeeDataT (n :: k) :: Type
type family ApiWalletMigrationPostDataT (n :: k1) (s :: k2) :: Type
type family ApiPutAddressesDataT (n :: k) :: Type

type instance ApiAddressT (n :: NetworkDiscriminant) =
ApiAddress n
Expand Down
2 changes: 1 addition & 1 deletion lib/core/src/Cardano/Wallet/DB/Sqlite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -163,7 +163,7 @@ import Data.Functor
import Data.Generics.Internal.VL.Lens
( view, (^.) )
import Data.List
( nub, sortOn, unzip3 )
( nub, sortOn )
import Data.List.Split
( chunksOf )
import Data.Map.Strict
Expand Down
Loading

0 comments on commit 8937133

Please sign in to comment.