Word VBA heading text cut short and function produces reversed results when called from Sub - vba

Sorry for the two fold question in one post.
This indirectly relates to a question I posted recently here: vba: return page number from selection.find using text from array which was solved
Program purpose:
Firstly: add a footer with custom page numbers to documents (i.e. 0.0.0, Chapter.Section,Page representative) in a selected folder and sub folders.
Secondly: create a TOC with the custom page numbers saved as roottoc.docx in the root folder selected.
I now have two new problems before I can fully clean and finally put this to bed, I will post the full code at the end of this post.
Solved First of all, from what I have discovered and just read elsewhere too the getCrossReferenceItems(refTypeHeading) method will only return the text upto a certain length from what of finds. I have some pretty long headings which means this is quite an annoyance for the purpose of my code. So the first question I have is is there something I can do with the getCrossReferenceItems(refTypeHeading) method to force it to collect the full text from any referenced headings or is there an alternative way round this problem.
Solved Secondly the createOutline() function when called in ChooseFolder() produces the correct results but in reverse order, could someone point the way on this one too please.
Unfortunately the actual results I am recieving will be difficulty to exactly replicate but if a folder is made containing a couple of documents with various headings. The directory name should be the the same as what is in the Unit Array i.e. Unit(1) "Unit 1", the file names are made up of two parts i.e. Unit(1) & " " & Criteria(1) & ext becoming "Unit 1 p1.docx" etc, the arrays Unit and Criteria are in the ChooseFolder Sub. chapArr is a numerical representative of the Unit array contents soley for my page numbering system, I used another array because of laziness at this point in time. I could have used some other method on the Unit array to achieve the same result which I might look at when cleaning up.
When running the ChooseFolder Sub if the new folder with documents in is located in My Document then My Documents will be the folder to locate and select in the file dialogue window. This should produce results that are similar and will give an example of what I am talking about.
Complete code:
Public Sub ChooseFolder()
'Declare Variables
'|Applications|
Dim doc As Word.Document
'|Strings|
Dim chapNum As String
Dim sResult As String
Dim Filepath As String
Dim strText As String
Dim StrChapSec As String
'|Integers|
Dim secNum As Integer
Dim AckTime As Integer
Dim FolderChosen As Integer
'|Arrays|
Dim Unit() As Variant
Dim ChapArray() As Variant
Dim Criteria() As Variant
'|Ranges|
Dim rng As Range
'|Objects|
Dim InfoBox As Object
'|Dialogs|
Dim fd As FileDialog
'Constants
Const ext = ".docx"
'Set Variable Values
secNum = 0 'Set Section number start value
AckTime = 1 'Set the message box to close after 1 seconds
Set InfoBox = CreateObject("WScript.Shell") 'Set shell object
Set fd = Application.FileDialog(msoFileDialogFolderPicker) 'Set file dialog object
FolderChosen = fd.Show 'Display file dialogue
'Set Array Values
'ToDo: create form to set values for Arrays
'Folder names
Unit = Array("Unit 1", "Unit 2")
'Chapter Numbers
chapArr = Array("1", "2")
'Document names
Criteria = Array("P1", "P2", "P3", "P4", "P5", "P6", "P7", "P8", "P9", "M1", "M2", "M3", "M4", "D1", "D2", "D3")
If FolderChosen <> -1 Then
'didn't choose anything (clicked on CANCEL)
MsgBox "You chose cancel"
Else
'Set sResult equal to selected file/folder in file dialogue
sResult = fd.SelectedItems(1)
End If
' Loop through unit array items
For i = LBound(Unit) To UBound(Unit)
unitName = Unit(i)
' Test unit folder being looked at and concatenate sResult with
' unitName delimited with "\"
If unitName = "Unit 105" Then
Filepath = sResult & "\unit 9"
Else
Filepath = sResult & "\" & unitName
End If
' Loop through criteria array items
For j = LBound(Criteria) To UBound(Criteria)
criteriaName = Criteria(j)
' Set thisFile equal to full file path
thisfile = Filepath & "\" & unitName & " " & criteriaName & ext 'Create file name by concatenating filePath with "space" criteriaName and ext
' Test if file exists
If File_Exists(thisfile) = True Then
' If file exists do something (i.e. process number of pages/modify document start page number)
' Inform user of file being processed and close popup after 3 seconds
Select Case InfoBox.Popup("Processing file - " & thisfile, AckTime, "This is your Message Box", 0)
Case 1, -1
End Select
' Open document in word using generated filePath in read/write mode
' Process first section footer page number and amend to start as intPages (total pages) + 1
Set doc = Documents.Open(thisfile)
With doc
With ActiveDocument.Sections(1)
chapNum = chapArr(i)
secNum = secNum + 1
' Retrieve current footer text
strText = .Footers(wdHeaderFooterPrimary).Range.Text
.PageSetup.DifferentFirstPageHeaderFooter = False
' Set first page footer text to original text
.Footers(wdHeaderFooterFirstPage).Range.Text = strText
' Set other pages footer text
.Footers(wdHeaderFooterPrimary).Range.Text = Date & vbTab & "Author: Robert Ells" & vbTab & chapNum & "." & secNum & "."
Set rng = .Footers(wdHeaderFooterPrimary).Range.Duplicate
rng.Collapse wdCollapseEnd
rng.InsertBefore "{PAGE}"
TextToFields rng
End With
ActiveDocument.Sections(1).Footers(1).PageNumbers.StartingNumber = 1
Selection.Fields.Update
Hide_Field_Codes
ActiveDocument.Save
CreateOutline sResult, chapNum & "." & secNum & "."
End With
Else
'If file doesn't exist do something else (inform of non existant document and close popup after 3 seconds
Select Case InfoBox.Popup("File: " & thisfile & " - Does not exist", AckTime, "This is your Message Box", 0)
Case 1, -1
End Select
End If
Next
Filepath = ""
secNum = 0
Next
End Sub
Private Function TextToFields(rng1 As Range)
Dim c As Range
Dim fld As Field
Dim f As Integer
Dim rng2 As Range
Dim lFldStarts() As Long
Set rng2 = rng1.Duplicate
rng1.Document.ActiveWindow.View.ShowFieldCodes = True
For Each c In rng1.Characters
DoEvents
Select Case c.Text
Case "{"
ReDim Preserve lFldStarts(f)
lFldStarts(f) = c.Start
f = f + 1
Case "}"
f = f - 1
If f = 0 Then
rng2.Start = lFldStarts(f)
rng2.End = c.End
rng2.Characters.Last.Delete '{
rng2.Characters.First.Delete '}
Set fld = rng2.Fields.Add(rng2, , , False)
Set rng2 = fld.Code
TextToFields fld.Code
End If
Case Else
End Select
Next c
rng2.Expand wdStory
rng2.Fields.Update
rng1.Document.ActiveWindow.View.ShowFieldCodes = True
End Function
Private Function CreateOutline(Filepath, pgNum)
' from https://stackoverflow.com/questions/274814/getting-the-headings-from-a-word-document
'Declare Variables
'|Applications|
Dim App As Word.Application
Dim docSource As Word.Document
Dim docOutLine As Word.Document
'|Strings|
Dim strText As String
Dim strFileName As String
'|Integers|
Dim intLevel As Integer
Dim intItem As Integer
Dim minLevel As Integer
'|Arrays|
Dim strFootNum() As Integer
'|Ranges|
Dim rng As Word.Range
'|Variants|
Dim astrHeadings As Variant
Dim tabStops As Variant
'Set Variable values
Set docSource = ActiveDocument
If Not FileLocked(Filepath & "\" & "roottoc.docx") Then
If File_Exists(Filepath & "\" & "roottoc.docx") Then
Set docOutLine = Documents.Open(Filepath & "\" & "roottoc.docx", ReadOnly:=False)
Else
Set docOutLine = Document.Add
End If
End If
' Content returns only the
' main body of the document, not
' the headers and footer.
Set rng = docOutLine.Content
minLevel = 5 'levels above this value won't be copied.
astrHeadings = returnHeaderText(docSource) 'docSource.GetCrossReferenceItems(wdRefTypeHeading)
docSource.Select
ReDim strFootNum(0 To UBound(astrHeadings))
For i = 1 To UBound(astrHeadings)
With Selection.Find
.Text = Trim(astrHeadings(i))
.Wrap = wdFindContinue
End With
If Selection.Find.Execute = True Then
strFootNum(i) = Selection.Information(wdActiveEndPageNumber)
Else
MsgBox "No selection found", vbOKOnly 'Or whatever you want to do if it's not found'
End If
Selection.Move
Next
docOutLine.Select
With Selection.Paragraphs.tabStops
'.Add Position:=InchesToPoints(2), Alignment:=wdAlignTabLeft
.Add Position:=InchesToPoints(6), Alignment:=wdAlignTabRight, Leader:=wdTabLeaderDots
End With
For intItem = LBound(astrHeadings) To UBound(astrHeadings)
' Get the text and the level.
' strText = Trim$(astrHeadings(intItem))
intLevel = GetLevel(CStr(astrHeadings(intItem)))
' Test which heading is selected and indent accordingly
If intLevel <= minLevel Then
If intLevel = "1" Then
strText = " " & Trim$(astrHeadings(intItem)) & vbTab & pgNum & strFootNum(intItem) & vbCr
End If
If intLevel = "2" Then
strText = " " & Trim$(astrHeadings(intItem)) & vbTab & pgNum & strFootNum(intItem) & vbCr
End If
If intLevel = "3" Then
strText = " " & Trim$(astrHeadings(intItem)) & vbTab & pgNum & strFootNum(intItem) & vbCr
End If
If intLevel = "4" Then
strText = " " & Trim$(astrHeadings(intItem)) & vbTab & pgNum & strFootNum(intItem) & vbCr
End If
If intLevel = "5" Then
strText = " " & Trim$(astrHeadings(intItem)) & vbTab & pgNum & strFootNum(intItem) & vbCr
End If
' Add the text to the document.
rng.Collapse (False)
rng.InsertAfter strText & vbLf
docOutLine.SelectAllEditableRanges
' tab stop to set at 15.24 cm
'With Selection.Paragraphs.tabStops
' .Add Position:=InchesToPoints(6), _
' Leader:=wdTabLeaderDots, Alignment:=wdAlignTabRight
' .Add Position:=InchesToPoints(2), Alignment:=wdAlignTabCenter
'End With
rng.Collapse (False)
End If
Next intItem
docSource.Close
docOutLine.Save
docOutLine.Close
End Function
Function returnHeaderText(doc As Word.Document) As Variant
Dim returnArray() As Variant
Dim para As Word.Paragraph
Dim i As Integer
i = 0
For Each para In doc.Paragraphs
If Left(para.Style, 7) = "Heading" Then
ReDim Preserve returnArray(i)
returnArray(i) = para.Range.Text
i = i + 1
End If
Next
returnHeaderText = returnArray
End Function
Function FileLocked(strFileName As String) As Boolean
On Error Resume Next
' If the file is already opened by another process,
' and the specified type of access is not allowed,
' the Open operation fails and an error occurs.
Open strFileName For Binary Access Read Write Lock Read Write As #1
Close #1
' If an error occurs, the document is currently open.
If Err.Number <> 0 Then
' Display the error number and description.
MsgBox "Error #" & Str(Err.Number) & " - " & Err.Description
FileLocked = True
Err.Clear
End If
End Function
Private Function GetLevel(strItem As String) As Integer
' from https://stackoverflow.com/questions/274814/getting-the-headings-from-a-word-document
' Return the heading level of a header from the
' array returned by Word.
' The number of leading spaces indicates the
' outline level (2 spaces per level: H1 has
' 0 spaces, H2 has 2 spaces, H3 has 4 spaces.
Dim strTemp As String
Dim strOriginal As String
Dim intDiff As Integer
' Get rid of all trailing spaces.
strOriginal = RTrim$(strItem)
' Trim leading spaces, and then compare with
' the original.
strTemp = LTrim$(strOriginal)
' Subtract to find the number of
' leading spaces in the original string.
intDiff = Len(strOriginal) - Len(strTemp)
GetLevel = (intDiff / 2) + 1
End Function
Private Function File_Exists(ByVal sPathName As String, Optional Directory As Boolean) As Boolean
'Returns True if the passed sPathName exist
'Otherwise returns False
On Error Resume Next
If sPathName <> "" Then
If IsMissing(Directory) Or Directory = False Then
File_Exists = (Dir$(sPathName) <> "")
Else
File_Exists = (Dir$(sPathName, vbDirectory) <> "")
End If
End If
End Function
Sub Hide_Field_Codes()
Application.ActiveWindow.View.ShowFieldCodes = False
End Sub
Kevin's Solutions:
Question part 1, Answer
I thought initially that something went wrong when I added your function, but it was due to a blank heading on the following line after the actual heading in the documents. I suppose an If statement to test if there is text present could solve this. :-)
I haven't tested this bit yet (due to being tired), but if the heading is inline with normal text, would this function pick up only the heading or both heading and normal text?
Question part 2, Answer
Just worked, although with one niggle (the list produced is no longer indented as desired in the main CreateOutline function). Time is getting on now so will have to pick this up again tomorrow :-)
Thanks yet again kevin, this is where I should have concentrated more during programming at uni instead of thinking about the pub.
Phil :-)

welcome back! :-)
For the reversed data from the CreateOutline function - change your Collapse function to have a false parameter. Collapse defaults to putting the cursor at the beginning of the selection, but this will put it at the end so you're adding to the end of the doc instead of the beginning:
' Add the text to the document.
rng.Collapse(False) 'HERE'
rng.InsertAfter strText & vbLf
docOutLine.SelectAllEditableRanges
rng.Collapse(False) 'AND HERE'
For the CrossReferenceItems issue, try this and let me know if there's any data missing from what it returns. Call this instead of the CrossReferenceItems method:
Function returnHeaderText(doc As Word.Document) As Variant
Dim returnArray() As Variant
Dim para As Word.Paragraph
Dim i As Integer
i = 0
For Each para In doc.Paragraphs
If Left(para.Style, 7) = "Heading" Then
ReDim Preserve returnArray(i)
returnArray(i) = para.Range.Text
i = i + 1
End If
Next
returnHeaderText = returnArray
End Function

