Skip to content

Commit

Permalink
Remove orphan instances from pact-5
Browse files Browse the repository at this point in the history
  • Loading branch information
jmcardon committed Jul 19, 2024
1 parent 80b76c1 commit 18b9b72
Show file tree
Hide file tree
Showing 5 changed files with 593 additions and 470 deletions.
6 changes: 3 additions & 3 deletions pact-tests/Pact/Core/Test/SerialiseTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ module Pact.Core.Test.SerialiseTests where

import Pact.Core.Serialise
import Pact.Core.Gen
import Pact.Core.Serialise.CBOR_V1 ()
import Pact.Core.Serialise.CBOR_V1
import qualified Codec.Serialise as S
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.Hedgehog
Expand Down Expand Up @@ -72,10 +72,10 @@ tests = testGroup "Serialise Roundtrip"

-- | For any CBOR-Serialisable and `Gen` type, assert that serialization
-- roundtrips.
serialiseRoundtrip :: forall a. (S.Serialise a, Show a, Eq a) => Gen a -> Property
serialiseRoundtrip :: forall a. (S.Serialise (SerialiseV1 a), Show a, Eq a) => Gen a -> Property
serialiseRoundtrip g = property $ do
expr <- forAll g
S.deserialise (S.serialise expr) === expr
_getSV1 (S.deserialise (S.serialise (SerialiseV1 expr))) === expr

documentVersionGen :: Gen DocumentVersion
documentVersionGen = Gen.element [minBound .. maxBound]
Expand Down
5 changes: 4 additions & 1 deletion pact/Pact/Core/Guards.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE DerivingStrategies #-}


module Pact.Core.Guards
Expand Down Expand Up @@ -44,6 +45,7 @@ import Data.Maybe (isJust)
import Data.Text(Text)
import GHC.Generics
import Text.Parser.Token as P
import Codec.Serialise.Class (Serialise)

import qualified Data.Text as T
import qualified Data.Text.Encoding as T
Expand All @@ -60,7 +62,8 @@ import qualified Pact.Crypto.WebAuthn.Cose.PublicKeyWithSignAlg as WA
import qualified Pact.Crypto.WebAuthn.Cose.SignAlg as WA

newtype PublicKeyText = PublicKeyText { _pubKey :: Text }
deriving (Eq,Ord,Show, NFData)
deriving (Eq,Ord,Show)
deriving newtype (NFData, Serialise)

instance Pretty PublicKeyText where
pretty (PublicKeyText t) = pretty t
Expand Down
3 changes: 2 additions & 1 deletion pact/Pact/Core/Names.hs
Original file line number Diff line number Diff line change
Expand Up @@ -75,6 +75,7 @@ import Data.Word(Word64)
import Control.Applicative((<|>))
import Control.DeepSeq
import GHC.Generics
import Codec.Serialise.Class(Serialise)
import qualified Data.Char as Char
import qualified Text.Megaparsec as MP
import qualified Text.Megaparsec.Char as MP
Expand Down Expand Up @@ -194,7 +195,7 @@ instance Pretty ParsedName where
-- So in Field "a" in {"a":v},
newtype Field = Field { _field :: Text }
deriving (Eq, Ord, Show, Generic, FromJSONKey)
deriving newtype (IsString, NFData)
deriving newtype (IsString, NFData, Serialise)

instance Pretty Field where
pretty (Field f) = pretty f
Expand Down
Loading

0 comments on commit 18b9b72

Please sign in to comment.