Skip to content

Commit

Permalink
Merge pull request #1738 from rubberduck-vba/next
Browse files Browse the repository at this point in the history
v2.0b
  • Loading branch information
retailcoder committed Jun 8, 2016
2 parents 29f98b9 + f459715 commit d726201
Show file tree
Hide file tree
Showing 829 changed files with 57,943 additions and 36,859 deletions.
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -83,6 +83,7 @@ _TeamCity*
# NCrunch
*.ncrunch*
.*crunch*.local.xml
_Ncrunch*

# Installshield output folder
[Ee]xpress/
Expand Down
6 changes: 4 additions & 2 deletions Installer Build Script.iss
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
#define AddinDLL "Rubberduck.dll"
#define AppVersion GetFileVersion(SourcePath + "RetailCoder.VBE\bin\release\Rubberduck.dll")
#define AppPublisher "Rubberduck"
#define AppURL "http://rubberduck-vba.com"
#define AppURL "http://rubberduckvba.com"
#define License SourcePath + "\License.rtf"
#define OutputDirectory SourcePath + "\Installers"
#define AddinProgId "Rubberduck.Extension"
Expand Down Expand Up @@ -95,14 +95,16 @@ end;
function GetOfficeBitness(): Integer;
var
appBitness: Integer;
officeExeNames: array[0..4] of String;
officeExeNames: array[0..6] of String;
i: Integer;
begin
officeExeNames[0] := 'excel.exe';
officeExeNames[1] := 'msaccess.exe';
officeExeNames[2] := 'winword.exe';
officeExeNames[3] := 'outlook.exe';
officeExeNames[4] := 'powerpnt.exe';
officeExeNames[5] := 'mspub.exe';
officeExeNames[6] := 'winproj.exe';
for i := 0 to 4 do begin
appBitness := GetOfficeAppBitness(officeExeNames[i]);
Expand Down
33 changes: 17 additions & 16 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -8,36 +8,31 @@
[nextBuildStatus]:https://ci.appveyor.com/api/projects/status/we3pdnkeebo4nlck/branch/next?svg=true
[masterBuildStatus]:https://ci.appveyor.com/api/projects/status/we3pdnkeebo4nlck/branch/master?svg=true

