Skip to content

Commit

Permalink
Merge pull request #4175 from WaynePhillipsEA/next
Browse files Browse the repository at this point in the history
Add user-defined project-level compilation arguments to the preprocessor
  • Loading branch information
retailcoder committed Jul 16, 2018
2 parents b8c99c9 + e6da06f commit 693d266
Show file tree
Hide file tree
Showing 12 changed files with 89 additions and 47 deletions.
3 changes: 2 additions & 1 deletion Rubberduck.Parsing/Preprocessing/IVBAPreprocessor.cs
@@ -1,10 +1,11 @@
using Antlr4.Runtime;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
using System.Threading;

namespace Rubberduck.Parsing.PreProcessing
{
public interface IVBAPreprocessor
{
void PreprocessTokenStream(string moduleName, CommonTokenStream unprocessedTokenStream, BaseErrorListener errorListener, CancellationToken token);
void PreprocessTokenStream(IVBProject project, string moduleName, CommonTokenStream unprocessedTokenStream, BaseErrorListener errorListener, CancellationToken token);
}
}
Expand Up @@ -22,23 +22,23 @@ public bool VBA7
{
get
{
return _vbVersion < 8;
return _vbVersion >= 7;
}
}

public bool VBA6
{
get
{
return _vbVersion < 7;
return _vbVersion >= 6;
}
}

public bool Win64
{
get
{
return Environment.Is64BitOperatingSystem;
return IntPtr.Size >= 8;
}
}

Expand Down
26 changes: 24 additions & 2 deletions Rubberduck.Parsing/Preprocessing/VBAPreprocessor.cs
Expand Up @@ -2,6 +2,11 @@
using System.Threading;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
using System.Collections.Generic;
using Rubberduck.VBEditor.ComManagement.TypeLibs;
using Rubberduck.VBEditor.Utility;
using Rubberduck.Parsing.UIContext;

namespace Rubberduck.Parsing.PreProcessing
{
Expand All @@ -16,17 +21,34 @@ public VBAPreprocessor(double vbaVersion)
_parser = new VBAPrecompilationParser();
}

public void PreprocessTokenStream(string moduleName, CommonTokenStream tokenStream, BaseErrorListener errorListener, CancellationToken token)
public void PreprocessTokenStream(IVBProject project, string moduleName, CommonTokenStream tokenStream, BaseErrorListener errorListener, CancellationToken token)
{
token.ThrowIfCancellationRequested();
var symbolTable = new SymbolTable<string, IValue>();
var tree = _parser.Parse(moduleName, tokenStream, errorListener);
token.ThrowIfCancellationRequested();
var stream = tokenStream.TokenSource.InputStream;
var evaluator = new VBAPreprocessorVisitor(symbolTable, new VBAPredefinedCompilationConstants(_vbaVersion), stream, tokenStream);
var evaluator = new VBAPreprocessorVisitor(symbolTable, new VBAPredefinedCompilationConstants(_vbaVersion), GetUserDefinedCompilationArguments(project), stream, tokenStream);
var expr = evaluator.Visit(tree);
var processedTokens = expr.Evaluate(); //This does the actual preprocessing of the token stream as a side effect.
tokenStream.Reset();
}

public Dictionary<string, short> GetUserDefinedCompilationArguments(IVBProject project)
{
// for the mocks, just return an empty dictionary for now
if (project == null) return new Dictionary<string, short>();

// use the TypeLib API to grab the user defined compilation arguments. must be obtained on the main thread.
var providerInst = UiContextProvider.Instance();
var task = (new UiDispatcher(providerInst)).StartTask(delegate () {
using (var typeLib = TypeLibWrapper.FromVBProject(project))
{
return typeLib.ConditionalCompilationArguments;
}
});
task.Wait();
return task.Result;
}
}
}
23 changes: 17 additions & 6 deletions Rubberduck.Parsing/Preprocessing/VBAPreprocessorVisitor.cs
Expand Up @@ -3,6 +3,7 @@
using Antlr4.Runtime;
using Antlr4.Runtime.Misc;
using Rubberduck.Parsing.Symbols;
using System.Collections.Generic;

