Skip to content

Commit

Permalink
update arrayparser logic
Browse files Browse the repository at this point in the history
  • Loading branch information
martyall committed Oct 6, 2023
1 parent bc19502 commit 7672974
Showing 1 changed file with 29 additions and 58 deletions.
87 changes: 29 additions & 58 deletions src/Network/Ethereum/Web3/Solidity/Event.purs
Original file line number Diff line number Diff line change
@@ -1,17 +1,18 @@
module Network.Ethereum.Web3.Solidity.Event
( class DecodeEvent
, decodeEvent
, decodeEventDef
, class ArrayParser
, arrayParser
, genericArrayParser
, class GArrayParser
, gArrayParser
, class IndexedEvent
, isAnonymous
) where

import Prelude

import Control.Error.Util (note)
import Control.Monad.Error.Class (throwError)
import Data.Array (uncons)
import Data.Bifunctor (lmap)
import Data.Either (Either(..))
Expand All @@ -33,59 +34,54 @@ import Type.Proxy (Proxy(..))
class ArrayParser a where
arrayParser :: Array HexString -> Either Web3Error (Tuple a (Array HexString))

instance ArrayParser NoArguments where
arrayParser as = pure (Tuple NoArguments as)
instance (Generic a rep, GArrayParser rep) => ArrayParser a where
arrayParser hx = do
Tuple a rest <- gArrayParser hx
case rest of
[] -> pure $ Tuple (to a) rest
_ -> throwError $ ParserError "too many arguments to arrayParser"

instance ABIDecode a => ArrayParser (Argument a) where
arrayParser hxs = case uncons hxs of
class GArrayParser rep where
gArrayParser :: Array HexString -> Either Web3Error (Tuple rep (Array HexString))

instance GArrayParser NoArguments where
gArrayParser as = pure (Tuple NoArguments as)

else instance ABIDecode a => GArrayParser (Argument a) where
gArrayParser hxs = case uncons hxs of
Nothing -> Left $ ParserError "no arguments found for arrayParser"
Just { head, tail } -> do
res <- lmap (ParserError <<< show) <<< abiDecode $ head
pure $ Tuple (Argument res) tail

instance (ArrayParser as, ArrayParser bs) => ArrayParser (Product as bs) where
arrayParser hxs = do
else instance (ArrayParser as, ArrayParser bs) => GArrayParser (Product as bs) where
gArrayParser hxs = do
Tuple a rest <- arrayParser hxs
Tuple b rest' <- arrayParser rest
pure $ Tuple (Product a b) rest'

instance ArrayParser as => ArrayParser (Constructor name as) where
arrayParser hxs = do
else instance ArrayParser as => GArrayParser (Constructor name as) where
gArrayParser hxs = do
Tuple a rest <- arrayParser hxs
pure $ Tuple (Constructor a) rest

genericArrayParser
:: forall a rep
. Generic a rep
=> ArrayParser rep
=> Array HexString
-> Either Web3Error a
genericArrayParser hxs = do
Tuple a rest <- arrayParser hxs
case rest of
[] -> pure $ to a
_ -> Left $ ParserError "too many arguments to arrayParser"

--------------------------------------------------------------------------------
-- | Event Parsers
--------------------------------------------------------------------------------
data Event i ni = Event i ni

parseChange
:: forall a b arep
. Generic a arep
=> ArrayParser arep
:: forall a b
. ArrayParser a
=> ABIDecode b
=> Show a
=> Show b
=> Change
-> Boolean
-> Either Web3Error (Event a b)
parseChange (Change change) anonymous = do
topics <-
if anonymous then pure change.topics
else note (ParserError "no topics found") (_.tail <$> uncons change.topics)
a <- genericArrayParser topics
Tuple a _ <- arrayParser topics
b <- lmap (ParserError <<< show) $ abiDecode change.data
pure $ Event a b

Expand All @@ -96,8 +92,6 @@ combineChange
=> Row.Union afields bfields cfields
=> Row.Nub cfields cfields
=> Newtype c (Record cfields)
=> Show a
=> Show b
=> Event a b
-> c
combineChange (Event a b) =
Expand All @@ -107,28 +101,6 @@ class IndexedEvent :: forall k1 k2 k3. k1 -> k2 -> k3 -> Constraint
class IndexedEvent a b c | c -> a b where
isAnonymous :: Proxy c -> Boolean

decodeEventDef
:: forall afields a arep bfields b c cfields
. Generic a arep
=> RecordFieldsIso a () afields
=> ABIEncode a
=> ArrayParser arep
=> RecordFieldsIso b () bfields
=> ABIDecode b
=> Row.Union afields bfields cfields
=> Row.Nub cfields cfields
=> Show a
=> Show b
=> Show c
=> Newtype c (Record cfields)
=> IndexedEvent a b c
=> Change
-> Either Web3Error c
decodeEventDef change = do
let anonymous = isAnonymous (Proxy :: Proxy c)
(e :: Event a b) <- parseChange change anonymous
pure $ combineChange e

class DecodeEvent :: forall k1 k2. k1 -> k2 -> Type -> Constraint
class
IndexedEvent a b c <=
Expand All @@ -137,19 +109,18 @@ class
decodeEvent :: Change -> Either Web3Error c

instance
( ArrayParser arep
( ArrayParser a
, RecordFieldsIso a () afields
, ABIEncode a
, Generic a arep
, RecordFieldsIso b () bfields
, ABIDecode b
, Row.Union afields bfields cfields
, Row.Nub cfields cfields
, Newtype c (Record cfields)
, IndexedEvent a b c
, Show a
, Show b
, Show c
) =>
DecodeEvent a b c where
decodeEvent = decodeEventDef
decodeEvent change = do
let anonymous = isAnonymous (Proxy :: Proxy c)
(e :: Event a b) <- parseChange change anonymous
pure $ combineChange e

0 comments on commit 7672974

Please sign in to comment.