Skip to content

Commit

Permalink
refine: improve test and report error better (#1)
Browse files Browse the repository at this point in the history
  • Loading branch information
xieyuschen authored Aug 8, 2024
1 parent ae57c4f commit fcf4705
Show file tree
Hide file tree
Showing 7 changed files with 222 additions and 25 deletions.
53 changes: 33 additions & 20 deletions src/Lib/AST/Definition.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,9 @@ pModifierDefinition :: Parser ModifierDefinition
pModifierDefinition = do
ident <-
pOneKeyword "modifier"
*> pMany1Spaces
*> ( pMany1Spaces
<|> fail "space is required after keyword 'modifier'"
)
*> pIdentifier
args <- pManySpaces >> optionMaybe pFnDeclArgsInParentheses

Expand Down Expand Up @@ -71,7 +73,9 @@ pEventDefinition :: Parser EventDefinition
pEventDefinition = do
ident <-
pOneKeyword "event"
*> pMany1Spaces
*> ( pMany1Spaces
<|> fail "space is required after keyword 'event'"
)
*> pIdentifier
params <-
between
Expand All @@ -81,7 +85,7 @@ pEventDefinition = do
)

isAnonymous <- pOneKeyword "anonymous" $> True <|> return False
_ <- pOneKeyword semicolon
_ <- pManySpaces *> pOneKeyword semicolon
return
EventDefinition
{ eventParameters = params,
Expand All @@ -93,7 +97,9 @@ pErrorDefinition :: Parser ErrorDefinition
pErrorDefinition = do
ident <-
pOneKeyword "error"
*> pMany1Spaces
*> ( pMany1Spaces
<|> fail "space is required after keyword 'error'"
)
*> pIdentifier
<* pManySpaces
args <-
Expand All @@ -102,7 +108,7 @@ pErrorDefinition = do
(pOneKeyword rightParenthesis)
( sepBy (pManySpaces *> pErrorParameter <* pManySpaces) (char ',')
)

_ <- pManySpaces *> pOneKeyword semicolon
return $
ErrorDefinition
{ errParameters = args,
Expand All @@ -121,8 +127,8 @@ pErrorParameter = do

pInheritanceSpecifier :: Parser InheritanceSpecifier
pInheritanceSpecifier = do
path <- pIdentifierPath <* pManySpaces
args <- pFnCallArgs
path <- pIdentifierPath
args <- optionMaybe pFnCallArgs
return $
InheritanceSpecifier
{ inheritanceCallArgs = args,
Expand Down Expand Up @@ -201,26 +207,33 @@ pInterfaceDefinition = do
name <-
pManySpaces
*> pOneKeyword "interface"
*> pMany1Spaces
*> ( pMany1Spaces
<|> fail "space is required after keyword 'interface'"
)
*> pIdentifier
<* pMany1Spaces
<* pOneKeyword "is"
<* pMany1Spaces
<* pManySpaces

iSpecicier <-
sepBy
(pManySpaces *> pInheritanceSpecifier <* pManySpaces)
(char ',')
optionMaybe $
try
( pOneKeyword "is"
*> pMany1Spaces
*> sepBy
(pManySpaces *> pInheritanceSpecifier <* pManySpaces)
(char ',')
)

body <-
pManySpaces
*> between
(pOneKeyword leftParenthesis)
(pOneKeyword rightParenthesis)
(pOneKeyword leftCurlyBrace)
(pOneKeyword rightCurlyBrace)
(pManySpaces *> pContractBody <* pManySpaces)

return $
InterfaceDefinition
{ interfaceName = name,
interfaceInheritanceSpecifiers = iSpecicier,
interfaceInheritanceSpecifiers = fromMaybe [] iSpecicier,
interfaceBody = body
}

Expand All @@ -229,14 +242,14 @@ pLibraryDefinition = do
name <-
pManySpaces
*> pOneKeyword "library"
*> pMany1Spaces
*> (pMany1Spaces <|> fail "space is required after keyword 'library'")
*> pIdentifier
<* pManySpaces
body <-
pManySpaces
*> between
(pOneKeyword leftParenthesis)
(pOneKeyword rightParenthesis)
(pOneKeyword leftCurlyBrace)
(pOneKeyword rightCurlyBrace)
(pManySpaces *> pContractBody <* pManySpaces)
return $
LibraryDefinition
Expand Down
3 changes: 1 addition & 2 deletions src/Lib/AST/Function.hs
Original file line number Diff line number Diff line change
Expand Up @@ -83,7 +83,6 @@ pFunctionDefinition = do
(pOneKeyword rightCurlyBrace)
(many $ pState <* pManySpaces)

-- why 'many anyChar' doesn't work?
return
( FunctionDefinition
{ fnDefName = name,
Expand Down Expand Up @@ -114,7 +113,7 @@ pReturnsClause =
do
pManySpaces
*> pOneKeyword keywordReturns
*> pMany1Spaces
*> pManySpaces
*> pFunctionReturnTypeWithQuote
<* pManySpaces

Expand Down
2 changes: 1 addition & 1 deletion src/Lib/AST/Model.hs
Original file line number Diff line number Diff line change
Expand Up @@ -551,7 +551,7 @@ data LibraryDefinition = LibraryDefinition

data InheritanceSpecifier = InheritanceSpecifier
{ inheritancePath :: IdentifierPath,
inheritanceCallArgs :: FnCallArgs
inheritanceCallArgs :: Maybe FnCallArgs
}
deriving (Show, Eq)

Expand Down
2 changes: 2 additions & 0 deletions src/Lib/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -81,6 +81,8 @@ pBool =
isUnderscore :: Char -> Bool
isUnderscore = (== '_')

-- todo: currently the pIdentifier will stop once the character could not be recognized as a vliad char
-- for example variable&abc will stop parsing at '&', think about whether we can improve it or not
pIdentifier :: Parser Text
pIdentifier = do
first <- letter <|> char '_'
Expand Down
169 changes: 168 additions & 1 deletion tests/Lib/AST/DefinitionSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
module Lib.AST.DefinitionSpec (spec) where

import Control.Monad (forM_)
import Lib.AST.Definition (pContractBody, pEventDefinition, pModifierDefinition)
import Lib.AST.Definition (pContractBody, pErrorDefinition, pEventDefinition, pInterfaceDefinition, pLibraryDefinition, pModifierDefinition)
import Lib.AST.Model
import Lib.TestCommon (exactlyParserVerifier, leftRightJustifier, newParserVerifier, resultIsRight)
import Test.Hspec (Spec)
Expand All @@ -13,6 +13,9 @@ spec = do
parseModifierDefinitionSpec
parseEventDefinitionSpec
parseContractBodySpec
parseErrorDefintionSpec
parseInterfaceDefintionSpec
parseLibraryDefinitionSpec

parseModifierDefinitionSpec :: Spec
parseModifierDefinitionSpec = do
Expand Down Expand Up @@ -116,6 +119,10 @@ parseModifierDefinitionSpec = do
}
),
""
),
( "modifierExampleM(uint256 memory hello, string str);",
Left ["\"E\"", "space", "space is required after keyword 'modifier'"],
"modifierExampleM(uint256 memory hello, string str);"
)
]

Expand Down Expand Up @@ -222,6 +229,10 @@ parseEventDefinitionSpec = do
}
),
""
),
( "eventEA(string 0 str, string) anonymous;",
Left ["\"E\"", "space", "space is required after keyword 'event'"],
"eventEA(string 0 str, string) anonymous;"
)
]