Rubberduck is a COM Add-In for the VBA IDE that makes VBA development even more enjoyable, by extending the Visual Basic Editor (VBE) with menus, toolbars and toolwindows that enable things we didn't even think were possible when we first started this project.
[![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")

If you're learning VBA, Rubberduck can help you avoid a few common beginner mistakes, and can probably show you a trick or two - even if you're only ever writing *macros*. If you're a more advanced programmer, you will appreciate the richness of [Rubberduck's feature set](https://github.com/retailcoder/Rubberduck/wiki/Features).

[**Follow us on Twitter!**](https://twitter.com/rubberduckvba)

[**Rubberduck Wiki**](https://github.com/retailcoder/Rubberduck/wiki)
> **[rubberduckvba.com](http://rubberduckvba.com)** [Wiki](https://github.com/retailcoder/Rubberduck/wiki) [Rubberduck News](https://rubberduckvba.wordpress.com/)
> contact@rubberduckvba.com
> Follow [@rubberduckvba](https://twitter.com/rubberduckvba) on Twitter
---

#[Contributing](https://github.com/rubberduck-vba/Rubberduck/wiki/Contributing)
##What is Rubberduck?

If you're a C# developer looking for a fun project to contribute to, feel free to fork the project and
[come meet the devs in Code Review's "VBA Rubberducking" chatroom][chat] - we'll be happy to answer your questions and help you help us!
It's an add-in for the VBA IDE, the glorious *Visual Basic Editor* (VBE) - which hasn't seen an update in this century, but that's still in use everywhere around the world. Rubberduck wants to give its users access to features you would find in the VBE if it had kept up with the features of Visual Studio and other IDE's in the past, oh, *decade* or so.

We follow a [development branch workflow][branch], so please submit any Pull Requests to the `next` branch.
Rubberduck wants to help its users write better, cleaner, maintainable code. The many **code inspections** and **refactoring tools** help harmlessly making changes to the code, and **unit testing** helps writing a *safety net* that makes it easy to know exactly what broke when you made that *small little harmless modification*.

[chat]:http://chat.stackexchange.com/rooms/14929
[helpwanted]:https://github.com/rubberduck-vba/Rubberduck/labels/help-wanted
[branch]:https://github.com/rubberduck-vba/Rubberduck/issues/288
Rubberduck wants to bring VBA into the 21st century, and wants to see more open-source VBA repositories on [GitHub](https://github.com/) - VBA code and **source control** don't traditionally exactly work hand in hand; unless you've automated it, exporting each module one by one to your local repository, fetching the remote changes, re-importing every module one by one back into the project, ...is *a little bit* tedious. Rubberduck integrates Git into the IDE, and handles all the file handling behind the scenes - a bit like Visual Studio's *Team Explorer*.

---

#[Installing](https://github.com/rubberduck-vba/Rubberduck/wiki/Installing)
If you're learning VBA, Rubberduck can help you avoid a few common beginner mistakes, and can probably show you a trick or two - even if you're only ever writing *macros*. If you're a more advanced programmer, you will appreciate the richness of [Rubberduck's feature set](https://github.com/retailcoder/Rubberduck/wiki/Features). See the [Installing](https://github.com/rubberduck-vba/Rubberduck/wiki/Installing) wiki page.

This section was moved to a dedicated wiki page.
If you're a C# developer looking for a fun project to contribute to, see the [Contributing](https://github.com/rubberduck-vba/Rubberduck/wiki/Contributing) wiki page.

---

#License
##License

Rubberduck is a COM add-in for the VBA IDE (VBE).

Expand Down Expand Up @@ -92,6 +87,12 @@ This library makes localizing WPF applications at runtime using resx files a bre

> Licensed under [The Code Project Open License](http://www.codeproject.com/info/cpol10.aspx).
###[Using Raw Input from C# to handle multiple keyboards](http://www.codeproject.com/Articles/17123/Using-Raw-Input-from-C-to-handle-multiple-keyboard)

A library using the Raw Input API for reacting to low level keyboard/mouse events.

> Licensed under [The Code Project Open License](http://www.codeproject.com/info/cpol10.aspx).
##Icons

We didn't come up with these icons ourselves! Here's who did what:
Expand Down
2 changes: 1 addition & 1 deletion RetailCoder.VBE/API/Accessibility.cs
Original file line number Diff line number Diff line change
Expand Up @@ -12,4 +12,4 @@ public enum Accessibility
Friend,
Static,
}
}
}
37 changes: 33 additions & 4 deletions RetailCoder.VBE/API/Declaration.cs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
using System.ComponentModel;
using System.Collections.Generic;
using System.ComponentModel;
using System.Linq;
using System.Runtime.InteropServices;
using RubberduckDeclaration = Rubberduck.Parsing.Symbols.Declaration;
Expand Down Expand Up @@ -39,18 +40,46 @@ internal Declaration(RubberduckDeclaration declaration)

protected RubberduckDeclaration Instance { get { return _declaration; } }

public bool IsArray { get { return _declaration.IsArray; } }
public string Name { get { return _declaration.IdentifierName; } }
public Accessibility Accessibility { get { return (Accessibility)_declaration.Accessibility; } }
public DeclarationType DeclarationType {get { return (DeclarationType)_declaration.DeclarationType; }}
public DeclarationType DeclarationType {get { return TypeMappings[_declaration.DeclarationType]; }}
public string TypeName { get { return _declaration.AsTypeName; } }
public bool IsArray { get { return _declaration.IsArray(); } }

private static readonly IDictionary<Parsing.Symbols.DeclarationType,DeclarationType> TypeMappings =
new Dictionary<Parsing.Symbols.DeclarationType, DeclarationType>
{
{ Parsing.Symbols.DeclarationType.Project, DeclarationType.Project },
{ Parsing.Symbols.DeclarationType.ProceduralModule, DeclarationType.StandardModule },
{ Parsing.Symbols.DeclarationType.ClassModule, DeclarationType.ClassModule },
{ Parsing.Symbols.DeclarationType.Control, DeclarationType.Control },
{ Parsing.Symbols.DeclarationType.UserForm, DeclarationType.UserForm },
{ Parsing.Symbols.DeclarationType.Document, DeclarationType.Document },
{ Parsing.Symbols.DeclarationType.ModuleOption, DeclarationType.ModuleOption },
{ Parsing.Symbols.DeclarationType.Procedure, DeclarationType.Procedure },
{ Parsing.Symbols.DeclarationType.Function, DeclarationType.Function },
{ Parsing.Symbols.DeclarationType.PropertyGet, DeclarationType.PropertyGet },
{ Parsing.Symbols.DeclarationType.PropertyLet, DeclarationType.PropertyLet },
{ Parsing.Symbols.DeclarationType.PropertySet, DeclarationType.PropertySet },
{ Parsing.Symbols.DeclarationType.Parameter, DeclarationType.Parameter },
{ Parsing.Symbols.DeclarationType.Variable, DeclarationType.Variable },
{ Parsing.Symbols.DeclarationType.Constant, DeclarationType.Constant },
{ Parsing.Symbols.DeclarationType.Enumeration, DeclarationType.Enumeration },
{ Parsing.Symbols.DeclarationType.EnumerationMember, DeclarationType.EnumerationMember },
{ Parsing.Symbols.DeclarationType.Event, DeclarationType.Event },
{ Parsing.Symbols.DeclarationType.UserDefinedType, DeclarationType.UserDefinedType },
{ Parsing.Symbols.DeclarationType.UserDefinedTypeMember, DeclarationType.UserDefinedTypeMember },
{ Parsing.Symbols.DeclarationType.LibraryFunction, DeclarationType.LibraryFunction },
{ Parsing.Symbols.DeclarationType.LibraryProcedure, DeclarationType.LibraryProcedure },
{ Parsing.Symbols.DeclarationType.LineLabel, DeclarationType.LineLabel },
};

private Declaration _parentDeclaration;
public Declaration ParentDeclaration
{
get
{
return _parentDeclaration ?? (_parentDeclaration = new Declaration(Instance));
return _parentDeclaration ?? (_parentDeclaration = new Declaration(Instance.ParentDeclaration));
}
}

Expand Down
58 changes: 29 additions & 29 deletions RetailCoder.VBE/API/DeclarationType.cs
Original file line number Diff line number Diff line change
@@ -1,36 +1,36 @@
using System;
using System.Runtime.InteropServices;
using System.Runtime.InteropServices;

namespace Rubberduck.API
{
[ComVisible(true)]
[Flags]
//[Flags]
public enum DeclarationType
{
Project = 1 << 0,
Module = 1 << 1,
Class = 1 << 2,
Control = 1 << 3,
UserForm = 1 << 4,
Document = 1 << 5,
ModuleOption = 1 << 6,
Member = 1 << 7,
Procedure = 1 << 8 | Member,
Function = 1 << 9 | Member,
Property = 1 << 10 | Member,
PropertyGet = 1 << 11 | Property | Function,
PropertyLet = 1 << 12 | Property | Procedure,
PropertySet = 1 << 13 | Property | Procedure,
Parameter = 1 << 14,
Variable = 1 << 15,
Constant = 1 << 16,
Enumeration = 1 << 17,
EnumerationMember = 1 << 18 | Constant,
Event = 1 << 19,
UserDefinedType = 1 << 20,
UserDefinedTypeMember = 1 << 21 | Variable,
LibraryFunction = 1 << 22 | Function,
LibraryProcedure = 1 << 23 | Procedure,
LineLabel = 1 << 24
Project, //= 1 << 0,
StandardModule, //= 1 << 1,
ClassModule,// = 1 << 2,
Control, //= 1 << 3,
UserForm,// = 1 << 4,
Document,// = 1 << 5,
ModuleOption,// = 1 << 6,
Procedure, //= 1 << 8,
Function,// = 1 << 9,
PropertyGet,// = 1 << 11,
PropertyLet, //= 1 << 12,
PropertySet, //= 1 << 13,
Parameter, //= 1 << 14,
Variable, //= 1 << 15,
Constant,// = 1 << 16,
Enumeration, //= 1 << 17,
EnumerationMember, //= 1 << 18,
Event, //= 1 << 19,
UserDefinedType,// = 1 << 20,
UserDefinedTypeMember,// = 1 << 21,
LibraryFunction,// = 1 << 22,
LibraryProcedure,// = 1 << 23,
LineLabel,// = 1 << 24,
//Member = Procedure | Function | PropertyGet | PropertyLet | PropertySet,
//Property = PropertyGet | PropertyLet | PropertySet,
//Module = StandardModule | ClassModule | UserForm | Document
}
}
}
3 changes: 3 additions & 0 deletions RetailCoder.VBE/API/IdentifierReference.cs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ public interface IIdentifierReference
Declaration Declaration { get; }
Declaration ParentScope { get; }
Declaration ParentNonScoping { get; }
bool IsAssignment { get; }
int StartLine { get; }
int StartColumn { get; }
int EndLine { get; }
Expand Down Expand Up @@ -51,6 +52,8 @@ public Declaration ParentNonScoping
get { return _parentNonScoping ?? (_parentNonScoping = new Declaration(_reference.ParentNonScoping)); }
}

public bool IsAssignment { get { return _reference.IsAssignment; } }

public int StartLine { get { return _reference.Selection.StartLine; } }
public int EndLine { get { return _reference.Selection.EndLine; } }
public int StartColumn { get { return _reference.Selection.StartColumn; } }
Expand Down
43 changes: 31 additions & 12 deletions RetailCoder.VBE/API/ParserState.cs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,9 @@
using Microsoft.Vbe.Interop;
using Rubberduck.Common;
using Rubberduck.Parsing.VBA;
using Rubberduck.UI.Command.MenuItems;
using Rubberduck.Parsing.Preprocessing;
using System.Globalization;

namespace Rubberduck.API
{
Expand Down Expand Up @@ -37,20 +40,19 @@ public interface IParserStateEvents
[ComDefaultInterface(typeof(IParserState))]
[ComSourceInterfaces(typeof(IParserStateEvents))]
[EditorBrowsable(EditorBrowsableState.Always)]
public class ParserState : IParserState
public sealed class ParserState : IParserState, IDisposable
{
private const string ClassId = "28754D11-10CC-45FD-9F6A-525A65412B7A";
private const string ProgId = "Rubberduck.ParserState";

private readonly RubberduckParserState _state;
private readonly AttributeParser _attributeParser;

private AttributeParser _attributeParser;
private RubberduckParser _parser;

public ParserState()
{
UiDispatcher.Initialize();
_state = new RubberduckParserState();
_attributeParser = new AttributeParser(new ModuleExporter());

_state.StateChanged += _state_StateChanged;
}
Expand All @@ -61,8 +63,9 @@ public void Initialize(VBE vbe)
{
throw new InvalidOperationException("ParserState is already initialized.");
}

_parser = new RubberduckParser(vbe, _state, _attributeParser);
Func<IVBAPreprocessor> preprocessorFactory = () => new VBAPreprocessor(double.Parse(vbe.Version, CultureInfo.InvariantCulture));
_attributeParser = new AttributeParser(new ModuleExporter(), preprocessorFactory);
_parser = new RubberduckParser(vbe, _state, _attributeParser, preprocessorFactory);
}

/// <summary>
Expand All @@ -80,7 +83,7 @@ public void Parse()
public void BeginParse()
{
// non-blocking call
_state.OnParseRequested(this);
UiDispatcher.Invoke(() => _state.OnParseRequested(this));
}

public event Action OnParsed;
Expand All @@ -100,35 +103,51 @@ private void _state_StateChanged(object sender, System.EventArgs e)
var errorHandler = OnError;
if (_state.Status == Parsing.VBA.ParserState.Error && errorHandler != null)
{
errorHandler.Invoke();
UiDispatcher.Invoke(errorHandler.Invoke);
}

var parsedHandler = OnParsed;
if (_state.Status == Parsing.VBA.ParserState.Parsed && parsedHandler != null)
{
parsedHandler.Invoke();
UiDispatcher.Invoke(parsedHandler.Invoke);
}

var readyHandler = OnReady;
if (_state.Status == Parsing.VBA.ParserState.Ready && readyHandler != null)
{
readyHandler.Invoke();
UiDispatcher.Invoke(readyHandler.Invoke);
}
}

private Declaration[] _allDeclarations;

public Declaration[] AllDeclarations
{
[return: MarshalAs(UnmanagedType.SafeArray, SafeArraySubType = VarEnum.VT_VARIANT)]
//[return: MarshalAs(UnmanagedType.SafeArray/*, SafeArraySubType = VarEnum.VT_VARIANT*/)]
get { return _allDeclarations; }
}

private Declaration[] _userDeclarations;
public Declaration[] UserDeclarations
{
[return: MarshalAs(UnmanagedType.SafeArray, SafeArraySubType = VarEnum.VT_VARIANT)]
//[return: MarshalAs(UnmanagedType.SafeArray/*, SafeArraySubType = VarEnum.VT_VARIANT*/)]
get { return _userDeclarations; }
}

private bool _disposed;
public void Dispose()
{
if (_disposed)
{
return;
}

if (_state != null)
{
_state.StateChanged -= _state_StateChanged;
}

_disposed = true;
}
}
}
Loading

0 comments on commit d726201

Please sign in to comment.