Skip to content

Commit 7b6a520

Browse files
committed
remove bytestring deps
1 parent 257e2e5 commit 7b6a520

File tree

9 files changed

+55
-58
lines changed

9 files changed

+55
-58
lines changed

packages.dhall

+2-6
Original file line numberDiff line numberDiff line change
@@ -7,8 +7,7 @@ let eth-core-deps =
77
sha256:af2751772a729d58edf7056805007934e3687b3079f8a02ac514e705aeab8c42
88

99
let additions =
10-
{ bytestrings = eth-core-deps.bytestrings
11-
, coroutine-transducers =
10+
{ coroutine-transducers =
1211
{ dependencies = [
1312
"console",
1413
"either",
@@ -34,7 +33,6 @@ let additions =
3433
{ dependencies =
3534
[ "argonaut"
3635
, "arrays"
37-
, "bytestrings"
3836
, "effect"
3937
, "either"
4038
, "foldable-traversable"
@@ -51,16 +49,14 @@ let additions =
5149
, "ordered-collections"
5250
, "partial"
5351
, "prelude"
54-
, "quotient"
5552
, "simple-json"
5653
, "strings"
5754
, "unfoldable"
5855
, "unsafe-coerce"
5956
]
6057
, repo = "https://github.com/f-o-a-m/purescript-eth-core"
61-
, version = "v10.1.0"
58+
, version = "remove-bs-dep"
6259
}
63-
, quotient = eth-core-deps.quotient
6460
}
6561

6662
in upstream // additions

spago.dhall

+2-2
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44
, "argonaut"
55
, "arrays"
66
, "bifunctors"
7-
, "bytestrings"
87
, "control"
98
, "coroutine-transducers"
109
, "coroutines"
@@ -18,8 +17,10 @@
1817
, "fork"
1918
, "gen"
2019
, "heterogeneous"
20+
, "identity"
2121
, "maybe"
2222
, "newtype"
23+
, "node-buffer"
2324
, "parallel"
2425
, "parsing"
2526
, "partial"
@@ -37,7 +38,6 @@
3738
, "unfoldable"
3839
, "unsafe-coerce"
3940
, "variant"
40-
, "identity"
4141
]
4242
, packages = ./packages.dhall
4343
, sources = [ "src/**/*.purs" ]

src/Network/Ethereum/Web3.purs

+2-2
Original file line numberDiff line numberDiff line change
@@ -11,11 +11,11 @@ import Network.Ethereum.Web3.Contract.Events (event', EventHandler, MultiFilterS
1111
import Network.Ethereum.Web3.Solidity
1212
( Address
1313
, BigNumber
14-
, ByteString
14+
, ImmutableBuffer
1515
, BytesN
1616
, UIntN
1717
, Vector
18-
, fromByteString
18+
, fromBuffer
1919
, abiDecode
2020
, intNFromBigNumber
2121
, nilVector

src/Network/Ethereum/Web3/Solidity.purs

+3-3
Original file line numberDiff line numberDiff line change
@@ -8,13 +8,13 @@ module Network.Ethereum.Web3.Solidity
88
, module Network.Ethereum.Web3.Solidity.AbiEncoding
99
, module Network.Ethereum.Web3.Solidity.Event
1010
, module Network.Ethereum.Types
11-
, module Data.ByteString
11+
, module Node.Buffer.Immutable
1212
) where
1313

14-
import Data.ByteString (ByteString)
14+
import Node.Buffer.Immutable (ImmutableBuffer)
1515
import Network.Ethereum.Types (BigNumber, Address)
1616
import Network.Ethereum.Web3.Solidity.AbiEncoding (class ABIDecode, class ABIEncode, class EncodingType, abiDecode, isDynamic, abiEncode)
17-
import Network.Ethereum.Web3.Solidity.Bytes (BytesN, unBytesN, proxyBytesN, update, fromByteString)
17+
import Network.Ethereum.Web3.Solidity.Bytes (BytesN, unBytesN, proxyBytesN, update, fromBuffer)
1818
import Network.Ethereum.Web3.Solidity.Event (class DecodeEvent, decodeEvent, class IndexedEvent, isAnonymous)
1919
import Network.Ethereum.Web3.Solidity.Int (IntN, unIntN, intNFromBigNumber)
2020
import Network.Ethereum.Web3.Solidity.Internal (class RecordFieldsIso, fromRecord, toRecord)

src/Network/Ethereum/Web3/Solidity/AbiEncoding.purs

+14-13
Original file line numberDiff line numberDiff line change
@@ -16,9 +16,10 @@ module Network.Ethereum.Web3.Solidity.AbiEncoding
1616

1717
import Prelude
1818

19+
import Node.Encoding (Encoding(UTF8))
1920
import Data.Array (foldMap, foldl, length, sortBy, (:))
20-
import Data.ByteString (ByteString)
21-
import Data.ByteString (toUTF8, fromUTF8, length) as BS
21+
import Node.Buffer.Immutable (ImmutableBuffer)
22+
import Node.Buffer.Immutable as B
2223
import Data.Either (Either)
2324
import Data.Functor.Tagged (Tagged, tagged, untagged)
2425
import Data.Generic.Rep (class Generic, Argument(..), Constructor(..), NoArguments(..), Product(..), from, repOf, to)
@@ -32,7 +33,7 @@ import Data.Traversable (foldMapDefaultR)
3233
import Data.Tuple (Tuple(..))
3334
import Data.Unfoldable (replicateA)
3435
import Network.Ethereum.Core.BigNumber (fromString, fromTwosComplement, toString, toTwosComplement, unsafeToInt)
35-
import Network.Ethereum.Core.HexString (HexString, PadByte(..), fromByteString, mkHexString, numberOfBytes, padLeft, padRight, splitAtByteOffset, toByteString, unHex)
36+
import Network.Ethereum.Core.HexString (HexString, PadByte(..), fromBuffer, mkHexString, numberOfBytes, padLeft, padRight, splitAtByteOffset, toBuffer, unHex)
3637
import Network.Ethereum.Types (Address, BigNumber, fromInt, mkAddress, unAddress)
3738
import Network.Ethereum.Web3.Solidity.Bytes (BytesN, unBytesN, update, proxyBytesN)
3839
import Network.Ethereum.Web3.Solidity.Int (IntN, unIntN, intNFromBigNumber)
@@ -67,7 +68,7 @@ else instance EncodingType (BytesN n) where
6768
isDynamic = const false
6869
else instance EncodingType a => EncodingType (Vector n a) where
6970
isDynamic _ = isDynamic (Proxy :: Proxy a)
70-
else instance EncodingType ByteString where
71+
else instance EncodingType ImmutableBuffer where
7172
isDynamic = const true
7273
else instance EncodingType a => EncodingType (Tagged s a) where
7374
isDynamic _ = isDynamic (Proxy :: Proxy a)
@@ -114,11 +115,11 @@ else instance Reflectable n Int => ABIEncode (BytesN n) where
114115
else instance Reflectable n Int => ABIEncode (IntN n) where
115116
abiEncode a = int256HexBuilder <<< unIntN $ a
116117

117-
else instance ABIEncode ByteString where
118-
abiEncode bytes = uInt256HexBuilder (fromInt $ BS.length bytes) <> bytesBuilder bytes
118+
else instance ABIEncode ImmutableBuffer where
119+
abiEncode bytes = uInt256HexBuilder (fromInt $ B.size bytes) <> bytesBuilder bytes
119120

120121
else instance ABIEncode String where
121-
abiEncode = abiEncode <<< BS.toUTF8
122+
abiEncode = abiEncode <<< \a -> B.fromString a UTF8
122123

123124
else instance ABIEncode a => ABIEncode (Array a) where
124125
abiEncode l =
@@ -221,8 +222,8 @@ factorBuilder a = Endo \encoded ->
221222
} : map (\x -> x { order = x.order + 1 }) encoded
222223

223224
-- | base16 encode, then utf8 encode, then pad
224-
bytesBuilder :: ByteString -> HexString
225-
bytesBuilder = padRight Zero <<< fromByteString
225+
bytesBuilder :: ImmutableBuffer -> HexString
226+
bytesBuilder = padRight Zero <<< fromBuffer
226227

227228
-- | Encode something that is essentaially a signed integer.
228229
int256HexBuilder :: BigNumber -> HexString
@@ -267,13 +268,13 @@ else instance ABIDecode Address where
267268
maddr <- mkAddress <$> parseBytes 20
268269
maybe (fail "Address is 20 bytes, receieved more") pure maddr
269270

270-
else instance ABIDecode ByteString where
271+
else instance ABIDecode ImmutableBuffer where
271272
_abiDecode = do
272273
len <- _abiDecode
273-
toByteString <$> parseBytes len
274+
toBuffer <$> parseBytes len
274275

275276
else instance ABIDecode String where
276-
_abiDecode = BS.fromUTF8 <$> _abiDecode
277+
_abiDecode = B.toString UTF8 <$> _abiDecode
277278

278279
else instance Reflectable n Int => ABIDecode (BytesN n) where
279280
_abiDecode = do
@@ -282,7 +283,7 @@ else instance Reflectable n Int => ABIDecode (BytesN n) where
282283
zeroBytes = 32 - len
283284
raw <- parseBytes len
284285
_ <- parseBytes zeroBytes
285-
pure <<< update proxyBytesN <<< toByteString $ raw
286+
pure <<< update proxyBytesN <<< toBuffer $ raw
286287

287288
else instance (Reflectable n Int, ABIDecode a) => ABIDecode (Vector n a) where
288289
_abiDecode =

src/Network/Ethereum/Web3/Solidity/Bytes.purs

+13-12
Original file line numberDiff line numberDiff line change
@@ -3,15 +3,16 @@ module Network.Ethereum.Web3.Solidity.Bytes
33
, unBytesN
44
, proxyBytesN
55
, update
6-
, fromByteString
6+
, fromBuffer
77
, generator
88
) where
99

1010
import Prelude
1111

1212
import Control.Monad.Gen (class MonadGen)
13-
import Data.ByteString (empty, ByteString, Encoding(Hex))
14-
import Data.ByteString as BS
13+
import Node.Buffer.Immutable (ImmutableBuffer)
14+
import Node.Buffer.Immutable as B
15+
import Node.Encoding (Encoding(Hex))
1516
import Data.Maybe (Maybe(..), fromJust)
1617
import Data.Reflectable (class Reflectable, reflectType)
1718
import Network.Ethereum.Core.HexString as Hex
@@ -24,32 +25,32 @@ import Type.Proxy (Proxy(..))
2425
--------------------------------------------------------------------------------
2526
-- Represents a statically sized bytestring of size `n` bytes.
2627
-- | See module [Network.Ethereum.Web3.Solidity.Sizes](/Network.Ethereum.Web3.Solidity.Sizes) for some predefined sizes.
27-
newtype BytesN (n :: Int) = BytesN ByteString
28+
newtype BytesN (n :: Int) = BytesN ImmutableBuffer
2829

2930
derive newtype instance eqBytesN :: Eq (BytesN n)
3031
instance showBytesN :: Show (BytesN n) where
31-
show (BytesN bs) = show <<< unsafePartial fromJust <<< mkHexString $ BS.toString bs Hex
32+
show (BytesN bs) = show <<< unsafePartial fromJust <<< mkHexString $ B.toString Hex bs
3233

3334
generator :: forall n m. Reflectable n Int => MonadGen m => Proxy n -> m (BytesN n)
3435
generator p = do
3536
bs <- Hex.generator (reflectType p)
36-
pure $ BytesN $ Hex.toByteString bs
37+
pure $ BytesN $ Hex.toBuffer bs
3738

3839
-- | Access the underlying raw bytestring
39-
unBytesN :: forall n. BytesN n -> ByteString
40+
unBytesN :: forall n. BytesN n -> ImmutableBuffer
4041
unBytesN (BytesN bs) = bs
4142

4243
proxyBytesN :: forall n. BytesN n
43-
proxyBytesN = BytesN empty
44+
proxyBytesN = BytesN $ B.fromArray []
4445

45-
update :: forall n. BytesN n -> ByteString -> BytesN n
46+
update :: forall n. BytesN n -> ImmutableBuffer -> BytesN n
4647
update _ = BytesN
4748

4849
-- | Attempt to coerce a bytestring into one of the appropriate size.
4950
-- | See module [Network.Ethereum.Web3.Solidity.Sizes](/Network.Ethereum.Web3.Solidity.Sizes) for some predefined sizes.
50-
fromByteString :: forall proxy n. Reflectable n Int => proxy n -> ByteString -> Maybe (BytesN n)
51-
fromByteString _ bs =
52-
if not $ BS.length bs <= reflectType (Proxy :: Proxy n) then
51+
fromBuffer :: forall proxy n. Reflectable n Int => proxy n -> ImmutableBuffer -> Maybe (BytesN n)
52+
fromBuffer _ bs =
53+
if not $ B.size bs <= reflectType (Proxy :: Proxy n) then
5354
Nothing
5455
else
5556
Just $ BytesN bs

test.dhall

-1
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,6 @@ in conf
1313
, "nonempty"
1414
, "quickcheck"
1515
, "quickcheck-laws"
16-
, "quotient"
1716
, "spec"
1817
, "unsafe-coerce"
1918
]