Expand Down Expand Up @@ -262,6 +273,7 @@ parseContractBodySpec = do
\using a.b.c for Bitmap;\n\
\function receive(string name) public pure { count += 1; } \n\
\function fallback(string name) public pure { count += 1; } \n\
\function getResult() external view returns(uint);\n\
\ ",
resultIsRight,
""
Expand All @@ -270,3 +282,158 @@ parseContractBodySpec = do

-- we won't put the
forM_ testCases $ newParserVerifier leftRightJustifier "contract body" pContractBody

parseErrorDefintionSpec :: Spec
parseErrorDefintionSpec = do
let testCases =
[ ( "error Unauthorized();",
Right (ErrorDefinition {errName = "Unauthorized", errParameters = []}),
""
),
( "error InsufficientBalance(uint256 available, uint256 required);",
Right (ErrorDefinition {errName = "InsufficientBalance", errParameters = [ErrorParameter {errParamType = STypeUint 256, errParamName = Just "available"}, ErrorParameter {errParamType = STypeUint 256, errParamName = Just "required"}]}),
""
),
( "errorUnauthorized();",
Left ["\"U\"", "space", "space is required after keyword 'error'"],
"errorUnauthorized();"
)
]

forM_ testCases $ exactlyParserVerifier "modifier definition" pErrorDefinition

