Skip to content

Commit

Permalink
Merge 770c568 into fbfff3c
Browse files Browse the repository at this point in the history
  • Loading branch information
MDoerner committed Sep 30, 2021
2 parents fbfff3c + 770c568 commit f81ba65
Show file tree
Hide file tree
Showing 6 changed files with 129 additions and 31 deletions.
36 changes: 36 additions & 0 deletions Rubberduck.Parsing/Binding/Bindings/BindingContextBase.cs
@@ -0,0 +1,36 @@
using Antlr4.Runtime;
using Antlr4.Runtime.Tree;
using NLog;
using Rubberduck.Parsing.Symbols;

namespace Rubberduck.Parsing.Binding
{
public abstract class BindingContextBase : IBindingContext
{
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();



protected IExpressionBinding HandleUnexpectedExpressionType(ParserRuleContext expression)
{
Logger.Warn($"Unexpected context type {expression.GetType()}");
return new FailedExpressionBinding(expression);
}

public abstract IBoundExpression Resolve(Declaration module,
Declaration parent,
ParserRuleContext expression,
IBoundExpression withBlockVariable,
StatementResolutionContext statementContext,
bool requiresLetCoercion = false,
bool isLetAssignment = false);

public abstract IExpressionBinding BuildTree(Declaration module,
Declaration parent,
ParserRuleContext expression,
IBoundExpression withBlockVariable,
StatementResolutionContext statementContext,
bool requiresLetCoercion = false,
bool isLetAssignment = false);
}
}
19 changes: 19 additions & 0 deletions Rubberduck.Parsing/Binding/Bindings/FailedExpressionBinding.cs
@@ -0,0 +1,19 @@
using Antlr4.Runtime;

namespace Rubberduck.Parsing.Binding
{
public sealed class FailedExpressionBinding : IExpressionBinding
{
private readonly ParserRuleContext _context;

public FailedExpressionBinding(ParserRuleContext context)
{
_context = context;
}

public IBoundExpression Resolve()
{
return new ResolutionFailedExpression(_context);
}
}
}
30 changes: 17 additions & 13 deletions Rubberduck.Parsing/Binding/DefaultBindingContext.cs
Expand Up @@ -3,12 +3,11 @@
using Rubberduck.Parsing.Symbols;
using System;
using System.Collections.Generic;
using Antlr4.Runtime.Tree;
using Rubberduck.Parsing.VBA.DeclarationCaching;