namespace Rubberduck.Parsing.PreProcessing
{
Expand All @@ -15,6 +16,7 @@ public sealed class VBAPreprocessorVisitor : VBAConditionalCompilationParserBase
public VBAPreprocessorVisitor(
SymbolTable<string, IValue> symbolTable,
VBAPredefinedCompilationConstants predefinedConstants,
Dictionary<string, short> userDefinedConstants,
ICharStream stream,
CommonTokenStream tokenStream)
{
Expand All @@ -39,16 +41,25 @@ public sealed class VBAPreprocessorVisitor : VBAConditionalCompilationParserBase
_tokenStream = tokenStream;
_symbolTable = symbolTable;
AddPredefinedConstantsToSymbolTable(predefinedConstants);
AddUserDefinedConstantsToSymbolTable(userDefinedConstants);
}

private void AddPredefinedConstantsToSymbolTable(VBAPredefinedCompilationConstants predefinedConstants)
{
_symbolTable.Add(VBAPredefinedCompilationConstants.VBA6_NAME, new BoolValue(predefinedConstants.VBA6));
_symbolTable.Add(VBAPredefinedCompilationConstants.VBA7_NAME, new BoolValue(predefinedConstants.VBA7));
_symbolTable.Add(VBAPredefinedCompilationConstants.WIN64_NAME, new BoolValue(predefinedConstants.Win64));
_symbolTable.Add(VBAPredefinedCompilationConstants.WIN32_NAME, new BoolValue(predefinedConstants.Win32));
_symbolTable.Add(VBAPredefinedCompilationConstants.WIN16_NAME, new BoolValue(predefinedConstants.Win16));
_symbolTable.Add(VBAPredefinedCompilationConstants.MAC_NAME, new BoolValue(predefinedConstants.Mac));
_symbolTable.Add(VBAPredefinedCompilationConstants.VBA6_NAME, new DecimalValue(predefinedConstants.VBA6 ? 1 : 0));
_symbolTable.Add(VBAPredefinedCompilationConstants.VBA7_NAME, new DecimalValue(predefinedConstants.VBA7 ? 1 : 0));
_symbolTable.Add(VBAPredefinedCompilationConstants.WIN64_NAME, new DecimalValue(predefinedConstants.Win64 ? 1 : 0));
_symbolTable.Add(VBAPredefinedCompilationConstants.WIN32_NAME, new DecimalValue(predefinedConstants.Win32 ? 1 : 0));
_symbolTable.Add(VBAPredefinedCompilationConstants.WIN16_NAME, new DecimalValue(predefinedConstants.Win16 ? 1 : 0));
_symbolTable.Add(VBAPredefinedCompilationConstants.MAC_NAME, new DecimalValue(predefinedConstants.Mac ? 1 : 0));
}

private void AddUserDefinedConstantsToSymbolTable(Dictionary<string, short> userDefinedConstants)
{
foreach (var constant in userDefinedConstants)
{
_symbolTable.Add(constant.Key, new DecimalValue(constant.Value));
}
}

public override IExpression VisitCompilationUnit([NotNull] VBAConditionalCompilationParser.CompilationUnitContext context)
Expand Down
7 changes: 5 additions & 2 deletions Rubberduck.Parsing/VBA/AttributeParser.cs
Expand Up @@ -52,8 +52,11 @@ public AttributeParser(ISourceCodeHandler sourceCodeHandler, Func<IVBAPreprocess
var tokenStreamProvider = new SimpleVBAModuleTokenStreamProvider();
var tokens = tokenStreamProvider.Tokens(code);
var preprocessor = _preprocessorFactory();
var preprocessorErrorListener = new PreprocessorExceptionErrorListener(module.ComponentName, ParsePass.AttributesPass);
preprocessor.PreprocessTokenStream(module.ComponentName, tokens, preprocessorErrorListener, cancellationToken);
var preprocessorErrorListener = new PreprocessorExceptionErrorListener(module.ComponentName, ParsePass.AttributesPass);
using (var project = component.ParentProject)
{
preprocessor.PreprocessTokenStream(project, module.ComponentName, tokens, preprocessorErrorListener, cancellationToken);
}
var listener = new AttributeListener(Tuple.Create(module.ComponentName, type));
// parse tree isn't usable for declarations because
// line numbers are offset due to module header and attributes
Expand Down
7 changes: 5 additions & 2 deletions Rubberduck.Parsing/VBA/ComponentParseTask.cs
Expand Up @@ -170,9 +170,9 @@ private static string GetCode(ICodeModule codeModule)
private CommonTokenStream RewriteAndPreprocess(CancellationToken cancellationToken)
{
var code = _rewriter?.GetText();
var component = _projectsProvider.Component(_module);
if (code == null)
{
var component = _projectsProvider.Component(_module);
using (var codeModule = component.CodeModule)
{
code = string.Join(Environment.NewLine, GetCode(codeModule));
Expand All @@ -181,7 +181,10 @@ private CommonTokenStream RewriteAndPreprocess(CancellationToken cancellationTok

var tokenStreamProvider = new SimpleVBAModuleTokenStreamProvider();
var tokens = tokenStreamProvider.Tokens(code);
_preprocessor.PreprocessTokenStream(_module.Name, tokens, new PreprocessorExceptionErrorListener(_module.ComponentName, ParsePass.CodePanePass), cancellationToken);
using (var project = component.ParentProject)
{
_preprocessor.PreprocessTokenStream(project, _module.Name, tokens, new PreprocessorExceptionErrorListener(_module.ComponentName, ParsePass.CodePanePass), cancellationToken);
}
return tokens;
}

Expand Down
24 changes: 12 additions & 12 deletions Rubberduck.VBEEditor/ComManagement/TypeLibs/IVBETypeLibsAPI.cs
Expand Up @@ -158,24 +158,24 @@ public interface IVBETypeLibsAPI
/// <remarks>does not expose compiler-defined arguments, such as WIN64, VBA7 etc, which must be determined via the running process</remarks>
/// <param name="ide">Safe-com wrapper representing the VBE</param>
/// <param name="projectName">VBA Project name, as declared in the VBE</param>
/// <returns>returns a Dictionary<string, string>, parsed from the conditional arguments string</returns>
Dictionary<string, string> GetProjectConditionalCompilationArgs(IVBE ide, string projectName);
/// <returns>returns a Dictionary<string, short>, parsed from the conditional arguments string</returns>
Dictionary<string, short> GetProjectConditionalCompilationArgs(IVBE ide, string projectName);

/// <summary>
/// Retrieves the developer-defined conditional compilation arguments of a VBA project
/// </summary>
/// <remarks>does not expose compiler-defined arguments, such as WIN64, VBA7 etc, which must be determined via the running process</remarks>
/// <param name="project">Safe-com wrapper representing the VBA project</param>
/// <returns>returns a Dictionary<string, string>, parsed from the conditional arguments string</returns>
Dictionary<string, string> GetProjectConditionalCompilationArgs(IVBProject project);
/// <returns>returns a Dictionary<string, short>, parsed from the conditional arguments string</returns>
Dictionary<string, short> GetProjectConditionalCompilationArgs(IVBProject project);

/// <summary>
/// Retrieves the developer-defined conditional compilation arguments of a VBA project
/// </summary>
/// <remarks>does not expose compiler-defined arguments, such as WIN64, VBA7 etc, which must be determined via the running process</remarks>
/// <param name="projectTypeLib">Low-level ITypeLib wrapper representing the VBA project</param>
/// <returns>returns a Dictionary<string, string>, parsed from the conditional arguments string</returns>
Dictionary<string, string> GetProjectConditionalCompilationArgs(TypeLibWrapper projectTypeLib);
/// <returns>returns a Dictionary<string, short>, parsed from the conditional arguments string</returns>
Dictionary<string, short> GetProjectConditionalCompilationArgs(TypeLibWrapper projectTypeLib);

/// <summary>
/// Sets the developer-defined conditional compilation arguments of a VBA project
Expand Down Expand Up @@ -208,24 +208,24 @@ public interface IVBETypeLibsAPI
/// <remarks>don't set compiler-defined arguments, such as WIN64, VBA7 etc</remarks>
/// <param name="ide">Safe-com wrapper representing the VBE</param>
/// <param name="projectName">VBA Project name, as declared in the VBE</param>
/// <param name="newConditionalArgs">Dictionary<string, string> representing the argument name-value pairs</param>
void SetProjectConditionalCompilationArgs(IVBE ide, string projectName, Dictionary<string, string> newConditionalArgs);
/// <param name="newConditionalArgs">Dictionary<string, short> representing the argument name-value pairs</param>
void SetProjectConditionalCompilationArgs(IVBE ide, string projectName, Dictionary<string, short> newConditionalArgs);

/// <summary>
/// Sets the developer-defined conditional compilation arguments of a VBA project
/// </summary>
/// <remarks>don't set compiler-defined arguments, such as WIN64, VBA7 etc</remarks>
/// <param name="project">Safe-com wrapper representing the VBA project</param>
/// <param name="newConditionalArgs">Dictionary<string, string> representing the argument name-value pairs</param>
void SetProjectConditionalCompilationArgs(IVBProject project, Dictionary<string, string> newConditionalArgs);
/// <param name="newConditionalArgs">Dictionary<string, short> representing the argument name-value pairs</param>
void SetProjectConditionalCompilationArgs(IVBProject project, Dictionary<string, short> newConditionalArgs);

/// <summary>
/// Sets the developer-defined conditional compilation arguments of a VBA project
/// </summary>
/// <remarks>don't set compiler-defined arguments, such as WIN64, VBA7 etc</remarks>
/// <param name="projectTypeLib">Low-level ITypeLib wrapper representing the VBA project</param>
/// <param name="newConditionalArgs">Dictionary<string, string> representing the argument name-value pairs</param>
void SetProjectConditionalCompilationArgs(TypeLibWrapper projectTypeLib, Dictionary<string, string> newConditionalArgs);
/// <param name="newConditionalArgs">Dictionary<string, short> representing the argument name-value pairs</param>
void SetProjectConditionalCompilationArgs(TypeLibWrapper projectTypeLib, Dictionary<string, short> newConditionalArgs);

/// <summary>
/// Determines whether the specified document class is a known document class type (e.g. Excel._Workbook, Access._Form)
Expand Down
6 changes: 3 additions & 3 deletions Rubberduck.VBEEditor/ComManagement/TypeLibs/TypeLibs.cs
Expand Up @@ -336,7 +336,7 @@ public string ConditionalCompilationArgumentsRaw
/// Exposes the conditional compilation arguments defined in the BA project represented by this ITypeLib
/// as a dictionary of key/value pairs
/// </summary>
public Dictionary<string, string> ConditionalCompilationArguments
public Dictionary<string, short> ConditionalCompilationArguments
{
get
{
Expand All @@ -350,11 +350,11 @@ public string ConditionalCompilationArgumentsRaw
if (args.Length > 0)
{
string[] argsArray = args.Split(new[] { ':' });
return argsArray.Select(item => item.Split('=')).ToDictionary(s => s[0], s => s[1]);
return argsArray.Select(item => item.Split('=')).ToDictionary(s => s[0].Trim(), s => short.Parse(s[1]));
}
else
{
return new Dictionary<string, string>();
return new Dictionary<string, short>();
}
}

Expand Down

0 comments on commit 693d266

Please sign in to comment.