test/web3/Web3Spec/Encoding/ContainersSpec.purs

+3-3
Original file line numberDiff line numberDiff line change
@@ -54,7 +54,7 @@ typePropertyTests =
5454
it "can encode/decode bytestring" $ liftEffect $ do
5555
quickCheckGen $ do
5656
n <- chooseInt 1 100
57-
x <- Hex.toByteString <$> Hex.generator n
57+
x <- Hex.toBuffer <$> Hex.generator n
5858
pure $ encodeDecode x === Right x
5959

6060
it "can encode/decode bool" $ liftEffect $ do
@@ -300,7 +300,7 @@ tupleTests = do
300300
reifyType m \pm ->
301301
reifyType k \pk -> do
302302
ints <- arrayOf (IntN.generator pn)
303-
bytes <- Hex.toByteString <$> (chooseInt 1 100 >>= Hex.generator)
303+
bytes <- Hex.toBuffer <$> (chooseInt 1 100 >>= Hex.generator)
304304
addrs <- Vector.generator pm (arrayOf Address.generator)
305305
strings <- arrayOf (Vector.generator pk (arbitrary @BMPString))
306306
bool <- arbitrary :: Gen Boolean
@@ -364,7 +364,7 @@ tupleTests = do
364364
let
365365
mkTuple5 = do
366366
ints <- arrayOf (IntN.generator _pn)
367-
bytes <- Hex.toByteString <$> (chooseInt 1 100 >>= Hex.generator)
367+
bytes <- Hex.toBuffer <$> (chooseInt 1 100 >>= Hex.generator)
368368
addrs <- Vector.generator _pm (arrayOf Address.generator)
369369
strings <- map (map (un BMPString)) <$>
370370
arrayOf (Vector.generator _pk (arbitrary @BMPString))

