Skip to content

Commit

Permalink
Making progress
Browse files Browse the repository at this point in the history
  • Loading branch information
msooseth committed Oct 31, 2024
1 parent 2cb92a9 commit 92a7048
Showing 1 changed file with 24 additions and 30 deletions.
54 changes: 24 additions & 30 deletions src/EVM/ABI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -328,19 +328,22 @@ abiTailSize x =
_ -> internalError "impossible"

abiHeadSize :: AbiValue -> Int
abiHeadSize x =
case abiKind (abiValueType x) of
abiHeadSize x = abiSizeType (abiValueType x)

abiSizeType :: AbiType -> Int
abiSizeType x =
case abiKind x of
Dynamic -> 32
Static ->
case x of
AbiUInt _ _ -> 32
AbiInt _ _ -> 32
AbiBytes n _ -> roundTo32Bytes n
AbiAddress _ -> 32
AbiBool _ -> 32
AbiTuple v -> sum (abiHeadSize <$> v)
AbiArray _ _ xs -> sum (abiHeadSize <$> xs)
AbiFunction _ -> 32
AbiUIntType _ -> 32
AbiIntType _ -> 32
AbiBytesType n -> roundTo32Bytes n
AbiAddressType -> 32
AbiBoolType -> 32
AbiTupleType n -> sum (abiSizeType <$> n)
AbiArrayType n t -> n*(abiSizeType t)
AbiFunctionType -> 32
_ -> internalError "impossible"

putAbiSeq :: Vector AbiValue -> Put
Expand Down Expand Up @@ -512,38 +515,29 @@ decodeBuf tpsOrig bufOrig = go tpsOrig bufOrig 0 NoVals
go :: [AbiType] -> Expr Buf -> Int -> AbiVals -> AbiVals
go [] _ _ ret = ret
go [AbiStringType] buf off (SAbi acc) = MixAbi (acc, decodeStringArg off buf)
go [_] _ _ (SAbi _) = internalError "Currently we can only decode string as last dynamic type"
go (x:_) _ _ _ | isDynamic x = internalError "Dynamic type must be last in the list"
go (_:tps) buf off (SAbi acc) =
let
v = readWord (Lit (unsafeInto off)) buf
in if not (isLitWord v) then go tps buf (off+32) (SAbi (acc++[v]))
else internalError "can't mix Symbolic and Concrete"
go (t:tps) buf off (CAbi acc) =
let v = readWord (Lit (unsafeInto off)) buf
go (t:ts) buf off (SAbi acc) =
let len = abiSizeType t
v = readBytes len (Lit (unsafeInto off)) buf
in go ts buf (off+len) (SAbi (acc++[v]))
go (t:ts) buf off (CAbi acc) | (not . isDynamic) t =
let len = abiSizeType t
v = readBytes len (Lit (unsafeInto off)) buf
asBS = mconcat $ fmap word256Bytes (mapMaybe maybeLitWord [v])
in case runGetOrFail (getAbiSeq 1 [t]) (BSLazy.fromStrict asBS) of
Right ("", _, args) -> go tps buf (off+32) $ CAbi (acc++(toList args))
Right ("", _, args) -> go ts buf (off+len) $ CAbi (acc++(toList args))
_ -> NoVals
go _ _ _ _ = internalError "decodeBuf: expected concrete buffer"
-- decodeBuf tps buf =
-- let
-- vs = decodeStaticArgs 0 (length tps) buf
-- asBS = mconcat $ fmap word256Bytes (mapMaybe maybeLitWord vs)
-- in if not (all isLitWord vs)
-- then SAbi vs
-- else case runGetOrFail (getAbiSeq (length tps) tps) (BSLazy.fromStrict asBS) of
-- Right ("", _, args) -> CAbi (toList args)
-- _ -> NoVals
-- decodeBuf _ _ = internalError "decodeBuf: expected concrete buffer"

decodeStaticArgs :: Int -> Int -> Expr Buf -> [Expr EWord]
decodeStaticArgs offset numArgs b =
[readWord (Lit . unsafeInto $ i) b | i <- [offset,(offset+32) .. (offset + (numArgs-1)*32)]]

decodeStringArg :: Int -> Expr Buf -> AbiValue
decodeStringArg offs (ConcreteBuf b) =
let len = forceLit $ readBytes 4 (Lit . unsafeInto $ offs) (ConcreteBuf b)
str = [readByte (Lit . unsafeInto $ (offs + 4 + (unsafeInto i))) (ConcreteBuf b) | i <- [0..len]]
let len = forceLit $ readBytes 32 (Lit . unsafeInto $ offs) (ConcreteBuf b)
str = [readByte (Lit . unsafeInto $ (offs + 32 + (unsafeInto i))) (ConcreteBuf b) | i <- [0..len]]
bs = (map toLitByte str)
in AbiString $ BS.pack bs
where
Expand Down

0 comments on commit 92a7048

Please sign in to comment.