Skip to content

Commit

Permalink
remove arb tuples
Browse files Browse the repository at this point in the history
  • Loading branch information
martyall committed Sep 14, 2023
1 parent 7722e44 commit 5815988
Show file tree
Hide file tree
Showing 2 changed files with 1 addition and 63 deletions.
52 changes: 1 addition & 51 deletions src/Network/Ethereum/Web3/Solidity/Tuple.purs
Original file line number Diff line number Diff line change
@@ -1,13 +1,13 @@
module Network.Ethereum.Web3.Solidity.Tuple
( Tuple0(..)
, Tuple1(..)
, Tuple10(..)
, Tuple11(..)
, Tuple12(..)
, Tuple13(..)
, Tuple14(..)
, Tuple15(..)
, Tuple16(..)
, Tuple1(..)
, Tuple2(..)
, Tuple3(..)
, Tuple4(..)
Expand Down Expand Up @@ -56,8 +56,6 @@ import Prelude
import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic)
import Data.Show.Generic (genericShow)
import Test.QuickCheck (class Arbitrary)
import Test.QuickCheck.Arbitrary (genericArbitrary)

-- * Tuple0
data Tuple0 = Tuple0
Expand All @@ -70,9 +68,6 @@ instance Show Tuple0 where
instance Eq Tuple0 where
eq _ _ = true

instance Arbitrary Tuple0 where
arbitrary = pure Tuple0

-- * Tuple 1
newtype Tuple1 a = Tuple1 a

Expand All @@ -87,9 +82,6 @@ instance Show a => Show (Tuple1 a) where
instance Eq a => Eq (Tuple1 a) where
eq = genericEq

instance Arbitrary a => Arbitrary (Tuple1 a) where
arbitrary = genericArbitrary

uncurry1 :: forall a b. (a -> b) -> Tuple1 a -> b
uncurry1 fun (Tuple1 a) = fun a

Expand All @@ -113,9 +105,6 @@ uncurry2 fun (Tuple2 a b) = fun a b
curry2 :: forall a b c. (Tuple2 a b -> c) -> a -> b -> c
curry2 fun a b = fun (Tuple2 a b)

instance (Arbitrary a, Arbitrary b) => Arbitrary (Tuple2 a b) where
arbitrary = genericArbitrary

-- * Tuple3
data Tuple3 a b c = Tuple3 a b c

Expand All @@ -127,9 +116,6 @@ instance (Show a, Show b, Show c) => Show (Tuple3 a b c) where
instance (Eq a, Eq b, Eq c) => Eq (Tuple3 a b c) where
eq = genericEq

instance (Arbitrary a, Arbitrary b, Arbitrary c) => Arbitrary (Tuple3 a b c) where
arbitrary = genericArbitrary

uncurry3 :: forall a b c d. (a -> b -> c -> d) -> Tuple3 a b c -> d
uncurry3 fun (Tuple3 a b c) = fun a b c

Expand All @@ -153,9 +139,6 @@ uncurry4 fun (Tuple4 a b c d) = fun a b c d
curry4 :: forall a b c d e. (Tuple4 a b c d -> e) -> a -> b -> c -> d -> e
curry4 fun a b c d = fun (Tuple4 a b c d)

instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => Arbitrary (Tuple4 a b c d) where
arbitrary = genericArbitrary

-- * Tuple5
data Tuple5 a b c d e = Tuple5 a b c d e

Expand Down Expand Up @@ -184,9 +167,6 @@ instance (Show a, Show b, Show c, Show d, Show e, Show f) => Show (Tuple6 a b c
instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (Tuple6 a b c d e f) where
eq = genericEq

instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f) => Arbitrary (Tuple6 a b c d e f) where
arbitrary = genericArbitrary

uncurry6 :: forall a b c d e f g. (a -> b -> c -> d -> e -> f -> g) -> Tuple6 a b c d e f -> g
uncurry6 fun (Tuple6 a b c d e f) = fun a b c d e f

Expand All @@ -204,9 +184,6 @@ instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (Tuple
instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (Tuple7 a b c d e f g) where
eq = genericEq

instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g) => Arbitrary (Tuple7 a b c d e f g) where
arbitrary = genericArbitrary

uncurry7 :: forall a b c d e f g h. (a -> b -> c -> d -> e -> f -> g -> h) -> Tuple7 a b c d e f g -> h
uncurry7 fun (Tuple7 a b c d e f g) = fun a b c d e f g

Expand All @@ -221,9 +198,6 @@ derive instance Generic (Tuple8 a b c d e f g h) _
instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h) => Show (Tuple8 a b c d e f g h) where
show = genericShow

instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h) => Arbitrary (Tuple8 a b c d e f g h) where
arbitrary = genericArbitrary

uncurry8 :: forall a b c d e f g h i. (a -> b -> c -> d -> e -> f -> g -> h -> i) -> Tuple8 a b c d e f g h -> i
uncurry8 fun (Tuple8 a b c d e f g h) = fun a b c d e f g h

Expand All @@ -241,9 +215,6 @@ instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i
instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (Tuple9 a b c d e f g h i) where
eq = genericEq

instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h, Arbitrary i) => Arbitrary (Tuple9 a b c d e f g h i) where
arbitrary = genericArbitrary

uncurry9 :: forall a b c d e f g h i j. (a -> b -> c -> d -> e -> f -> g -> h -> i -> j) -> Tuple9 a b c d e f g h i -> j
uncurry9 fun (Tuple9 a b c d e f g h i) = fun a b c d e f g h i

Expand All @@ -261,9 +232,6 @@ instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i
instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (Tuple10 a b c d e f g h i j) where
eq = genericEq

instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h, Arbitrary i, Arbitrary j) => Arbitrary (Tuple10 a b c d e f g h i j) where
arbitrary = genericArbitrary

uncurry10 :: forall a b c d e f g h i j k. (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k) -> Tuple10 a b c d e f g h i j -> k
uncurry10 fun (Tuple10 a b c d e f g h i j) = fun a b c d e f g h i j

Expand All @@ -278,9 +246,6 @@ derive instance Generic (Tuple11 a b c d e f g h i j k) _
instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k) => Show (Tuple11 a b c d e f g h i j k) where
show = genericShow

instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h, Arbitrary i, Arbitrary j, Arbitrary k) => Arbitrary (Tuple11 a b c d e f g h i j k) where
arbitrary = genericArbitrary

uncurry11 :: forall a b c d e f g h i j k l. (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l) -> Tuple11 a b c d e f g h i j k -> l
uncurry11 fun (Tuple11 a b c d e f g h i j k) = fun a b c d e f g h i j k

Expand All @@ -298,9 +263,6 @@ instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i
instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (Tuple12 a b c d e f g h i j k l) where
eq = genericEq

instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h, Arbitrary i, Arbitrary j, Arbitrary k, Arbitrary l) => Arbitrary (Tuple12 a b c d e f g h i j k l) where
arbitrary = genericArbitrary

uncurry12 :: forall a b c d e f g h i j k l m. (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m) -> Tuple12 a b c d e f g h i j k l -> m
uncurry12 fun (Tuple12 a b c d e f g h i j k l) = fun a b c d e f g h i j k l

Expand All @@ -318,9 +280,6 @@ instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i
instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (Tuple13 a b c d e f g h i j k l m) where
eq = genericEq

instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h, Arbitrary i, Arbitrary j, Arbitrary k, Arbitrary l, Arbitrary m) => Arbitrary (Tuple13 a b c d e f g h i j k l m) where
arbitrary = genericArbitrary

uncurry13 :: forall a b c d e f g h i j k l m n. (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n) -> Tuple13 a b c d e f g h i j k l m -> n
uncurry13 fun (Tuple13 a b c d e f g h i j k l m) = fun a b c d e f g h i j k l m

Expand All @@ -338,9 +297,6 @@ instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i
instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (Tuple14 a b c d e f g h i j k l m n) where
eq = genericEq

instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h, Arbitrary i, Arbitrary j, Arbitrary k, Arbitrary l, Arbitrary m, Arbitrary n) => Arbitrary (Tuple14 a b c d e f g h i j k l m n) where
arbitrary = genericArbitrary

uncurry14 :: forall a b c d e f g h i j k l m n o. (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> o) -> Tuple14 a b c d e f g h i j k l m n -> o
uncurry14 fun (Tuple14 a b c d e f g h i j k l m n) = fun a b c d e f g h i j k l m n

Expand All @@ -358,9 +314,6 @@ instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i
instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (Tuple15 a b c d e f g h i j k l m n o) where
eq = genericEq

instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h, Arbitrary i, Arbitrary j, Arbitrary k, Arbitrary l, Arbitrary m, Arbitrary n, Arbitrary o) => Arbitrary (Tuple15 a b c d e f g h i j k l m n o) where
arbitrary = genericArbitrary

uncurry15 :: forall a b c d e f g h i j k l m n o p. (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> o -> p) -> Tuple15 a b c d e f g h i j k l m n o -> p
uncurry15 fun (Tuple15 a b c d e f g h i j k l m n o) = fun a b c d e f g h i j k l m n o

Expand All @@ -378,9 +331,6 @@ instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i
instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o, Eq p) => Eq (Tuple16 a b c d e f g h i j k l m n o p) where
eq = genericEq

instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h, Arbitrary i, Arbitrary j, Arbitrary k, Arbitrary l, Arbitrary m, Arbitrary n, Arbitrary o, Arbitrary p) => Arbitrary (Tuple16 a b c d e f g h i j k l m n o p) where
arbitrary = genericArbitrary

uncurry16 :: forall a b c d e f g h i j k l m n o p q. (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> n -> o -> p -> q) -> Tuple16 a b c d e f g h i j k l m n o p -> q
uncurry16 fun (Tuple16 a b c d e f g h i j k l m n o p) = fun a b c d e f g h i j k l m n o p

Expand Down
12 changes: 0 additions & 12 deletions src/Network/Ethereum/Web3/Solidity/UInt.purs
Original file line number Diff line number Diff line change
Expand Up @@ -13,8 +13,6 @@ import Data.Reflectable (class Reflectable, reflectType)
import Network.Ethereum.Core.BigNumber (BigNumber, embed, fromString, pow)
import Network.Ethereum.Core.HexString as Hex
import Partial.Unsafe (unsafePartial)
import Test.QuickCheck (class Arbitrary)
import Test.QuickCheck.Gen as Gen
import Type.Proxy (Proxy(..))

--------------------------------------------------------------------------------
Expand Down Expand Up @@ -43,16 +41,6 @@ generator p = do
else unsafePartial $ fromJust $ fromString $ Hex.unHex bs
pure $ UIntN $ if a < zero then -a else a

instance Reflectable n Int => Arbitrary (UIntN n) where
arbitrary = do
nBytes <- (flip div 8) <$> Gen.chooseInt 1 (reflectType (Proxy @n))
bs <- Hex.generator nBytes
let
a =
if bs == mempty then zero
else unsafePartial $ fromJust $ fromString $ Hex.unHex bs
pure $ UIntN $ if a < zero then -a else a

-- | Access the raw underlying unsigned integer
unUIntN :: forall n. UIntN n -> BigNumber
unUIntN (UIntN a) = a
Expand Down

0 comments on commit 5815988

Please sign in to comment.