Skip to content

Commit 8d9d780

Browse files
committed
Remove AsType usage where not necessary
1 parent bcf60b8 commit 8d9d780

File tree

25 files changed

+84
-98
lines changed

25 files changed

+84
-98
lines changed

cardano-api/gen/Test/Hedgehog/Roundtrip/Bech32.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -10,8 +10,8 @@ import Hedgehog qualified as H
1010

1111
roundtrip_Bech32
1212
:: (SerialiseAsBech32 a, Eq a, Show a)
13-
=> AsType a -> Gen a -> Property
14-
roundtrip_Bech32 typeProxy gen =
13+
=> Gen a -> Property
14+
roundtrip_Bech32 gen =
1515
H.property $ do
1616
val <- H.forAll gen
17-
H.tripping val serialiseToBech32 (deserialiseFromBech32 typeProxy)
17+
H.tripping val serialiseToBech32 deserialiseFromBech32

cardano-api/src/Cardano/Api/Internal/Address.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -270,7 +270,7 @@ instance SerialiseAddress (Address ShelleyAddr) where
270270

271271
deserialiseAddress (AsAddress AsShelleyAddr) t =
272272
either (const Nothing) Just $
273-
deserialiseFromBech32 (AsAddress AsShelleyAddr) t
273+
deserialiseFromBech32 t
274274

275275
instance ToJSON (Address ShelleyAddr) where
276276
toJSON = Aeson.String . serialiseAddress
@@ -590,7 +590,7 @@ instance SerialiseAddress StakeAddress where
590590

591591
deserialiseAddress AsStakeAddress t =
592592
either (const Nothing) Just $
593-
deserialiseFromBech32 AsStakeAddress t
593+
deserialiseFromBech32 t
594594

595595
instance ToJSON StakeAddress where
596596
toJSON s = Aeson.String $ serialiseAddress s

