@@ -46,13 +46,13 @@ import Prelude
4646
4747import Control.Alt (class Alt )
4848import Control.Alternative (class Alternative , class Plus , (<|>))
49- import Control.Monad.Aff (Aff , Fiber , ParAff , forkAff , liftEff' , throwError )
49+ import Control.Monad.Aff (Aff , Fiber , ParAff , forkAff , liftEff' )
5050import Control.Monad.Aff.Class (class MonadAff , liftAff )
5151import Control.Monad.Eff (kind Effect )
5252import Control.Monad.Eff.Class (class MonadEff )
5353import Control.Monad.Eff.Exception (Error , throwException )
5454import Control.Monad.Error.Class (class MonadThrow , catchError )
55- import Control.Monad.Except (ExceptT , except , runExceptT )
55+ import Control.Monad.Except (ExceptT , runExceptT )
5656import Control.Monad.Reader (class MonadAsk , class MonadReader , ReaderT , ask , runReaderT )
5757import Control.Monad.Rec.Class (class MonadRec )
5858import Control.Parallel.Class (class Parallel , parallel , sequential )
@@ -61,7 +61,6 @@ import Data.Foreign (F, Foreign, ForeignError(..), fail, isNull, readBoolean, re
6161import Data.Foreign.Class (class Decode , class Encode , decode , encode )
6262import Data.Foreign.Generic (defaultOptions , genericDecode , genericEncode )
6363import Data.Foreign.Index (readProp )
64- import Data.Foreign.NullOrUndefined (NullOrUndefined (..), unNullOrUndefined )
6564import Data.Functor.Compose (Compose )
6665import Data.Generic.Rep (class Generic )
6766import Data.Generic.Rep.Eq (genericEq )
@@ -70,12 +69,9 @@ import Data.Lens.Lens (Lens', Lens, lens)
7069import Data.Maybe (Maybe (..))
7170import Data.Newtype (class Newtype , unwrap )
7271import Data.Ordering (invert )
73- import Data.Record as Record
74- import Data.Symbol (SProxy (..))
7572import Network.Ethereum.Types (Address , BigNumber , HexString )
7673import Network.Ethereum.Web3.Types.EtherUnit (class EtherUnit , NoPay , Value , Wei , convert )
7774import Network.Ethereum.Web3.Types.Provider (Provider )
78- import Simple.JSON (read )
7975
8076-- ------------------------------------------------------------------------------
8177-- * Block
@@ -128,11 +124,11 @@ newtype Block
128124 , extraData :: HexString
129125 , gasLimit :: BigNumber
130126 , gasUsed :: BigNumber
131- , hash :: HexString
132- , logsBloom :: HexString
127+ , hash :: Maybe HexString
128+ , logsBloom :: Maybe HexString
133129 , miner :: HexString
134- , nonce :: HexString
135- , number :: BigNumber
130+ , nonce :: Maybe HexString
131+ , number :: Maybe BigNumber
136132 , parentHash :: HexString
137133 , receiptsRoot :: HexString
138134 , sha3Uncles :: HexString
@@ -153,18 +149,7 @@ instance showBlock :: Show Block where
153149 show = genericShow
154150
155151instance decodeBlock :: Decode Block where
156- decode x = catchError (genericDecode decodeOpts x)
157- -- if this attempt fails for any reason pass back the original error
158- \origError -> catchError tryKovanAuthorHack (\_ -> throwError origError)
159- where
160- decodeOpts = defaultOptions { unwrapSingleConstructors = true }
161- tryKovanAuthorHack = do
162- rec <- except $ read x
163- let blockRec = Record .delete (SProxy :: SProxy " author" ) rec
164- # Record .insert (SProxy :: SProxy " nonce" ) rec.author
165- pure $ Block blockRec
166-
167-
152+ decode x = genericDecode (defaultOptions { unwrapSingleConstructors = true }) x
168153
169154-- ------------------------------------------------------------------------------
170155-- * Transaction
@@ -173,11 +158,11 @@ instance decodeBlock :: Decode Block where
173158newtype Transaction =
174159 Transaction { hash :: HexString
175160 , nonce :: BigNumber
176- , blockHash :: HexString
177- , blockNumber :: BlockNumber
178- , transactionIndex :: BigNumber
161+ , blockHash :: Maybe HexString
162+ , blockNumber :: Maybe BlockNumber
163+ , transactionIndex :: Maybe BigNumber
179164 , from :: Address
180- , to :: NullOrUndefined Address
165+ , to :: Maybe Address
181166 , value :: Value Wei
182167 , gas :: BigNumber
183168 , gasPrice :: BigNumber
@@ -221,7 +206,7 @@ newtype TransactionReceipt =
221206 , blockNumber :: BlockNumber
222207 , cumulativeGasUsed :: BigNumber
223208 , gasUsed :: BigNumber
224- , contractAddress :: NullOrUndefined Address
209+ , contractAddress :: Maybe Address
225210 , logs :: Array Change
226211 , status :: TransactionStatus
227212 }
@@ -241,13 +226,13 @@ instance decodeTxReceipt :: Decode TransactionReceipt where
241226-- ------------------------------------------------------------------------------
242227
243228newtype TransactionOptions u =
244- TransactionOptions { from :: NullOrUndefined Address
245- , to :: NullOrUndefined Address
246- , value :: NullOrUndefined (Value u )
247- , gas :: NullOrUndefined BigNumber
248- , gasPrice :: NullOrUndefined BigNumber
249- , data :: NullOrUndefined HexString
250- , nonce :: NullOrUndefined BigNumber
229+ TransactionOptions { from :: Maybe Address
230+ , to :: Maybe Address
231+ , value :: Maybe (Value u )
232+ , gas :: Maybe BigNumber
233+ , gasPrice :: Maybe BigNumber
234+ , data :: Maybe HexString
235+ , nonce :: Maybe BigNumber
251236 }
252237
253238derive instance genericTransactionOptions :: Generic (TransactionOptions u ) _
@@ -262,42 +247,42 @@ instance encodeTransactionOptions :: Encode (TransactionOptions u) where
262247
263248defaultTransactionOptions :: TransactionOptions NoPay
264249defaultTransactionOptions =
265- TransactionOptions { from : NullOrUndefined Nothing
266- , to : NullOrUndefined Nothing
267- , value : NullOrUndefined Nothing
268- , gas : NullOrUndefined Nothing
269- , gasPrice : NullOrUndefined Nothing
270- , data : NullOrUndefined Nothing
271- , nonce : NullOrUndefined Nothing
250+ TransactionOptions { from: Nothing
251+ , to: Nothing
252+ , value: Nothing
253+ , gas: Nothing
254+ , gasPrice: Nothing
255+ , data: Nothing
256+ , nonce: Nothing
272257 }
273258-- * Lens Boilerplate
274259_from :: forall u . Lens' (TransactionOptions u ) (Maybe Address )
275- _from = lens (\(TransactionOptions txOpt) -> unNullOrUndefined $ txOpt.from)
276- (\(TransactionOptions txOpts) addr -> TransactionOptions $ txOpts {from = NullOrUndefined addr})
260+ _from = lens (\(TransactionOptions txOpt) -> txOpt.from)
261+ (\(TransactionOptions txOpts) addr -> TransactionOptions $ txOpts {from = addr})
277262
278263_to :: forall u . Lens' (TransactionOptions u ) (Maybe Address )
279- _to = lens (\(TransactionOptions txOpt) -> unNullOrUndefined $ txOpt.to)
280- (\(TransactionOptions txOpts) addr -> TransactionOptions $ txOpts {to = NullOrUndefined addr})
264+ _to = lens (\(TransactionOptions txOpt) -> txOpt.to)
265+ (\(TransactionOptions txOpts) addr -> TransactionOptions $ txOpts {to = addr})
281266
282267_data :: forall u . Lens' (TransactionOptions u ) (Maybe HexString )
283- _data = lens (\(TransactionOptions txOpt) -> unNullOrUndefined $ txOpt.data)
284- (\(TransactionOptions txOpts) dat -> TransactionOptions $ txOpts {data = NullOrUndefined dat})
268+ _data = lens (\(TransactionOptions txOpt) -> txOpt.data)
269+ (\(TransactionOptions txOpts) dat -> TransactionOptions $ txOpts {data = dat})
285270
286271_value :: forall u . EtherUnit (Value u ) => Lens (TransactionOptions u ) (TransactionOptions Wei ) (Maybe (Value u )) (Maybe (Value Wei ))
287- _value = lens (\(TransactionOptions txOpt) -> unNullOrUndefined $ txOpt.value)
288- (\(TransactionOptions txOpts) val -> TransactionOptions $ txOpts {value = NullOrUndefined $ map convert val})
272+ _value = lens (\(TransactionOptions txOpt) -> txOpt.value)
273+ (\(TransactionOptions txOpts) val -> TransactionOptions $ txOpts {value = map convert val})
289274
290275_gas :: forall u . Lens' (TransactionOptions u ) (Maybe BigNumber )
291- _gas = lens (\(TransactionOptions txOpt) -> unNullOrUndefined $ txOpt.gas)
292- (\(TransactionOptions txOpts) g -> TransactionOptions $ txOpts {gas = NullOrUndefined g})
276+ _gas = lens (\(TransactionOptions txOpt) -> txOpt.gas)
277+ (\(TransactionOptions txOpts) g -> TransactionOptions $ txOpts {gas = g})
293278
294279_gasPrice :: forall u . Lens' (TransactionOptions u ) (Maybe BigNumber )
295- _gasPrice = lens (\(TransactionOptions txOpt) -> unNullOrUndefined $ txOpt.gasPrice)
296- (\(TransactionOptions txOpts) gp -> TransactionOptions $ txOpts {gasPrice = NullOrUndefined gp})
280+ _gasPrice = lens (\(TransactionOptions txOpt) -> txOpt.gasPrice)
281+ (\(TransactionOptions txOpts) gp -> TransactionOptions $ txOpts {gasPrice = gp})
297282
298283_nonce :: forall u . Lens' (TransactionOptions u ) (Maybe BigNumber )
299- _nonce = lens (\(TransactionOptions txOpt) -> unNullOrUndefined $ txOpt.nonce)
300- (\(TransactionOptions txOpts) n -> TransactionOptions $ txOpts {nonce = NullOrUndefined n})
284+ _nonce = lens (\(TransactionOptions txOpt) -> txOpt.nonce)
285+ (\(TransactionOptions txOpts) n -> TransactionOptions $ txOpts {nonce = n})
301286
302287-- ------------------------------------------------------------------------------
303288-- * Node Synchronisation
@@ -395,8 +380,8 @@ forkWeb3' web3Action = do
395380
396381-- | Low-level event filter data structure
397382newtype Filter a = Filter
398- { address :: NullOrUndefined Address
399- , topics :: NullOrUndefined (Array (NullOrUndefined HexString ))
383+ { address :: Maybe Address
384+ , topics :: Maybe (Array (Maybe HexString ))
400385 , fromBlock :: ChainCursor
401386 , toBlock :: ChainCursor
402387 }
@@ -414,19 +399,19 @@ instance encodeFilter :: Encode (Filter a) where
414399 encode x = genericEncode (defaultOptions { unwrapSingleConstructors = true }) x
415400
416401defaultFilter :: forall a . Filter a
417- defaultFilter = Filter { address: NullOrUndefined Nothing
418- , topics: NullOrUndefined Nothing
402+ defaultFilter = Filter { address: Nothing
403+ , topics: Nothing
419404 , fromBlock: Latest
420405 , toBlock: Latest
421406 }
422407
423408_address :: forall a . Lens' (Filter a ) (Maybe Address )
424- _address = lens (\(Filter f) -> unNullOrUndefined f.address)
425- (\(Filter f) addr -> Filter $ f {address = NullOrUndefined addr})
409+ _address = lens (\(Filter f) -> f.address)
410+ (\(Filter f) addr -> Filter $ f {address = addr})
426411
427412_topics :: forall a . Lens' (Filter a ) (Maybe (Array (Maybe HexString )))
428- _topics = lens (\(Filter f) -> map unNullOrUndefined <$> unNullOrUndefined f.topics)
429- (\(Filter f) ts -> Filter $ f {topics = NullOrUndefined (map NullOrUndefined <$> ts) })
413+ _topics = lens (\(Filter f) -> f.topics)
414+ (\(Filter f) ts -> Filter $ f {topics = ts })
430415
431416_fromBlock :: forall a . Lens' (Filter a ) ChainCursor
432417_fromBlock = lens (\(Filter f) -> f.fromBlock)
@@ -437,7 +422,7 @@ _toBlock = lens (\(Filter f) -> f.toBlock)
437422 (\(Filter f) b -> Filter $ f {toBlock = b})
438423
439424-- | Used by the ethereum client to identify the filter you are querying
440- newtype FilterId = FilterId HexString
425+ newtype FilterId = FilterId BigNumber
441426
442427derive instance genericFilterId :: Generic FilterId _
443428
@@ -480,9 +465,10 @@ instance eqEventAction :: Eq EventAction where
480465-- | Changes pulled by low-level call 'eth_getFilterChanges', 'eth_getLogs',
481466-- | and 'eth_getFilterLogs'
482467newtype Change = Change
483- { logIndex :: HexString
484- , transactionIndex :: HexString
468+ { logIndex :: BigNumber
469+ , transactionIndex :: BigNumber
485470 , transactionHash :: HexString
471+ , removed :: Boolean
486472 , blockHash :: HexString
487473 , blockNumber :: BlockNumber
488474 , address :: Address
0 commit comments