Skip to content

Commit

Permalink
Merge branch 'RemoveParamsRewriter' of https://github.com/Hosch250/Ru…
Browse files Browse the repository at this point in the history
  • Loading branch information
Hosch250 committed Mar 24, 2017
2 parents 462237f + cf6921a commit d16f5db
Show file tree
Hide file tree
Showing 67 changed files with 2,452 additions and 645 deletions.
34 changes: 22 additions & 12 deletions README.md
Expand Up @@ -16,7 +16,7 @@ Branch | Description | Build Status |
---

##What is Rubberduck?
## What is Rubberduck?

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.

Expand All @@ -32,7 +32,7 @@ If you're a C# developer looking for a fun project to contribute to, see the [Co

---

##License
## License

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

Expand All @@ -53,11 +53,11 @@ along with this program. If not, see http://www.gnu.org/licenses/.

---

#Attributions
# Attributions

##Software & Libraries
## Software & Libraries

###[ANTLR](http://www.antlr.org/)
### [ANTLR](http://www.antlr.org/)

As of v1.2, Rubberduck is empowered by the awesomeness of ANTLR.

Expand All @@ -67,7 +67,7 @@ As of v1.2, Rubberduck is empowered by the awesomeness of ANTLR.
We're not doing half of what we could be doing with this amazing tool. Try it, see for yourself!

###[LibGit2Sharp](https://github.com/libgit2/libgit2sharp)
### [LibGit2Sharp](https://github.com/libgit2/libgit2sharp)

**What is LibGit2Sharp?**

Expand All @@ -81,39 +81,47 @@ LibGit2Sharp is the library that has allowed us to integrate Git right into the
Which basically means it's a reimplementation of Git in C. It also [happens to be the technology Microsoft uses for their own Git integration with Visual Studio](http://www.hanselman.com/blog/GitSupportForVisualStudioGitTFSAndVSPutIntoContext.aspx).

###[AvalonEdit](http://avalonedit.net)
### [AvalonEdit](http://avalonedit.net)

Source code looks a lot better with syntax highlighting, and AvalonEdit excels at it.