parseInterfaceDefintionSpec :: Spec
parseInterfaceDefintionSpec = do
let testCases =
[ ( "interface Calculator { \n \
\ function getResult() external view returns(uint); \
\ }",
Right
( InterfaceDefinition
{ interfaceName = "Calculator",
interfaceInheritanceSpecifiers = [],
interfaceBody =
ContractBody
{ ctBodyConstructor = Nothing,
ctBodyFunctions = [FunctionDefinition {fnDefName = FnNormal "getResult", fnState = FnStateView, fnVisibility = FnExternal, fnModifierInvocations = [], fnFnOverrideSpecifier = Nothing, fnIsVirtual = False, fargs = [], fnReturnTyp = Just (STypeUint 256), fnBody = Nothing}],
ctBodyModifiers = [],
ctBodyFallbackFunctions = [],
ctBodyReceiveFunctions = [],
ctBodyStructDefinitions = [],
ctBodyEnumDefinitions = [],
ctBodyUserDefinedValueTypeDefinition = [],
ctBodyStateVariables = [],
ctBodyEventDefinitions = [],
ctBodyErrorDefinitions = [],
ctBodyUsingDirectives = [],
ctBodyAllFields = [CBFSSumFunction (FunctionDefinition {fnDefName = FnNormal "getResult", fnState = FnStateView, fnVisibility = FnExternal, fnModifierInvocations = [], fnFnOverrideSpecifier = Nothing, fnIsVirtual = False, fargs = [], fnReturnTyp = Just (STypeUint 256), fnBody = Nothing})]
}
}
),
""
),
( "interface Calculator is MyInterface { \n \
\ function getResult() external view returns(uint); \
\ }",
Right
( InterfaceDefinition
{ interfaceName = "Calculator",
interfaceInheritanceSpecifiers = [InheritanceSpecifier {inheritancePath = ["MyInterface"], inheritanceCallArgs = Nothing}],
interfaceBody =
ContractBody
{ ctBodyConstructor = Nothing,
ctBodyFunctions = [FunctionDefinition {fnDefName = FnNormal "getResult", fnState = FnStateView, fnVisibility = FnExternal, fnModifierInvocations = [], fnFnOverrideSpecifier = Nothing, fnIsVirtual = False, fargs = [], fnReturnTyp = Just (STypeUint 256), fnBody = Nothing}],
ctBodyModifiers = [],
ctBodyFallbackFunctions = [],
ctBodyReceiveFunctions = [],
ctBodyStructDefinitions = [],
ctBodyEnumDefinitions = [],
ctBodyUserDefinedValueTypeDefinition = [],
ctBodyStateVariables = [],
ctBodyEventDefinitions = [],
ctBodyErrorDefinitions = [],
ctBodyUsingDirectives = [],
ctBodyAllFields = [CBFSSumFunction (FunctionDefinition {fnDefName = FnNormal "getResult", fnState = FnStateView, fnVisibility = FnExternal, fnModifierInvocations = [], fnFnOverrideSpecifier = Nothing, fnIsVirtual = False, fargs = [], fnReturnTyp = Just (STypeUint 256), fnBody = Nothing})]
}
}
),
""
),
( "interface Calculator is MyInterface(123, \"hello\"), A.MyInterface() { \n \
\ function getResult() external view returns(uint); \
\ }",
Right
( InterfaceDefinition
{ interfaceName = "Calculator",
interfaceInheritanceSpecifiers =
[ InheritanceSpecifier {inheritancePath = ["MyInterface"], inheritanceCallArgs = Just (FnCallArgsList [SExprL (LNum 123), SExprL (LString "hello")])},
InheritanceSpecifier
{ inheritancePath = ["A", "MyInterface"],
inheritanceCallArgs = Just (FnCallArgsList [])
}
],
interfaceBody =
ContractBody
{ ctBodyConstructor = Nothing,
ctBodyFunctions = [FunctionDefinition {fnDefName = FnNormal "getResult", fnState = FnStateView, fnVisibility = FnExternal, fnModifierInvocations = [], fnFnOverrideSpecifier = Nothing, fnIsVirtual = False, fargs = [], fnReturnTyp = Just (STypeUint 256), fnBody = Nothing}],
ctBodyModifiers = [],
ctBodyFallbackFunctions = [],
ctBodyReceiveFunctions = [],
ctBodyStructDefinitions = [],
ctBodyEnumDefinitions = [],
ctBodyUserDefinedValueTypeDefinition = [],
ctBodyStateVariables = [],
ctBodyEventDefinitions = [],
ctBodyErrorDefinitions = [],
ctBodyUsingDirectives = [],
ctBodyAllFields = [CBFSSumFunction (FunctionDefinition {fnDefName = FnNormal "getResult", fnState = FnStateView, fnVisibility = FnExternal, fnModifierInvocations = [], fnFnOverrideSpecifier = Nothing, fnIsVirtual = False, fargs = [], fnReturnTyp = Just (STypeUint 256), fnBody = Nothing})]
}
}
),
""
),
( "interfaceABC();",
Left ["\"A\"", "space", "space is required after keyword 'interface'"],
"interfaceABC();"
)
]

