Skip to content

Commit

Permalink
merge next
Browse files Browse the repository at this point in the history
  • Loading branch information
comintern committed Nov 17, 2018
2 parents 62dfc35 + 1991a0c commit 2ed334e
Show file tree
Hide file tree
Showing 327 changed files with 8,798 additions and 8,688 deletions.
2 changes: 1 addition & 1 deletion README.md
Expand Up @@ -18,7 +18,7 @@ If you like this project and would like to thank its contributors, you are welco

[![Average time to resolve an issue](http://isitmaintained.com/badge/resolution/rubberduck-vba/Rubberduck.svg)](http://isitmaintained.com/project/rubberduck-vba/Rubberduck "Average time to resolve an issue") [![Percentage of issues still open](http://isitmaintained.com/badge/open/rubberduck-vba/Rubberduck.svg)](http://isitmaintained.com/project/rubberduck-vba/Rubberduck "Percentage of issues still open")

> **[rubberduckvba.com](http://rubberduckvba.com)** [Wiki](https://github.com/retailcoder/Rubberduck/wiki) [Rubberduck News](https://rubberduckvba.wordpress.com/)
> **[rubberduckvba.com](http://rubberduckvba.com)** [Wiki](https://github.com/rubberduck-vba/Rubberduck/wiki) [Rubberduck News](https://rubberduckvba.wordpress.com/)
> devs@rubberduckvba.com
> Follow [@rubberduckvba](https://twitter.com/rubberduckvba) on Twitter
Expand Down
2 changes: 1 addition & 1 deletion Rubberduck.API/Rubberduck.API.csproj
@@ -1,5 +1,5 @@
<?xml version="1.0" encoding="utf-8"?>
<Project Sdk="Microsoft.NET.Sdk">
<Project Sdk="Sunburst.NET.Sdk.WPF/1.0.47">
<PropertyGroup>
<Product>Rubberduck.API</Product>
<Description>Rubberduck Reflection API</Description>
Expand Down
13 changes: 3 additions & 10 deletions Rubberduck.API/VBA/Parser.cs
Expand Up @@ -5,13 +5,11 @@
using System.Linq;
using System.Runtime.InteropServices;
using System.Threading;
using Rubberduck.Common;
using Rubberduck.Parsing.ComReflection;
using Rubberduck.Parsing.PreProcessing;
using Rubberduck.Parsing.Rewriter;
using Rubberduck.Parsing.Symbols.DeclarationLoaders;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.UIContext;
using Rubberduck.Parsing.VBA.ComReferenceLoading;
using Rubberduck.Parsing.VBA.DeclarationCaching;
Expand Down Expand Up @@ -98,8 +96,6 @@ internal Parser(object vbe) : this()
var projectRepository = new ProjectsRepository(_vbe);
_state = new RubberduckParserState(_vbe, projectRepository, declarationFinderFactory, _vbeEvents);
_state.StateChanged += _state_StateChanged;

var sourceFileHandler = _vbe.TempSourceFileHandler;
var vbeVersion = double.Parse(_vbe.Version, CultureInfo.InvariantCulture);
var predefinedCompilationConstants = new VBAPredefinedCompilationConstants(vbeVersion);
var typeLibProvider = new TypeLibWrapperProvider(projectRepository);
Expand All @@ -112,7 +108,6 @@ internal Parser(object vbe) : this()
var mainTokenStreamParser = new VBATokenStreamParser(mainParseErrorListenerFactory, mainParseErrorListenerFactory);
var tokenStreamProvider = new SimpleVBAModuleTokenStreamProvider();
var stringParser = new TokenStreamParserStringParserAdapterWithPreprocessing(tokenStreamProvider, mainTokenStreamParser, preprocessor);
var attributesSourceCodeHandler = new SourceFileHandlerSourceCodeHandlerAdapter(sourceFileHandler, projectRepository);
var projectManager = new RepositoryProjectManager(projectRepository);
var moduleToModuleReferenceManager = new ModuleToModuleReferenceManager();
var parserStateManager = new ParserStateManager(_state);
Expand All @@ -133,14 +128,12 @@ internal Parser(object vbe) : this()
}
);
var codePaneSourceCodeHandler = new CodePaneSourceCodeHandler(projectRepository);
var moduleRewriterFactory = new ModuleRewriterFactory(
codePaneSourceCodeHandler,
attributesSourceCodeHandler);
var sourceFileHandler = _vbe.TempSourceFileHandler;
var attributesSourceCodeHandler = new SourceFileHandlerSourceCodeHandlerAdapter(sourceFileHandler, projectRepository);
var moduleParser = new ModuleParser(
codePaneSourceCodeHandler,
attributesSourceCodeHandler,
stringParser,
moduleRewriterFactory);
stringParser);
var parseRunner = new ParseRunner(
_state,
parserStateManager,
Expand Down
Expand Up @@ -2,6 +2,7 @@
using System;
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Parsing.Symbols;

namespace Rubberduck.Inspections.CodePathAnalysis.Extensions
{
Expand Down Expand Up @@ -50,5 +51,34 @@ public static INode GetFirstNode(this INode node, IEnumerable<Type> excludedType

return GetFirstNode(node.Children[0], excludedTypes);
}

public static List<IdentifierReference> GetIdentifierReferences(this INode node)
{
var nodes = new List<IdentifierReference>();

var blockNodes = node.GetNodes(new[] { typeof(BlockNode) });
foreach (var block in blockNodes)
{
INode lastNode = default;
foreach (var flattenedNode in block.GetFlattenedNodes(new[] { typeof(GenericNode), typeof(BlockNode) }))
{
if (flattenedNode is AssignmentNode &&
lastNode is AssignmentNode)
{
nodes.Add(lastNode.Reference);
}

lastNode = flattenedNode;
}

if (lastNode is AssignmentNode &&
block.Children[0].GetFirstNode(new[] { typeof(GenericNode) }) is DeclarationNode)
{
nodes.Add(lastNode.Reference);
}
}

return nodes;
}
}
}
@@ -0,0 +1,23 @@
using System.Collections.Generic;
using System.Collections.Immutable;
using Antlr4.Runtime.Tree;
using Rubberduck.Parsing.Symbols;

namespace Rubberduck.Inspections.CodePathAnalysis.Nodes
{
public abstract class NodeBase : INode
{
protected NodeBase(IParseTree tree)
{
Children = new List<INode>().ToImmutableList();
ParseTree = tree;
}

public int SortOrder { get; set; }
public ImmutableList<INode> Children { get; set; }
public INode Parent { get; set; }
public IParseTree ParseTree { get; }
public Declaration Declaration { get; set; }
public IdentifierReference Reference { get; set; }
}
}
3 changes: 2 additions & 1 deletion Rubberduck.CodeAnalysis/CodePathAnalysis/Nodes/INode.cs
@@ -1,5 +1,6 @@
using Rubberduck.Parsing.Symbols;
using System.Collections.Immutable;
using Antlr4.Runtime.Tree;

namespace Rubberduck.Inspections.CodePathAnalysis.Nodes
{
Expand All @@ -8,7 +9,7 @@ public interface INode
int SortOrder { get; set; }
ImmutableList<INode> Children { get; set; }
INode Parent { get; set; }

IParseTree ParseTree { get; }
Declaration Declaration { get; set; }
IdentifierReference Reference { get; set; }
}
Expand Down
@@ -1,21 +1,9 @@
using System.Collections.Generic;
using System.Collections.Immutable;
using Rubberduck.Parsing.Symbols;
using Antlr4.Runtime.Tree;

namespace Rubberduck.Inspections.CodePathAnalysis.Nodes
{
public class AssignmentNode : INode
public class AssignmentNode : NodeBase
{
public AssignmentNode()
{
Children = new List<INode>().ToImmutableList();
}

public int SortOrder { get; set; }
public ImmutableList<INode> Children { get; set; }
public INode Parent { get; set; }

public Declaration Declaration { get; set; }
public IdentifierReference Reference { get; set; }
public AssignmentNode(IParseTree tree) : base(tree) { }
}
}
@@ -1,21 +1,9 @@
using System.Collections.Generic;
using System.Collections.Immutable;
using Rubberduck.Parsing.Symbols;
using Antlr4.Runtime.Tree;

namespace Rubberduck.Inspections.CodePathAnalysis.Nodes
{
public class BlockNode : INode
public class BlockNode : NodeBase
{
public BlockNode()
{
Children = new List<INode>().ToImmutableList();
}

public int SortOrder { get; set; }
public ImmutableList<INode> Children { get; set; }
public INode Parent { get; set; }

public Declaration Declaration { get; set; }
public IdentifierReference Reference { get; set; }
public BlockNode(IParseTree tree) : base(tree) { }
}
}
@@ -1,21 +1,9 @@
using System.Collections.Generic;
using System.Collections.Immutable;
using Rubberduck.Parsing.Symbols;
using Antlr4.Runtime.Tree;

namespace Rubberduck.Inspections.CodePathAnalysis.Nodes
{
public class BranchNode : IBranchNode
public class BranchNode : NodeBase, IBranchNode
{
public BranchNode()
{
Children = new List<INode>().ToImmutableList();
}

public int SortOrder { get; set; }
public ImmutableList<INode> Children { get; set; }
public INode Parent { get; set; }

public Declaration Declaration { get; set; }
public IdentifierReference Reference { get; set; }
public BranchNode(IParseTree tree) : base(tree) { }
}
}
@@ -1,21 +1,9 @@
using System.Collections.Generic;
using System.Collections.Immutable;
using Rubberduck.Parsing.Symbols;
using Antlr4.Runtime.Tree;

namespace Rubberduck.Inspections.CodePathAnalysis.Nodes
{
public class DeclarationNode : INode
public class DeclarationNode : NodeBase
{
public DeclarationNode()
{
Children = new List<INode>().ToImmutableList();
}

public int SortOrder { get; set; }
public ImmutableList<INode> Children { get; set; }
public INode Parent { get; set; }

public Declaration Declaration { get; set; }
public IdentifierReference Reference { get; set; }
public DeclarationNode(IParseTree tree) : base(tree) { }
}
}
@@ -1,21 +1,9 @@
using System.Collections.Generic;
using System.Collections.Immutable;
using Rubberduck.Parsing.Symbols;
using Antlr4.Runtime.Tree;

namespace Rubberduck.Inspections.CodePathAnalysis.Nodes
{
public class GenericNode : INode
public class GenericNode : NodeBase
{
public GenericNode()
{
Children = new List<INode>().ToImmutableList();
}

public int SortOrder { get; set; }
public ImmutableList<INode> Children { get; set; }
public INode Parent { get; set; }

public Declaration Declaration { get; set; }
public IdentifierReference Reference { get; set; }
public GenericNode(IParseTree tree) : base(tree) { }
}
}
@@ -1,21 +1,9 @@
using Rubberduck.Parsing.Symbols;
using System.Collections.Generic;
using System.Collections.Immutable;
using Antlr4.Runtime.Tree;

namespace Rubberduck.Inspections.CodePathAnalysis.Nodes
{
public class LoopNode : ILoopNode
public class LoopNode : NodeBase, ILoopNode
{
public LoopNode()
{
Children = new List<INode>().ToImmutableList();
}

public int SortOrder { get; set; }
public ImmutableList<INode> Children { get; set; }
public INode Parent { get; set; }

public Declaration Declaration { get; set; }
public IdentifierReference Reference { get; set; }
public LoopNode(IParseTree tree) : base(tree) { }
}
}
@@ -1,21 +1,9 @@
using System.Collections.Generic;
using System.Collections.Immutable;
using Rubberduck.Parsing.Symbols;
using Antlr4.Runtime.Tree;

namespace Rubberduck.Inspections.CodePathAnalysis.Nodes
{
public class ReferenceNode : INode
public class ReferenceNode : NodeBase
{
public ReferenceNode()
{
Children = new List<INode>().ToImmutableList();
}

public int SortOrder { get; set; }
public ImmutableList<INode> Children { get; set; }
public INode Parent { get; set; }

public Declaration Declaration { get; set; }
public IdentifierReference Reference { get; set; }
public ReferenceNode(IParseTree tree) : base(tree) { }
}
}
15 changes: 8 additions & 7 deletions Rubberduck.CodeAnalysis/CodePathAnalysis/Walker.cs
Expand Up @@ -5,6 +5,7 @@
using System.Collections.Generic;
using System.Collections.Immutable;
using System.Linq;
using Antlr4.Runtime;

namespace Rubberduck.Inspections.CodePathAnalysis
{
Expand All @@ -19,7 +20,7 @@ public INode GenerateTree(IParseTree tree, Declaration declaration)
case VBAParser.ForEachStmtContext _:
case VBAParser.WhileWendStmtContext _:
case VBAParser.DoLoopStmtContext _:
node = new LoopNode();
node = new LoopNode(tree);
break;
case VBAParser.IfStmtContext _:
case VBAParser.ElseBlockContext _:
Expand All @@ -28,16 +29,16 @@ public INode GenerateTree(IParseTree tree, Declaration declaration)
case VBAParser.SingleLineElseClauseContext _:
case VBAParser.CaseClauseContext _:
case VBAParser.CaseElseClauseContext _:
node = new BranchNode();
node = new BranchNode(tree);
break;
case VBAParser.BlockContext _:
node = new BlockNode();
node = new BlockNode(tree);
break;
}

if (declaration.Context == tree)
{
node = new DeclarationNode
node = new DeclarationNode(tree)
{
Declaration = declaration
};
Expand All @@ -48,14 +49,14 @@ public INode GenerateTree(IParseTree tree, Declaration declaration)
{
if (reference.IsAssignment)
{
node = new AssignmentNode
node = new AssignmentNode(tree)
{
Reference = reference
};
}
else
{
node = new ReferenceNode
node = new ReferenceNode(tree)
{
Reference = reference
};
Expand All @@ -64,7 +65,7 @@ public INode GenerateTree(IParseTree tree, Declaration declaration)

if (node == null)
{
node = new GenericNode();
node = new GenericNode(tree);
}

var children = new List<INode>();
Expand Down

0 comments on commit 2ed334e

Please sign in to comment.