Skip to content

Commit

Permalink
Merge pull request #6014 from awb95/dev-4795-Indenter_Declare_PtrSafe
Browse files Browse the repository at this point in the history
Fix Indenter "Declare PtrSafe"
  • Loading branch information
retailcoder committed Aug 22, 2022
2 parents 5ff67f4 + fccbe4e commit b53f353
Show file tree
Hide file tree
Showing 3 changed files with 24 additions and 2 deletions.
2 changes: 1 addition & 1 deletion Rubberduck.SmartIndenter/AbsoluteCodeLine.cs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ public class AbsoluteCodeLine

private static readonly Regex PropertyStartRegex = new Regex(@"^(Public\s|Private\s|Friend\s)?(Static\s)?(Property\s(Let|Get|Set))\s", RegexOptions.IgnoreCase);

private static readonly Regex ProcedureStartIgnoreRegex = new Regex(@"^[LR]?Set\s|^Let\s|^(Public|Private)\sDeclare\s(Function|Sub)", RegexOptions.IgnoreCase);
private static readonly Regex ProcedureStartIgnoreRegex = new Regex(@"^[LR]?Set\s|^Let\s|^(Public\s|Private\s)?Declare\s(PtrSafe\s)?(Function|Sub)", RegexOptions.IgnoreCase);
private static readonly Regex ProcedureEndRegex = new Regex(@"^End\s(Sub|Function|Property)", RegexOptions.IgnoreCase);
private static readonly Regex TypeEnumStartRegex = new Regex(@"^(Public\s|Private\s)?(Enum\s|Type\s)", RegexOptions.IgnoreCase);
private static readonly Regex TypeEnumEndRegex = new Regex(@"^End\s(Enum|Type)", RegexOptions.IgnoreCase);
Expand Down
2 changes: 1 addition & 1 deletion Rubberduck.SmartIndenter/LogicalCodeLine.cs
Original file line number Diff line number Diff line change
Expand Up @@ -202,7 +202,7 @@ public override string ToString()
return _lines.Aggregate(string.Empty, (x, y) => x + y.ToString());
}

private static readonly Regex StartIgnoreRegex = new Regex(@"^(\d*\s)?\s*[LR]?Set\s|^(\d*\s)?\s*Let\s|^(\d*\s)?\s*(Public|Private)\sDeclare\s(Function|Sub)|^(\d*\s+)", RegexOptions.IgnoreCase);
private static readonly Regex StartIgnoreRegex = new Regex(@"^(\d*\s)?\s*[LR]?Set\s|^(\d*\s)?\s*Let\s|^(\d*\s)?\s*(Public\s|Private\s)?Declare\s(PtrSafe\s)?(Function|Sub)|^(\d*\s+)", RegexOptions.IgnoreCase);
private readonly Stack<AlignmentToken> _alignment = new Stack<AlignmentToken>();
private int _nestingDepth;

Expand Down
22 changes: 22 additions & 0 deletions RubberduckTests/SmartIndenter/LineContinuationTests.cs
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,28 @@ public void DeclarationLineAlignsCorrectly()
Assert.IsTrue(expected.SequenceEqual(actual));
}

// https://github.com/rubberduck-vba/Rubberduck/issues/4795
[Test]
[Category("Indenter")]
public void DeclarationPtrSafeLineAlignsCorrectly()
{
var code = new[]
{
@"Private Declare PtrSafe Function Foo Lib ""bar.dll"" _",
"(x As Long y As Long) As LongPtr"
};

var expected = new[]
{
@"Private Declare PtrSafe Function Foo Lib ""bar.dll"" _",
" (x As Long y As Long) As LongPtr"
};

var indenter = new Indenter(null, () => IndenterSettingsTests.GetMockIndenterSettings());
var actual = indenter.Indent(code);
Assert.IsTrue(expected.SequenceEqual(actual));
}

[Test]
[Category("Indenter")]
public void FunctionParametersAlignCorrectly()
Expand Down

0 comments on commit b53f353

Please sign in to comment.