namespace Rubberduck.Parsing.Binding
{
public sealed class DefaultBindingContext : IBindingContext
public sealed class DefaultBindingContext : BindingContextBase
{
private readonly DeclarationFinder _declarationFinder;
private readonly IBindingContext _typeBindingContext;
Expand All @@ -24,19 +23,24 @@ public sealed class DefaultBindingContext : IBindingContext
_procedurePointerBindingContext = procedurePointerBindingContext;
}

public IBoundExpression Resolve(Declaration module, Declaration parent, IParseTree expression, IBoundExpression withBlockVariable, StatementResolutionContext statementContext, bool requiresLetCoercion, bool isLetAssignment)
public override IBoundExpression Resolve(Declaration module,
Declaration parent,
ParserRuleContext expression,
IBoundExpression withBlockVariable,
StatementResolutionContext statementContext,
bool requiresLetCoercion = false,
bool isLetAssignment = false)
{
var bindingTree = BuildTree(module, parent, expression, withBlockVariable, statementContext, requiresLetCoercion, isLetAssignment);
return bindingTree?.Resolve();
}

public IExpressionBinding BuildTree(
Declaration module,
Declaration parent,
IParseTree expression,
IBoundExpression withBlockVariable,
public override IExpressionBinding BuildTree(Declaration module,
Declaration parent,
ParserRuleContext expression,
IBoundExpression withBlockVariable,
StatementResolutionContext statementContext,
bool requiresLetCoercion = false,
bool requiresLetCoercion = false,
bool isLetAssignment = false)
{
return Visit(
Expand All @@ -49,7 +53,7 @@ public IBoundExpression Resolve(Declaration module, Declaration parent, IParseTr
isLetAssignment);
}

public IExpressionBinding Visit(Declaration module, Declaration parent, IParseTree expression, IBoundExpression withBlockVariable, StatementResolutionContext statementContext, bool requiresLetCoercion = false, bool isLetAssignment = false)
public IExpressionBinding Visit(Declaration module, Declaration parent, ParserRuleContext expression, IBoundExpression withBlockVariable, StatementResolutionContext statementContext, bool requiresLetCoercion = false, bool isLetAssignment = false)
{
if (requiresLetCoercion && expression is ParserRuleContext context)
{
Expand All @@ -76,7 +80,7 @@ public IExpressionBinding Visit(Declaration module, Declaration parent, IParseTr
case VBAParser.UnqualifiedObjectPrintStmtContext unqualifiedObjectPrintStmtContext:
return Visit(module, parent, unqualifiedObjectPrintStmtContext, withBlockVariable);
default:
throw new NotSupportedException($"Unexpected context type {expression.GetType()}");
return HandleUnexpectedExpressionType(expression);
}
}

Expand Down Expand Up @@ -160,7 +164,7 @@ private IExpressionBinding Visit(Declaration module, Declaration parent, VBAPars
return Visit(builtInTypeExprContext);
//We do not handle the VBAParser.TypeofexprContext because that should only ever appear as a child of an IS relational operator expression and is specifically handled there.
default:
throw new NotSupportedException($"Unexpected expression type {expression.GetType()}");
return HandleUnexpectedExpressionType(expression);
}
}

Expand All @@ -187,7 +191,7 @@ private IExpressionBinding Visit(Declaration module, Declaration parent, VBAPars
case VBAParser.ObjectPrintExprContext objectPrintExprContext:
return Visit(module, parent, objectPrintExprContext, withBlockVariable);
default:
throw new NotSupportedException($"Unexpected lExpression type {expression.GetType()}");
return HandleUnexpectedExpressionType(expression);
}
}

Expand Down
20 changes: 17 additions & 3 deletions Rubberduck.Parsing/Binding/IBindingContext.cs
@@ -1,11 +1,25 @@
using Antlr4.Runtime.Tree;
using Antlr4.Runtime;
using Rubberduck.Parsing.Symbols;

namespace Rubberduck.Parsing.Binding
{
public interface IBindingContext
{
IBoundExpression Resolve(Declaration module, Declaration parent, IParseTree expression, IBoundExpression withBlockVariable, StatementResolutionContext statementContext, bool requiresLetCoercion = false, bool isLetAssignment = false);
IExpressionBinding BuildTree(Declaration module, Declaration parent, IParseTree expression, IBoundExpression withBlockVariable, StatementResolutionContext statementContext, bool requiresLetCoercion = false, bool isLetAssignment = false);
IBoundExpression Resolve(
Declaration module,
Declaration parent,
ParserRuleContext expression,
IBoundExpression withBlockVariable,
StatementResolutionContext statementContext,
bool requiresLetCoercion = false,
bool isLetAssignment = false);
IExpressionBinding BuildTree(
Declaration module,
Declaration parent,
ParserRuleContext expression,
IBoundExpression withBlockVariable,
StatementResolutionContext statementContext,
bool requiresLetCoercion = false,
bool isLetAssignment = false);
}
}
29 changes: 21 additions & 8 deletions Rubberduck.Parsing/Binding/ProcedurePointerBindingContext.cs
@@ -1,12 +1,11 @@
using System;
using Antlr4.Runtime.Tree;
using Antlr4.Runtime;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA.DeclarationCaching;

namespace Rubberduck.Parsing.Binding
{
public sealed class ProcedurePointerBindingContext : IBindingContext
public sealed class ProcedurePointerBindingContext : BindingContextBase
{
private readonly DeclarationFinder _declarationFinder;

Expand All @@ -15,7 +14,14 @@ public ProcedurePointerBindingContext(DeclarationFinder declarationFinder)
_declarationFinder = declarationFinder;
}

public IBoundExpression Resolve(Declaration module, Declaration parent, IParseTree expression, IBoundExpression withBlockVariable, StatementResolutionContext statementContext, bool requiresLetCoercion = false, bool isLetAssignment = false)
public override IBoundExpression Resolve(
Declaration module,
Declaration parent,
ParserRuleContext expression,
IBoundExpression withBlockVariable,
StatementResolutionContext statementContext,
bool requiresLetCoercion = false,
bool isLetAssignment = false)
{
IExpressionBinding bindingTree = BuildTree(module, parent, expression, withBlockVariable, statementContext);
if (bindingTree != null)
Expand All @@ -25,7 +31,14 @@ public IBoundExpression Resolve(Declaration module, Declaration parent, IParseTr
return null;
}

public IExpressionBinding BuildTree(Declaration module, Declaration parent, IParseTree expression, IBoundExpression withBlockVariable, StatementResolutionContext statementContext, bool requiresLetCoercion = false, bool isLetAssignment = false)
public override IExpressionBinding BuildTree(
Declaration module,
Declaration parent,
ParserRuleContext expression,
IBoundExpression withBlockVariable,
StatementResolutionContext statementContext,
bool requiresLetCoercion = false,
bool isLetAssignment = false)
{
switch (expression)
{
Expand All @@ -36,7 +49,7 @@ public IExpressionBinding BuildTree(Declaration module, Declaration parent, IPar
case VBAParser.AddressOfExpressionContext addressOfExpressionContext:
return Visit(module, parent, addressOfExpressionContext);
default:
throw new NotSupportedException($"Unexpected context type {expression.GetType()}");
return HandleUnexpectedExpressionType(expression);
}
}

Expand All @@ -52,7 +65,7 @@ private IExpressionBinding Visit(Declaration module, Declaration parent, VBAPars
case VBAParser.LExprContext lExprContext:
return Visit(module, parent, lExprContext.lExpression());
default:
throw new NotSupportedException($"Unexpected expression type {expression.GetType()}");
return HandleUnexpectedExpressionType(expression);
}
}

Expand All @@ -65,7 +78,7 @@ private IExpressionBinding Visit(Declaration module, Declaration parent, VBAPars
case VBAParser.MemberAccessExprContext memberAccessExprContext:
return Visit(module, parent, memberAccessExprContext);
default:
throw new NotSupportedException($"Unexpected lExpression type {expression.GetType()}");
return HandleUnexpectedExpressionType(expression);
}
}

Expand Down
26 changes: 19 additions & 7 deletions Rubberduck.Parsing/Binding/TypeBindingContext.cs
@@ -1,12 +1,11 @@
using System;
using Antlr4.Runtime.Tree;
using Antlr4.Runtime;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA.DeclarationCaching;

namespace Rubberduck.Parsing.Binding
{
public sealed class TypeBindingContext : IBindingContext
public sealed class TypeBindingContext : BindingContextBase
{
private readonly DeclarationFinder _declarationFinder;

Expand All @@ -15,13 +14,26 @@ public TypeBindingContext(DeclarationFinder declarationFinder)
_declarationFinder = declarationFinder;
}

public IBoundExpression Resolve(Declaration module, Declaration parent, IParseTree expression, IBoundExpression withBlockVariable, StatementResolutionContext statementContext, bool requiresLetCoercion = false, bool isLetAssignment = false)
public override IBoundExpression Resolve(
Declaration module,
Declaration parent, ParserRuleContext expression,
IBoundExpression withBlockVariable,
StatementResolutionContext statementContext,
bool requiresLetCoercion = false,
bool isLetAssignment = false)
{
IExpressionBinding bindingTree = BuildTree(module, parent, expression, withBlockVariable, statementContext);
return bindingTree?.Resolve();
}

public IExpressionBinding BuildTree(Declaration module, Declaration parent, IParseTree expression, IBoundExpression withBlockVariable, StatementResolutionContext statementContext, bool requiresLetCoercion = false, bool isLetAssignment = false)
public override IExpressionBinding BuildTree(
Declaration module,
Declaration parent,
ParserRuleContext expression,
IBoundExpression withBlockVariable,
StatementResolutionContext statementContext,
bool requiresLetCoercion = false,
bool isLetAssignment = false)
{
switch (expression)
{
Expand All @@ -32,7 +44,7 @@ public IExpressionBinding BuildTree(Declaration module, Declaration parent, IPar
case VBAParser.BuiltInTypeExprContext builtInTypeExprContext:
return Visit(builtInTypeExprContext.builtInType());
default:
throw new NotSupportedException($"Unexpected context type {expression.GetType()}");
return HandleUnexpectedExpressionType(expression);
}
}

Expand All @@ -52,7 +64,7 @@ private IExpressionBinding Visit(Declaration module, Declaration parent, VBAPars
case VBAParser.IndexExprContext indexExprContext:
return Visit(module, parent, indexExprContext);
default:
throw new NotSupportedException($"Unexpected lExpression type {expression.GetType()}");
return HandleUnexpectedExpressionType(expression);
}
}

Expand Down

0 comments on commit f81ba65

Please sign in to comment.