Related

Replace square brackets + contents with the contents as a mergefield

I am trying to change the contents of square brackets into a merge field. I've got 80-ish documents to go through some with none square brackets and some with a few (none nested).
I have managed to run my code and it has worked for some files. Others (majority) have given an overflow error. When I examined what was happening in one of the files, the code picks up the contents correctly, it just puts the merge field in the wrong place which in turn causes it to keep finding the same set of square brackets.
Public Function searchFiles(fFile As Variant, rootFolderStr2 As String, rootFolderStr As String)
Dim strTemp As String, mfc As String, msg As String
Dim startStr As Integer, endStr As Integer
Dim objWord As New Word.Application
Dim objDoc As Word.Document
Dim aField As Field, fFolder As String
Dim rng As Variant, myField As Field, oldField As Variant
On Error GoTo ErrorHandler
'open file
'Open fFile For Input As #1
Set objDoc = objWord.Documents.Open(fFile)
objDoc.TrackRevisions = False
strTemp = objDoc.Range(0, objDoc.Range.End)
startStr = InStrRev(strTemp, "[")
endStr = InStrRev(strTemp, "]")
Do While startStr <> 0
'Merge field contents
mfc = Right(Left(strTemp, endStr - 1), endStr - startStr - 1)
Set rng = objDoc.Range(startStr - 1, endStr)
Set myField = objDoc.Fields.Add(Range:=rng, Type:=wdFieldMergeField, Text:=mfc)
strTemp = objDoc.Range(0, objDoc.Range.End)
'Find next merge field
startStr = InStrRev(strTemp, "[")
endStr = InStrRev(strTemp, "]")
If endStr < startStr And endStr <> -1 Then
msg = "Error occured in " & fileName & " " & startStr & " " & endStr
Debug.Print (msg)
startStr = 0
endStr = 0
End If
Loop
'put in right folder
fFolder = Right(objDoc.FullName, Len(objDoc.FullName) - Len(rootFolderStr))
objDoc.SaveAs fileName:=rootFolderStr2 & "\" & fFolder
objDoc.Close
objWord.Quit
ErrorHandler:
If Err.Number <> 0 Then
Debug.Print ("Error occured in file: " & fileName & " " & Err.Description)
Exit Function
End If
End Function
I'm struggling to understand how the objects in word work so forgive, please.
Any answers as to what's causing this problem would be appreciated or any help with methods to do this in a better manner.
Try:
Sub UpdateDocuments()
Application.ScreenUpdating = False
Dim strFolder As String, strFile As String, strDocNm As String, wdDoc As Document
strDocNm = ActiveDocument.FullName
strFolder = GetFolder
If strFolder = "" Then Exit Sub
strFile = Dir(strFolder & "\*.doc", vbNormal)
While strFile <> ""
If strFolder & "\" & strFile <> strDocNm Then
Set wdDoc = Documents.Open(FileName:=strFolder & "\" & strFile, AddToRecentFiles:=False, Visible:=False)
Call MakeFields(wdDoc)
wdDoc.Close SaveChanges:=True
End If
strFile = Dir()
Wend
Set wdDoc = Nothing
Application.ScreenUpdating = True
End Sub
Function GetFolder() As String
Dim oFolder As Object
GetFolder = ""
Set oFolder = CreateObject("Shell.Application").BrowseForFolder(0, "Choose a folder", 0)
If (Not oFolder Is Nothing) Then GetFolder = oFolder.Items.Item.Path
Set oFolder = Nothing
End Function
Sub MakeFields(wdDoc As Document)
With wdDoc.Range
With .Find
.ClearFormatting
.Replacement.ClearFormatting
.Forward = True
.Format = False
.Wrap = wdFindStop
.MatchWildcards = True
.Text = "\[*\]"
.Execute
End With
Do While .Find.Found
.Characters.First.Text = vbNullString
.Characters.Last.Text = vbNullString
.Fields.Add Range:=.Duplicate, Type:=wdFieldEmpty, Text:="MERGEFIELD " & .Text, Preserveformatting:=False
.Collapse wdCollapseEnd
.Find.Execute
Loop
End With
End Sub
The above code processes all documents in the selected folder.
OK. The generic advice is to always, always, always put option explicit as the start of your module or class. This helps highlights errors in your code related misuse of syntax and undeclared variables etc. In your posted code there is one undeclared variable 'Filename'.
When working with Word it is always better to try to find a way of working with the word object model rather than extracting text.
You can modify your existing code by replacing the instrrev with the .MoveStart/EndUntil methods.
I've updated your code to use these move methods.
If you don't understand what a keyword does then place your cursor on it and press F1. This will take you to the MS help page. For the Word object model the help pages need careful reading.
Option Explicit
' Changed to sub as you are not returning any values
Public Sub searchFiles(fFile As Variant, rootFolderStr2 As String, rootFolderStr As String)
Const FieldOpen As String = "["
Const FieldClose As String = "]"
Dim strTemp As String, mfc As String, msg As String
Dim objWord As New Word.Application
Dim objDoc As Word.Document
' Dim aField As FieldDim
Dim fFolder As String
' Dim rng As Variant
' Dim myField As Field
' Dim oldField As Variant
' Not previously declared
Dim Filename As String
Dim SearchRng As Word.Range
Dim FieldRng As Word.Range
Dim Moved As Long
'open file
'Open fFile For Input As #1
On Error GoTo ErrorHandler
Set objDoc = objWord.Documents.Open(fFile)
objDoc.TrackRevisions = False
'strTemp = objDoc.Range(0, objDoc.Range.End)
Set SearchRng = ActiveDocument.Content
'startStr = InStrRev(strTemp, "[")
Moved = SearchRng.MoveStartUntil(cset:=FieldOpen)
'Do While startStr <> 0
Do Until Moved = 0
'Merge field contents
'mfc = Right(Left(strTemp, endStr - 1), endStr - startStr - 1)
FieldRng.Start = SearchRng.Start + 1
'endStr = InStrRev(strTemp, "]")
' exit if we don't find a closing field marker
' The side effect (which we want) is that the end is also moved
If SearchRng.MoveEndUntil(cset:=FieldClose) = 0 Then GoTo ErrorHandler
FieldRng.End = SearchRng.End + 1
' reduce the FieldRng to just the text
FieldRng.Characters.First.Delete
FieldRng.Characters.Last.Delete
'Set rng = objDoc.Range(startStr - 1, endStr
'Set myField = objDoc.Fields.Add(Range:=rng, Type:=wdFieldMergeField, Text:=mfc)
objDoc.Fields.Add Range:=FieldRng, Type:=wdFieldMergeField, Text:=FieldRng.Text
'strTemp = objDoc.Range(0, objDoc.Range.End)
' We now need to move the start of the search range to after the mergefield
SearchRng.Start = FieldRng.End + 1
'Find next merge field
'startStr = InStrRev(strTemp, "[")
'endStr = InStrRev(strTemp, "]")
Moved = SearchRng.MoveStartUntil(cset:=FieldOpen)
' If endStr < startStr And endStr <> -1 Then
' msg = "Error occured in " & Filename & " " & startStr & " " & endStr
' Debug.Print (msg)
' startStr = 0
' endStr = 0
' End If
Loop
'put in right folder
fFolder = Right(objDoc.FullName, Len(objDoc.FullName) - Len(rootFolderStr))
objDoc.SaveAs Filename:=rootFolderStr2 & "\" & fFolder
objDoc.Close
objWord.Quit
ErrorHandler:
If Err.Number <> 0 Then
Debug.Print ("Error occured in file: " & Filename & " " & Err.Description)
Exit Sub
End If
End Sub
The code above compiles without error but I haven't testing the logic. I'll leave that as 'an exercise for the reader'

Passing values from Excel to Word with VBA

For Each cell In rng
workSheetName = Format(SaturdayIsComing(), "mm-dd-yyyy") & " " & cell.Value
If WorksheetExists(workSheetName) Then
Dim localRange, localCell As Range
Set localRange = Worksheets(workSheetName).Range("D8:D19")
Dim contents As Variant
contents = ""
Dim firstLine As Boolean
firstLine = True
For Each localCell In localRange
If Len(localCell.Value) > 0 Then
If firstLine Then
contents = contents & localCell.Value & Chr(11)
Else
contents = contents & Chr(9) & Chr(9) & Chr(9) & localCell.Value & Chr(11)
End If
Else
contents = fixString(contents)
End If
If Len(contents) > 0 Then
firstLine = False
End If
Next localCell
For Each cc In wDoc.SelectContentControlsByTag(cell.Value & "Notes")
If Len(contents) > 0 Then
cc.Range.Text = fixString(contents)
Else
cc.Range.Text = "No Issues Found"
End If
Next
Else
errorCodesString = errorCodesString & cell.Value & ":"
End If
Next cell
Output to Word
Forgot to terminate the meeting
This is a test message\'s
If my cell contains a ' then I get an error saying
One of the values passwed to this method or property is incorrect
I know a ' is a comment in VBA. How do I go around this while preserving the notes that someone had added to the Excel cell?
You need to write a piece of code to search for quotes, either the single (') or double (") variety and either add a backslash before them OR double the character so '' in place of ' and "" in place of " and run this on contents before assigning it to cc.Range.Text.
This routine can also check for other instances of incorrect strings and fix them.
Something like this would do:
Function fixString(ByVal strIn As Variant) As String
Dim i As Integer
Const strIllegals = "\'"""
For i = 1 To Len(strIllegals)
strIn = Replace(strIn, Mid$(strIllegals, i, 1), "\" & Mid$(strIllegals, i, 1))
Next i
fixString = strIn
End Function
Try changing cell.Value to Replace(cell.Value, "'", "")
Or is it contents that has the apostrophe in it? A bit confusing.
Try changing contents to Replace(contents , "'", "")

Regex for VBA Excel macro for new folder chars

I have a function which is Boolean, and returns whether is the cell OK for creating a New Folder based on its value or its not (if it posses following chars:<,>,|,\,*,?)
But from some weird reason, it returns always false, either is a cell OK or not.
So, I have a sub which creates a loop for all rows and creates some .txt files and puts it in auto-generated folders.
Here is my code:
Sub CreateTxtSrb()
Dim iRow As Long
Dim iFile As Integer
Dim sPath As String
Dim sFile As String
Dim iEnd As Range
'iEnd = Cells(Rows.Count, "B").End(xlUp).Row
For iRow = 1 To Cells(Rows.Count, "B").End(xlUp).Row
iFile = FreeFile
With Rows(iRow)
If IsValidFolderName(.Range("B2").Value) = False Or IsValidFolderName(.Range("D2").Value) = False Or IsValidFolderName(.Range("F2").Value) = False Then
MsgBox ("Check columns B,D or F, it cannot contains chars: <,>,?,|,\,/,*,. or a space at the end")
Exit Sub
Else
strShort = IIf(InStr(.Range("E2").Value, vbCrLf), Left(.Range("E2").Value, InStr(.Range("E2").Value, vbCrLf) - 2), .Range("E2").Value)
sPath = "E:\" & .Range("B2").Value & "\"
If Len(Dir(sPath, vbDirectory)) = 0 Then MkDir sPath
sFile = .Range("D2").Value & ".txt"
Open sPath & sFile For Output As #iFile
Print #iFile, .Range("E2").Value
Close #iFile
End If
End With
Next iRow
End Sub
Function IsValidFolderName(ByVal sFolderName As String) As Boolean
'http://msdn.microsoft.com/en- us/library/windows/desktop/aa365247(v=vs.85).aspx#file_and_directory_names
'http://msdn.microsoft.com/en-us/library/ie/ms974570.aspx
On Error GoTo Error_Handler
Dim oRegEx As Object
'Check to see if any illegal characters have been used
Set oRegEx = CreateObject("vbscript.regexp")
oRegEx.Pattern = "[<>:""/\\\|\?\*]"
IsValidFolderName = Not oRegEx.test(sFolderName)
'Ensure the folder name does end with a . or a blank space
If Right(sFolderName, 1) = "." Then IsValidFolderName = False
If Right(sFolderName, 1) = " " Then IsValidFolderName = False
Error_Handler_Exit:
On Error Resume Next
Set oRegEx = Nothing
Exit Function
Error_Handler:
MsgBox ("test")
' MsgBox "The following error has occurred" & vbCrLf & vbCrLf & _
' "Error Number: " & Err.Number & vbCrLf & vbCrLf & _
' "Error Source: IsInvalidFolderName" & vbCrLf & _
' "Error Description: " & Err.Description, _
' vbCritical, "An Error has Occurred!"
Resume Error_Handler_Exit
End Function
How can I make it return true if need be?
You don't need the external reference you can simply:
hasInvalidChars = sFolderName like "*[<>|\/:*?""]*"
I added " and : which are also illegal.
(In your example you have HTML entities (E.g. <) - these have no meaning in your RegEx string and are interpreted as 4 characters in the class)
That's a mess. Use a separate function
Public Function IsInvalid(ByVal name As String) As Boolean
Dim regex As Object
Set regex = VBA.CreateObject("VBScript.RegExp")
regex.Pattern = "[\\/:\*\?""<>\|]" 'the disallowed characters
IsInvalid = (regex.Execute(name).Count > 0)
End Function
instead, and call it when appropriate.

Word macro to split document is creating an extra page

I created a macro which, based on user input, splits the Word document into smaller documents and then outputs them as a .pdf with a unique name. Each individual document though is outputting with an extra blank page on the back, which at no point is in the original document. Is there any way to stop this happening/remove the back page before saving to .pdf? I tried removing the final page by section break but that also didn't work.
Sub SplitToPDF()
Dim docMultiple As Document
Dim docSingle As Document
Dim rngPage As Range
Dim iCurrentPage As Integer
Dim iPageCount As Integer
Dim strNewFileName As String
Dim fDialog As FileDialog
Dim x As Integer
Dim Response As VbMsgBoxResult
Dim userInput As Integer
Dim fso
Dim currentDate As String
Dim customerName As String
Dim currentMonth As String
Dim currentYear As Integer
Response = MsgBox("Insturctions for use:" & vbNewLine & "Please ensure the first blank page has been deleted." & vbNewLine & "Please ensure you have saved (and re-named) this document to the fund operation name." & vbNewLine & vbNewLine & "This will also overwrite any other split you have done in the same folder. Continue?", vbExclamation + vbYesNo, "Warning!")
If Response = vbNo Then Exit Sub
inputData = InputBox("Please enter the length of each letter below.", "Notice length:")
If inputData = "" Then Exit Sub
' 1 Create dialog for saving and get directory details
Set fDialog = Application.FileDialog(msoFileDialogFolderPicker)
With fDialog
.Title = "Select folder to save split files"
.AllowMultiSelect = False
.InitialView = msoFileDialogViewList
If .Show <> -1 Then
MsgBox "Cancelled By User", vbInformation
Exit Sub
End If
DocDir = fDialog.SelectedItems.Item(1)
End With
Application.ScreenUpdating = False
Set docMultiple = ActiveDocument
Set rngPage = docMultiple.Range
iCurrentPage = 1
iPageCount = docMultiple.BuiltInDocumentProperties(wdPropertyPages)
' 2 Loop through each page set and copy/paste data
Do Until iCurrentPage > iPageCount
If iCurrentPage = iPageCount Then
rngPage.End = ActiveDocument.Range.End
Else
Selection.GoTo wdGoToPage, wdGoToAbsolute, iCurrentPage + inputData
rngPage.End = Selection.Start
End If
rngPage.Copy
Set docSingle = Documents.Add
docSingle.Range.Paste
For i = 0 To docSingle.Sections.Count
Next
Set delSec = docSingle.Sections(i)
delSec.Range.Delete
' 3 Variable for document name
Application.Selection.Find.Execute "customer: "
Application.Selection.Expand wdLine
customerName = Replace(Application.Selection.Text, "customer: ", "")
x = Len(customerName) - 1
customerName = Left(customerName, x)
Set fso = CreateObject("Scripting.FileSystemObject")
currentDate = Replace(Date, "/", "-")
currentMonth = Format(currentDate, "MMM")
currentYear = Format(currentDate, "YY")
currentDate = currentMonth & "_" & currentYear
strNewFileName = fso.GetBaseName(docMultiple) & "_" & currentDate & "_" & customerName & ".pdf"
docSingle.SaveAs FileName:=DocDir & "\" & strNewFileName, FileFormat:=wdFormatPDF
iCurrentPage = iCurrentPage + inputData
docSingle.Close SaveChanges:=wdDoNotSaveChanges
rngPage.Collapse wdCollapseEnd
Loop
Application.ScreenUpdating = True
MsgBox "Complete", vbInformation
Set docMultiple = Nothing
Set docSingle = Nothing
Set rngPage = Nothing
End Sub
In Step 2 (Looping through the page sets), just after you do the paste (line 57) add the following:
' There is now an empty page at the end of the document.
' This is caused by a section break. Get rid of it.
Selection.MoveLeft
Selection.Delete
Remove the extra code looping through the sections.

Extract Headings and Pagenumber of Table of Contents of a Word Document with VBA

Basically what we have here
Getting the headings from a Word document
Public Sub CreateOutline()
Dim docOutline As Word.Document
Dim docSource As Word.Document
Dim rng As Word.Range
Dim astrHeadings As Variant
Dim strText As String
Dim intLevel As Integer
Dim intItem As Integer
Set docSource = ActiveDocument
Set docOutline = Documents.Add
' Content returns only the
' main body of the document, not
' the headers and footer.
Set rng = docOutline.Content
astrHeadings = _
docSource.GetCrossReferenceItems(wdRefTypeHeading)
For intItem = LBound(astrHeadings) To UBound(astrHeadings)
' Get the text and the level.
strText = Trim$(astrHeadings(intItem))
intLevel = GetLevel(CStr(astrHeadings(intItem)))
' Add the text to the document.
rng.InsertAfter strText & vbNewLine
' Set the style of the selected range and
' then collapse the range for the next entry.
rng.Style = "Heading " & intLevel
rng.Collapse wdCollapseEnd
Next intItem
End Sub
Private Function GetLevel(strItem As String) As Integer
' Return the heading level of a header from the
' array returned by Word.
' The number of leading spaces indicates the
' outline level (2 spaces per level: H1 has
' 0 spaces, H2 has 2 spaces, H3 has 4 spaces.
Dim strTemp As String
Dim strOriginal As String
Dim intDiff As Integer
' Get rid of all trailing spaces.
strOriginal = RTrim$(strItem)
' Trim leading spaces, and then compare with
' the original.
strTemp = LTrim$(strOriginal)
' Subtract to find the number of
' leading spaces in the original string.
intDiff = Len(strOriginal) - Len(strTemp)
GetLevel = (intDiff / 2) + 1
End Function
but I need the page number for each heading too.
I tried doing a search for each heading, select the search result and retrieve the wdActiveEndPageNumber.
This didn't work, was slow and is sure an ugly approach.
I'd like to paste the found stuff into another word document like:
rng.InsertAfter "Page: " & pageNum & " Header: " & strText & vbNewLine
I may not understand the question, then, but this code goes through the document, looking for lines that are only headers and gets the page its on.
Public Sub SeeHeadingPageNumber()
On Error GoTo MyErrorHandler
Dim sourceDocument As Document
Set sourceDocument = ActiveDocument
Dim myPara As Paragraph
For Each myPara In sourceDocument.Paragraphs
myPara.Range.Select 'For debug only
If InStr(LCase$(myPara.Range.Style.NameLocal), LCase$("heading")) > 0 Then
Debug.Print myPara.Range.Information(wdActiveEndAdjustedPageNumber)
End If
DoEvents
Next
Exit Sub
MyErrorHandler:
MsgBox "SeeHeadingPageNumber" & vbCrLf & vbCrLf & "Err = " & Err.Number & vbCrLf & "Description: " & Err.Description
End Sub
Try using a Table of Content field. The following code dissects a TOC and gives you the item, page number and style. You might have to parse each string to get the exact info or formatting you need.
Public Sub SeeTOCInfo()
On Error GoTo MyErrorHandler
Dim sourceDocument As Document
Set sourceDocument = ActiveDocument
Dim myField As Field
For Each myField In sourceDocument.TablesOfContents(1).Range.Fields
Debug.Print Replace(myField.Result.Text, Chr(13), "-") & " " & " Type: " & myField.Type
If Not myField.Result.Style Is Nothing Then
Debug.Print myField.Result.Style
End If
DoEvents
Next
Exit Sub
MyErrorHandler:
MsgBox "SeeTOCInfo" & vbCrLf & vbCrLf & "Err = " & Err.Number & vbCrLf & "Description: " & Err.Description
End Sub
This will insert the page number of the referenced Heading:
rng.InsertCrossReference ReferenceType:=wdRefTypeHeading, _
ReferenceKind:=wdPageNumber, ReferenceItem:=intItem
But only works if you're inserting in the same document. You could insert in the current document and then cut/paste out to a new document.