> AvalonEdit is a WPF-based text editor component. It was written by [Daniel Grunwald](https://github.com/dgrunwald) for the [SharpDevelop](http://www.icsharpcode.net/OpenSource/SD/) IDE. Starting with version 5.0, AvalonEdit is released under the [MIT license](http://opensource.org/licenses/MIT).
We're currently only using a tiny bit of this code editor's functionality (more to come!).

###[WPF Localization Using RESX Files](http://www.codeproject.com/Articles/35159/WPF-Localization-Using-RESX-Files)
### [EasyHook](http://easyhook.github.io/index.html)

Without the EasyHook library, many of our more advanced Unit Testing features would simply not be possible. This library really lives up to its name, and allows us to intercept and inspect traffic through VBE7.dll and other unmanged libraries.

> EasyHook makes it possible to extend (via hooking) unmanaged code APIs with pure managed functions, from within a fully managed environment on 32- or 64-bit Windows XP SP2, Windows Vista x64, Windows Server 2008 x64, Windows 7, Windows 8.1, and Windows 10.
EasyHook is released under the [MIT license](https://github.com/EasyHook/EasyHook#license).

### [WPF Localization Using RESX Files](http://www.codeproject.com/Articles/35159/WPF-Localization-Using-RESX-Files)

This library makes localizing WPF applications at runtime using resx files a breeze. Thank you [Grant Frisken](http://www.codeproject.com/script/Membership/View.aspx?mid=1079060)!

> Licensed under [The Code Project Open License](http://www.codeproject.com/info/cpol10.aspx) with the [author's permission](http://www.codeproject.com/Messages/5272045/Re-License.aspx) to re-release under the GPLv3.
##Icons
## Icons

We didn't come up with these icons ourselves! Here's who did what:

###[Fugue Icons](http://p.yusukekamiyamane.com/)
### [Fugue Icons](http://p.yusukekamiyamane.com/)

This beautiful suite of professional-grade icons packs over 3,570 icons (16x16). You name it, there's an icon for that.

> (C) 2012 Yusuke Kamiyamane. All rights reserved.
These icons are licensed under a [Creative Commons Attribution 3.0 License](http://creativecommons.org/licenses/by/3.0/).
If you can't or don't want to provide attribution, please [purchase a royalty-free license](http://p.yusukekamiyamane.com/).

###[SharpDevelop](https://github.com/icsharpcode/SharpDevelop.git)
### [SharpDevelop](https://github.com/icsharpcode/SharpDevelop.git)

Icons in the `./Resources/Custom/` directory were created by (or modified using elements from) the SharpDevelop icon set licensed under the [MIT license](https://opensource.org/licenses/MIT).

---

##[JetBrains](https://www.jetbrains.com) | [ReSharper](https://www.jetbrains.com/resharper/)
## [JetBrains](https://www.jetbrains.com) | [ReSharper](https://www.jetbrains.com/resharper/)

[![JetBrains ReSharper logo](https://cloud.githubusercontent.com/assets/5751684/20271309/616bb740-aa58-11e6-91c9-65287b740985.png)](https://www.jetbrains.com/resharper/)

Expand Down Expand Up @@ -198,3 +206,5 @@ End Sub
---

There's *quite a lot* to Rubberduck, the above is barely even a "quick tour"; the project's [website](http://www.rubberduckvba.com/) lists all the features, and the [wiki](https://github.com/rubberduck-vba/Rubberduck/wiki) will eventually document everything there is to document. Feel free to poke around and break things and [request features / create new issues](https://github.com/rubberduck-vba/Rubberduck/issues/new) too!

0
2 changes: 1 addition & 1 deletion RetailCoder.VBE/API/Accessibility.cs
Expand Up @@ -10,6 +10,6 @@ public enum Accessibility
Public,
Global,
Friend,
Static,
Static
}
}
7 changes: 2 additions & 5 deletions RetailCoder.VBE/API/Declaration.cs
Expand Up @@ -26,15 +26,12 @@ public interface IDeclaration
}

[ComVisible(true)]
[Guid(ClassId)]
[ProgId(ProgId)]
[Guid(RubberduckGuid.DeclarationClassGuid)]
[ProgId(RubberduckProgId.DeclarationProgId)]
[ComDefaultInterface(typeof(IDeclaration))]
[EditorBrowsable(EditorBrowsableState.Always)]
public class Declaration : IDeclaration
{
private const string ClassId = "67940D0B-081A-45BE-B0B9-CAEAFE034BC0";
private const string ProgId = "Rubberduck.Declaration";

private readonly RubberduckDeclaration _declaration;

internal Declaration(RubberduckDeclaration declaration)
Expand Down
7 changes: 2 additions & 5 deletions RetailCoder.VBE/API/IdentifierReference.cs
Expand Up @@ -18,15 +18,12 @@ public interface IIdentifierReference
}

[ComVisible(true)]
[Guid(ClassId)]
[ProgId(ProgId)]
[Guid(RubberduckGuid.IdentifierReferenceClassGuid)]
[ProgId(RubberduckProgId.IdentifierReferenceProgId)]
[ComDefaultInterface(typeof(IIdentifierReference))]
[EditorBrowsable(EditorBrowsableState.Always)]
public class IdentifierReference : IIdentifierReference
{
private const string ClassId = "57F78E64-8ADF-4D81-A467-A0139B877D14";
private const string ProgId = "Rubberduck.IdentifierReference";

private readonly Parsing.Symbols.IdentifierReference _reference;

public IdentifierReference(Parsing.Symbols.IdentifierReference reference)
Expand Down
9 changes: 3 additions & 6 deletions RetailCoder.VBE/API/ParserState.cs
Expand Up @@ -26,7 +26,7 @@ public interface IParserState
}

[ComVisible(true)]
[Guid("3D8EAA28-8983-44D5-83AF-2EEC4C363079")]
[Guid(RubberduckGuid.IParserStateEventsGuid)]
[InterfaceType(ComInterfaceType.InterfaceIsIDispatch)]
public interface IParserStateEvents
{
Expand All @@ -36,17 +36,14 @@ public interface IParserStateEvents
}

[ComVisible(true)]
[Guid(ClassId)]
[ProgId(ProgId)]
[Guid(RubberduckGuid.ParserStateClassGuid)]
[ProgId(RubberduckProgId.ParserStateProgId)]
[ClassInterface(ClassInterfaceType.AutoDual)]
[ComDefaultInterface(typeof(IParserState))]
[ComSourceInterfaces(typeof(IParserStateEvents))]
[EditorBrowsable(EditorBrowsableState.Always)]
public sealed class ParserState : IParserState, IDisposable
{
private const string ClassId = "28754D11-10CC-45FD-9F6A-525A65412B7A";
private const string ProgId = "Rubberduck.ParserState";

private RubberduckParserState _state;
private AttributeParser _attributeParser;
private ParseCoordinator _parser;
Expand Down
Binary file added RetailCoder.VBE/EasyHook32.dll
Binary file not shown.
Binary file added RetailCoder.VBE/EasyHook32Svc.exe
Binary file not shown.
Binary file added RetailCoder.VBE/EasyHook64.dll
Binary file not shown.
Binary file added RetailCoder.VBE/EasyHook64Svc.exe
Binary file not shown.
Binary file added RetailCoder.VBE/EasyLoad32.dll
Binary file not shown.
Binary file added RetailCoder.VBE/EasyLoad64.dll
Binary file not shown.
7 changes: 2 additions & 5 deletions RetailCoder.VBE/Extension.cs
Expand Up @@ -29,15 +29,12 @@ namespace Rubberduck
/// Special thanks to Carlos Quintero (MZ-Tools) for providing the general structure here.
/// </remarks>
[ComVisible(true)]
[Guid(ClassId)]
[ProgId(ProgId)]
[Guid(RubberduckGuid.ExtensionGuid)]
[ProgId(RubberduckProgId.ExtensionProgId)]
[EditorBrowsable(EditorBrowsableState.Never)]
// ReSharper disable once InconsistentNaming // note: underscore prefix hides class from COM API
public class _Extension : IDTExtensibility2
{
private const string ClassId = "8D052AD8-BBD2-4C59-8DEC-F697CA1F8A66";
private const string ProgId = "Rubberduck.Extension";

private IVBE _ide;
private IAddIn _addin;
private bool _isInitialized;
Expand Down
Expand Up @@ -14,18 +14,19 @@ namespace Rubberduck.Inspections
public sealed class ObsoleteCommentSyntaxInspection : InspectionBase, IParseTreeInspection
{
private IEnumerable<QualifiedContext> _parseTreeResults;
public IEnumerable<QualifiedContext<VBAParser.RemCommentContext>> ParseTreeResults { get { return _parseTreeResults.OfType<QualifiedContext<VBAParser.RemCommentContext>>(); } }

public ObsoleteCommentSyntaxInspection(RubberduckParserState state) : base(state, CodeInspectionSeverity.Suggestion) { }

public override CodeInspectionType InspectionType { get { return CodeInspectionType.LanguageOpportunities; } }

public override IEnumerable<IInspectionResult> GetInspectionResults()
{
if (_parseTreeResults == null)
if (ParseTreeResults == null)
{
return Enumerable.Empty<IInspectionResult>();
}
return _parseTreeResults.Where(context => !IsIgnoringInspectionResultFor(context.ModuleName.Component, context.Context.Start.Line))
return ParseTreeResults.Where(context => !IsIgnoringInspectionResultFor(context.ModuleName.Component, context.Context.Start.Line))
.Select(context => new ObsoleteCommentSyntaxInspectionResult(this, new QualifiedContext<ParserRuleContext>(context.ModuleName, context.Context)));
}

Expand Down
Expand Up @@ -105,13 +105,15 @@ private void ImplementMissingMembers()
AddItems(nonImplementedMembers);
}

private void AddItems(List<Declaration> members)
private void AddItems(List<Declaration> missingMembers)
{
var module = _targetClass.QualifiedSelection.QualifiedName.Component.CodeModule;
{
var missingMembersText = members.Aggregate(string.Empty, (current, member) => current + Environment.NewLine + GetInterfaceMember(member));
module.InsertLines(module.CountOfDeclarationLines + 1, missingMembersText);
}
var missingMembersText = missingMembers.Aggregate(string.Empty,
(current, member) => current + Environment.NewLine + GetInterfaceMember(member));

var rewriter = _state.GetRewriter(_targetClass);
rewriter.InsertAfter(rewriter.TokenStream.Size, Environment.NewLine + missingMembersText);

rewriter.Rewrite();
}

private string GetInterfaceMember(Declaration member)
Expand Down

0 comments on commit d16f5db

Please sign in to comment.