Skip to content

Commit

Permalink
Added RegexGetGroupNamesExample.bas
Browse files Browse the repository at this point in the history
  • Loading branch information
MarkJohnstoneGitHub committed Sep 30, 2023
1 parent e033c68 commit ce48916
Show file tree
Hide file tree
Showing 2 changed files with 53 additions and 0 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,53 @@
Attribute VB_Name = "RegexGetGroupNamesExample"
'@Folder("Examples.System.Text.RegularExpressions.Regex.Methods")

'@Author Mark Johnstone
'@Project https://github.com/MarkJohnstoneGitHub/VBA-DotNetLib
'@Version v1.0 October 1, 2023
'@LastModified October 1, 2023

'@Reference https://learn.microsoft.com/en-us/dotnet/api/system.text.regularexpressions.regex.getgroupnames?view=netframework-4.8.1#examples

Option Explicit

''
' The following example defines a general-purpose ShowMatches method that
' displays the names of regular expression groups and their matched text.
''
Public Sub RegexGetGroupNames()
Dim pattern As String
pattern = "\b(?<FirstWord>\w+)\s?((\w+)\s)*(?<LastWord>\w+)?(?<Punctuation>\p{Po})"
Dim strInput As String
strInput = "The cow jumped over the moon."
Dim rgx As DotNetLib.Regex
Set rgx = Regex.Create(pattern)

Dim pvtMatch As DotNetLib.Match
Set pvtMatch = rgx.Match(strInput)
If (pvtMatch.Success) Then
ShowMatches rgx, pvtMatch
End If

End Sub

Private Sub ShowMatches(ByVal r As DotNetLib.Regex, ByVal m As DotNetLib.Match)
Dim names() As String
names = r.GetGroupNames()
Debug.Print "Named Groups:"

Dim name As Variant
For Each name In names
Dim grp As DotNetLib.Group
Set grp = m.Groups.Item_2(name)
Debug.Print Strings.Format(" {0}: '{1}'", name, grp.Value)
Next
End Sub

' The example displays the following output:
' Named Groups:
' 0: 'The cow jumped over the moon.'
' 1: 'the '
' 2: 'the'
' FirstWord: 'The'
' LastWord: 'moon'
' Punctuation: '.'
Binary file modified VBA/MS-Access/VBADotNetLibrary.accdb
Binary file not shown.

0 comments on commit ce48916

Please sign in to comment.