test/web3/Web3Spec/Live/RPCSpec.purs

+16-16
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,9 @@
11
module Web3Spec.Live.RPCSpec (spec) where
22

33
import Prelude
4-
import Data.Array ((!!))
5-
import Data.ByteString as BS
4+
import Data.Array ((!!), last)
5+
import Node.Buffer.Immutable as B
6+
import Node.Encoding (Encoding(UTF8))
67
import Data.Either (isRight)
78
import Data.Lens ((?~), (%~))
89
import Data.Maybe (Maybe(..), fromJust)
@@ -13,11 +14,9 @@ import Network.Ethereum.Core.Keccak256 (keccak256)
1314
import Network.Ethereum.Core.Signatures as Sig
1415
import Network.Ethereum.Web3 (Block(..), ChainCursor(..), Provider, TransactionReceipt(..), _from, _to, _value, convert, defaultTransactionOptions, fromMinorUnit, mkHexString, runWeb3)
1516
import Network.Ethereum.Web3.Api as Api
16-
import Node.Buffer.Class (slice)
1717
import Partial.Unsafe (unsafePartial)
1818
import Test.Spec (SpecT, describe, it)
1919
import Test.Spec.Assertions (shouldEqual, shouldSatisfy)
20-
import Type.Quotient (runQuotient)
2120
import Web3Spec.Live.Utils (assertWeb3, pollTransactionReceipt)
2221