cardano-api/src/Cardano/Api/Internal/CIP/Cip129.hs

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -4,8 +4,8 @@
44
{-# LANGUAGE LambdaCase #-}
55
{-# LANGUAGE RankNTypes #-}
66
{-# LANGUAGE ScopedTypeVariables #-}
7+
{-# LANGUAGE TypeApplications #-}
78
{-# LANGUAGE TypeFamilies #-}
8-
{-# OPTIONS_GHC -Wno-orphans #-}
99

1010
module Cardano.Api.Internal.CIP.Cip129
1111
( Cip129 (..)
@@ -98,15 +98,17 @@ serialiseToBech32Cip129 a =
9898
humanReadablePart = cip129Bech32PrefixFor (proxyToAsType (Proxy :: Proxy a))
9999

100100
deserialiseFromBech32Cip129
101-
:: Cip129 a
102-
=> AsType a -> Text -> Either Bech32DecodeError a
103-
deserialiseFromBech32Cip129 asType bech32Str = do
101+
:: forall a
102+
. Cip129 a
103+
=> Text
104+
-> Either Bech32DecodeError a
105+
deserialiseFromBech32Cip129 bech32Str = do
104106
(prefix, dataPart) <-
105107
Bech32.decodeLenient bech32Str
106108
?!. Bech32DecodingError
107109

108110
let actualPrefix = Bech32.humanReadablePartToText prefix
109-
permittedPrefixes = cip129Bech32PrefixesPermitted asType
111+
permittedPrefixes = cip129Bech32PrefixesPermitted (asType @a)
110112
guard (actualPrefix `elem` permittedPrefixes)
111113
?! Bech32UnexpectedPrefix actualPrefix (fromList permittedPrefixes)
112114

@@ -128,7 +130,7 @@ deserialiseFromBech32Cip129 asType bech32Str = do
128130
guard (header == expectedHeader)
129131
?! Bech32UnexpectedHeader (toBase16Text expectedHeader) (toBase16Text header)
130132

131-
let expectedPrefix = Bech32.humanReadablePartToText $ cip129Bech32PrefixFor asType
133+
let expectedPrefix = Bech32.humanReadablePartToText $ cip129Bech32PrefixFor (asType @a)
132134
guard (actualPrefix == expectedPrefix)
133135
?! Bech32WrongPrefix actualPrefix expectedPrefix
134136

cardano-api/src/Cardano/Api/Internal/DeserialiseAnyOf.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ where
2323

2424
import Cardano.Api.Internal.Address
2525
import Cardano.Api.Internal.Error
26+
import Cardano.Api.Internal.HasTypeProxy
2627
import Cardano.Api.Internal.Keys.Byron
2728
import Cardano.Api.Internal.Keys.Class
2829
import Cardano.Api.Internal.Keys.Praos
@@ -108,11 +109,10 @@ data DeserialiseInputResult a
108109
-- | Deserialise an input of some type that is formatted in some way.
109110
deserialiseInput
110111
:: forall a
111-
. AsType a
112-
-> NonEmpty (InputFormat a)
112+
. NonEmpty (InputFormat a)
113113
-> ByteString
114114
-> Either InputDecodeError a
115-
deserialiseInput asType acceptedFormats inputBs =
115+
deserialiseInput acceptedFormats inputBs =
116116
go (toList acceptedFormats)
117117
where
118118
inputText :: Text
@@ -135,7 +135,7 @@ deserialiseInput asType acceptedFormats inputBs =
135135
deserialiseTextEnvelope = do
136136
let textEnvRes :: Either TextEnvelopeError a
137137
textEnvRes =
138-
deserialiseFromTextEnvelope asType
138+
deserialiseFromTextEnvelope
139139
=<< first TextEnvelopeAesonDecodeError (Aeson.eitherDecodeStrict' inputBs)
140140
case textEnvRes of
141141
Right res -> DeserialiseInputSuccess res
@@ -148,7 +148,7 @@ deserialiseInput asType acceptedFormats inputBs =
148148

149149
deserialiseBech32 :: SerialiseAsBech32 a => DeserialiseInputResult a
150150
deserialiseBech32 =
151-
case deserialiseFromBech32 asType inputText of
151+
case deserialiseFromBech32 inputText of
152152
Right res -> DeserialiseInputSuccess res
153153
-- The input was not valid Bech32.
154154
Left (Bech32DecodingError _) -> DeserialiseInputErrorFormatMismatch
@@ -158,7 +158,7 @@ deserialiseInput asType acceptedFormats inputBs =
158158
deserialiseHex :: SerialiseAsRawBytes a => DeserialiseInputResult a
159159
deserialiseHex
160160
| isValidHex inputBs =
161-
case deserialiseFromRawBytesHex asType inputBs of
161+
case deserialiseFromRawBytesHex inputBs of
162162
Left _ -> DeserialiseInputError InputInvalidError
163163
Right x -> DeserialiseInputSuccess x
164164
| otherwise = DeserialiseInputErrorFormatMismatch

cardano-api/src/Cardano/Api/Internal/Keys/Read.hs

Lines changed: 6 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -28,27 +28,25 @@ import Data.List.NonEmpty (NonEmpty)
2828
-- The contents of the file can either be Bech32-encoded, hex-encoded, or in
2929
-- the text envelope format.
3030
readKeyFile
31-
:: AsType a
32-
-> NonEmpty (InputFormat a)
31+
:: NonEmpty (InputFormat a)
3332
-> FilePath
3433
-> IO (Either (FileError InputDecodeError) a)
35-
readKeyFile asType acceptedFormats path = do
34+
readKeyFile acceptedFormats path = do
3635
eContent <- runExceptT $ fileIOExceptT path readFileBlocking
3736
case eContent of
3837
Left e -> return $ Left e
3938
Right content ->
40-
return . first (FileError path) $ deserialiseInput asType acceptedFormats content
39+
return . first (FileError path) $ deserialiseInput acceptedFormats content
4140

4241
-- | Read a cryptographic key from a file.
4342
--
4443
-- The contents of the file must be in the text envelope format.
4544
readKeyFileTextEnvelope
4645
:: HasTextEnvelope a
47-
=> AsType a
48-
-> File content In
46+
=> File content In
4947
-> IO (Either (FileError InputDecodeError) a)
50-
readKeyFileTextEnvelope asType fp =
51-
first (fmap InputTextEnvelopeError) <$> readFileTextEnvelope asType fp
48+
readKeyFileTextEnvelope fp =
49+
first (fmap InputTextEnvelopeError) <$> readFileTextEnvelope fp
5250

5351
-- | Read a cryptographic key from a file given that it is one of the provided
5452
-- types.

cardano-api/src/Cardano/Api/Internal/Keys/Shelley.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1787,7 +1787,7 @@ instance ToJSONKey (Hash StakePoolKey) where
17871787

17881788
instance FromJSON (Hash StakePoolKey) where
17891789
parseJSON = withText "PoolId" $ \str ->
1790-
case deserialiseFromBech32 (AsHash AsStakePoolKey) str of
1790+
case deserialiseFromBech32 str of
17911791
Left err ->
17921792
fail $
17931793
docToString $
@@ -1953,7 +1953,7 @@ instance ToJSONKey (Hash StakePoolExtendedKey) where
19531953

19541954
instance FromJSON (Hash StakePoolExtendedKey) where
19551955
parseJSON = withText "PoolId" $ \str ->
1956-
case deserialiseFromBech32 (AsHash AsStakePoolExtendedKey) str of
1956+
case deserialiseFromBech32 str of
19571957
Left err ->
19581958
fail $
19591959
docToString $
@@ -2073,7 +2073,7 @@ instance ToJSONKey (Hash DRepKey) where
20732073

20742074
instance FromJSON (Hash DRepKey) where
20752075
parseJSON = withText "DRepId" $ \str ->
2076-
case deserialiseFromBech32 (AsHash AsDRepKey) str of
2076+
case deserialiseFromBech32 str of
20772077
Left err ->
20782078
fail $
20792079
docToString $

cardano-api/src/Cardano/Api/Internal/Script.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1039,9 +1039,9 @@ instance HasTypeProxy lang => HasTypeProxy (PlutusScript lang) where
10391039
-- do any additional transformation on Plutus script bytes.
10401040
instance HasTypeProxy lang => SerialiseAsRawBytes (PlutusScript lang) where
10411041
serialiseToRawBytes = serialiseToCBOR
1042-
deserialiseFromRawBytes asType bs =
1042+
deserialiseFromRawBytes asType' bs =
10431043
first (SerialiseAsRawBytesError . show . B.sformat B.build) $
1044-
deserialiseFromCBOR asType bs
1044+
deserialiseFromCBOR asType' bs
10451045

10461046
instance IsPlutusScriptLanguage lang => HasTextEnvelope (PlutusScript lang) where
10471047
textEnvelopeType _ =
@@ -1492,7 +1492,7 @@ parsePaymentKeyHash :: Text -> Aeson.Parser (Hash PaymentKey)
14921492
parsePaymentKeyHash =
14931493
failEitherWith
14941494
(\e -> "Error deserialising payment key hash: " ++ displayError e)
1495-
. deserialiseFromRawBytesHex (AsHash AsPaymentKey)
1495+
. deserialiseFromRawBytesHex
14961496
. Text.encodeUtf8
14971497

14981498
-- ----------------------------------------------------------------------------

cardano-api/src/Cardano/Api/Internal/SerialiseBech32.hs

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
{-# LANGUAGE LambdaCase #-}
33
{-# LANGUAGE OverloadedStrings #-}
44
{-# LANGUAGE ScopedTypeVariables #-}
5+
{-# LANGUAGE TypeApplications #-}
56

67
-- | Bech32 Serialisation
78
module Cardano.Api.Internal.SerialiseBech32
@@ -53,15 +54,16 @@ serialiseToBech32 a =
5354
++ show err
5455

5556
deserialiseFromBech32
56-
:: SerialiseAsBech32 a
57-
=> AsType a -> Text -> Either Bech32DecodeError a
58-
deserialiseFromBech32 asType bech32Str = do
57+
:: forall a
58+
. SerialiseAsBech32 a
59+
=> Text -> Either Bech32DecodeError a
60+
deserialiseFromBech32 bech32Str = do
5961
(prefix, dataPart) <-
6062
Bech32.decodeLenient bech32Str
6163
?!. Bech32DecodingError
6264

6365
let actualPrefix = Bech32.humanReadablePartToText prefix
64-
permittedPrefixes = bech32PrefixesPermitted asType
66+
permittedPrefixes = bech32PrefixesPermitted (asType @a)
6567
guard (actualPrefix `elem` permittedPrefixes)
6668
?! Bech32UnexpectedPrefix actualPrefix (fromList permittedPrefixes)
6769

cardano-api/src/Cardano/Api/Internal/SerialiseJSON.hs

Lines changed: 5 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,6 @@ module Cardano.Api.Internal.SerialiseJSON
1616
where
1717

1818
import Cardano.Api.Internal.Error
19-
import Cardano.Api.Internal.HasTypeProxy
2019
import Cardano.Api.Internal.Pretty
2120

2221
import Control.Monad.Trans.Except (runExceptT)
@@ -44,24 +43,22 @@ prettyPrintJSON = LBS.toStrict . encodePretty
4443

4544
deserialiseFromJSON
4645
:: FromJSON a
47-
=> AsType a
48-
-> ByteString
46+
=> ByteString
4947
-> Either JsonDecodeError a
50-
deserialiseFromJSON _proxy =
48+
deserialiseFromJSON =
5149
either (Left . JsonDecodeError) Right
5250
. Aeson.eitherDecodeStrict'
5351

5452
readFileJSON
5553
:: FromJSON a
56-
=> AsType a
57-
-> FilePath
54+
=> FilePath
5855
-> IO (Either (FileError JsonDecodeError) a)
59-
readFileJSON ttoken path =
56+
readFileJSON path =
6057
runExceptT $ do
6158
content <- fileIOExceptT path BS.readFile
6259
firstExceptT (FileError path) $
6360
hoistEither $
64-
deserialiseFromJSON ttoken content
61+
deserialiseFromJSON content
6562

6663
writeFileJSON
6764
:: ToJSON a

cardano-api/src/Cardano/Api/Internal/SerialiseLedgerCddl.hs

Lines changed: 3 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,6 @@ where
3434

3535
import Cardano.Api.Internal.Eon.ShelleyBasedEra
3636
import Cardano.Api.Internal.Error
37-
import Cardano.Api.Internal.HasTypeProxy
3837
import Cardano.Api.Internal.IO
3938
import Cardano.Api.Internal.Pretty
4039
import Cardano.Api.Internal.Serialise.Cbor.Canonical
@@ -175,12 +174,9 @@ deserialiseWitnessLedgerCddl sbe te =
175174
shelleyBasedEraConstraints sbe $
176175
legacyDecoding te $
177176
mapLeft textEnvelopeErrorToTextEnvelopeCddlError $
178-
deserialiseFromTextEnvelope asType te
177+
deserialiseFromTextEnvelope te
179178
where
180-
asType :: AsType (KeyWitness era)
181-
asType = shelleyBasedEraConstraints sbe $ proxyToAsType Proxy
182-
183-
-- \| This wrapper ensures that we can still decode the key witness
179+
-- This wrapper ensures that we can still decode the key witness
184180
-- that were serialized before we migrated to using 'serialiseToTextEnvelope'
185181
legacyDecoding
186182
:: TextEnvelope
@@ -309,9 +305,7 @@ deserialiseFromTextEnvelopeCddlAnyOf types teCddl =
309305
. ShelleyBasedEra era
310306
-> TextEnvelope
311307
-> Either TextEnvelopeError (Tx era)
312-
deserialiseTxLedgerCddl era =
313-
shelleyBasedEraConstraints era $
314-
deserialiseFromTextEnvelope (shelleyBasedEraConstraints era $ proxyToAsType Proxy)
308+
deserialiseTxLedgerCddl era = shelleyBasedEraConstraints era deserialiseFromTextEnvelope
315309

316310
-- Parse the text into types because this will increase code readability and
317311
-- will make it easier to keep track of the different Cddl descriptions via

0 commit comments

Comments
 (0)