forM_ testCases $ exactlyParserVerifier "interface definition" pInterfaceDefinition

parseLibraryDefinitionSpec :: Spec
parseLibraryDefinitionSpec = do
let testCases =
[ ( "library Lib{}",
Right (LibraryDefinition {libraryName = "Lib", libraryBody = ContractBody {ctBodyConstructor = Nothing, ctBodyFunctions = [], ctBodyModifiers = [], ctBodyFallbackFunctions = [], ctBodyReceiveFunctions = [], ctBodyStructDefinitions = [], ctBodyEnumDefinitions = [], ctBodyUserDefinedValueTypeDefinition = [], ctBodyStateVariables = [], ctBodyEventDefinitions = [], ctBodyErrorDefinitions = [], ctBodyUsingDirectives = [], ctBodyAllFields = []}}),
""
),
( "library Lib{function getResult() external view returns(uint);}",
Right
( LibraryDefinition
{ libraryName = "Lib",
libraryBody =
ContractBody
{ ctBodyConstructor = Nothing,
ctBodyFunctions = [FunctionDefinition {fnDefName = FnNormal "getResult", fnState = FnStateView, fnVisibility = FnExternal, fnModifierInvocations = [], fnFnOverrideSpecifier = Nothing, fnIsVirtual = False, fargs = [], fnReturnTyp = Just (STypeUint 256), fnBody = Nothing}],
ctBodyModifiers = [],
ctBodyFallbackFunctions = [],
ctBodyReceiveFunctions = [],
ctBodyStructDefinitions = [],
ctBodyEnumDefinitions = [],
ctBodyUserDefinedValueTypeDefinition = [],
ctBodyStateVariables = [],
ctBodyEventDefinitions = [],
ctBodyErrorDefinitions = [],
ctBodyUsingDirectives = [],
ctBodyAllFields = [CBFSSumFunction (FunctionDefinition {fnDefName = FnNormal "getResult", fnState = FnStateView, fnVisibility = FnExternal, fnModifierInvocations = [], fnFnOverrideSpecifier = Nothing, fnIsVirtual = False, fargs = [], fnReturnTyp = Just (STypeUint 256), fnBody = Nothing})]
}
}
),
""
),
( "libraryLib{}",
Left ["\"L\"", "space", "space is required after keyword 'library'"],
"libraryLib{}"
)
]
forM_ testCases $ exactlyParserVerifier "library definition" pLibraryDefinition
15 changes: 15 additions & 0 deletions tests/Lib/AST/FunctionSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -368,6 +368,21 @@ parseFunctionSignatureSpec = do
fnBody = Nothing
},
""
),
( "function getResult() external view returns(uint);",
Right
FunctionDefinition
{ fnDefName = FnNormal "getResult",
fnState = FnStateView,
fnVisibility = FnExternal,
fnModifierInvocations = [],
fnFnOverrideSpecifier = Nothing,
fnIsVirtual = False,
fargs = [],
fnReturnTyp = Just (STypeUint 256),
fnBody = Nothing
},
""
)
]
forM_ testCases $ exactlyParserVerifier "whole function" pFunctionDefinition
Expand Down
3 changes: 2 additions & 1 deletion tests/Lib/TestCommon.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,8 +39,9 @@ leftRightJustifier expectedResult result = do
if isRight result
then return ()
else expectationFailure $ "Expected Right but got Left: " ++ show (fromLeft (error "") result)
Left _ -> do
Left err -> do
errorPos (fromLeft (error "") result) `shouldBe` initialPos ""
err `shouldBe` []

exactlyJustifier :: (Eq a, Show a) => Justifier a a
exactlyJustifier expectedResult result = do
Expand Down

0 comments on commit fcf4705

Please sign in to comment.