2322
spec :: Provider -> SpecT Aff Unit Aff Unit
@@ -111,7 +110,7 @@ spec provider =
111110
signer `shouldEqual` signer'
112111
-- make sure that we can recover the signature in purescript natively
113112
let
114-
rsvSignature = case signatureFromByteString <<< Hex.toByteString $ signatureHex of
113+
rsvSignature = case signatureFromByteString <<< Hex.toBuffer $ signatureHex of
115114
Sig.Signature sig -> Sig.Signature sig { v = sig.v - 27 }
116115
Sig.publicToAddress (Sig.recoverSender fullHashedMessageBS rsvSignature) `shouldEqual` signer
117116
it "Can call eth_estimateGas" do
@@ -141,28 +140,29 @@ spec provider =
141140
pure $ Tuple tx tx'
142141
tx `shouldEqual` tx'
143142

144-
signatureFromByteString :: BS.ByteString -> Sig.Signature
145-
signatureFromByteString bs =
143+
signatureFromByteString :: B.ImmutableBuffer -> Sig.Signature
144+
signatureFromByteString bfr =
146145
let
147-
bfr = BS.unsafeThaw bs
148146

149-
r = Hex.fromByteString $ BS.unsafeFreeze $ slice 0 32 bfr
147+
r = Hex.fromBuffer $ B.slice 0 32 bfr
150148

151-
s = Hex.fromByteString $ BS.unsafeFreeze $ slice 32 64 bfr
149+
s = Hex.fromBuffer $ B.slice 32 64 bfr
152150

153-
v = runQuotient $ unsafePartial fromJust $ BS.last bs
151+
v = unsafePartial fromJust $ last $ B.toArray bfr
154152
in
155153
Sig.Signature { r, s, v }
156154

157155
makeRidiculousEthereumMessage :: Hex.HexString -> Hex.HexString
158156
makeRidiculousEthereumMessage s =
159157
let
160158
prefix =
161-
Hex.fromByteString
162-
$ BS.toUTF8
163-
$ "\x19" -- NOTE: 19 in hexadecimal is 25
159+
Hex.fromBuffer
160+
$ B.fromString
161+
( "\x19" -- NOTE: 19 in hexadecimal is 25
164162

165-
<> "Ethereum Signed Message:\n" -- NOTE: length of this string is 25
166-
<> show (Hex.numberOfBytes s)
163+
<> "Ethereum Signed Message:\n" -- NOTE: length of this string is 25
164+
<> show (Hex.numberOfBytes s)
165+
)
166+
UTF8
167167
in
168168
prefix <> s

0 commit comments

Comments
 (0)