Avoiding GoTo Statements

G

Greg Maxey

I have read here and in the VBA Help File that GoTo statements shoud be
avoided.

I am playing with a macro that is represented by the following example:

Sub Test()
Dim A
Dim uDecide As VbMsgBoxResult

A = True 'Resprents something alreay done

If A = True Then
uDecide = MsgBox("Do you want to undo the something alredy done?",
vbYesNo)
If uDecide = 6 Then
MsgBox "Undo something action in progress"
Else: GoTo DSE
End If
ElseIf A = False Then
DSE:
MsgBox "Do something else in progress"
End If
End Sub

Question - Is there a better construction that avoids the GoTo statement?
 
J

Jezebel

Sometime in the late 60s it was *proved*, in a formal logical sense, that
any logical sequence can be coded without the use of goto. For cases like
your example, it's really just a matter of readability. You should be able
to look at the code and see, without too much thinking, what's going on. I'd
be inclined to use something like this:

If A then
uDecide = Msgbox (...)
If uDecide = 6 then
msgbox (...)
else
A = false
end if
end if

if not A then
...
end if


As a separate issue, these statements are not identical:

If A then

and

If A = True then

In VB/VBA, 'true' has two meanings. As a built-in constant it means "-1";
but as a logical value it means "not false" which means anything other than
0. Which gives rise to ambiguity in situations like

n = 123
If (n AND testBitMap) then .... which is OK, equivalent to: if (n
AND testBitMap) <> 0 then

but

If (n AND testBitMap) = TRUE then ... which is not OK
 
G

Greg Maxey

Jezebel,

Thanks. I might have given a bad example. It is not the purpose to Set A =
False. From your sample I think you are saying it is always better to have
two IF Statements rather than one IF statement, an ELSE and a GoTo. I
didn't want to clog the question with details, but here is the situation. A
macro highlights a bit of text, the macro can be run multiple times, it
stores the last bit of text in a variable.

Another macro (the one below) clears or unhighlights the bits of text. It
gives the user a choice to clear all highlighted text, the last bit of
highlighted text, or to specify bits to unhighlight (crazy I know, and I am
only doing it for a learning experience). All that said, here is the code I
cobbled (or hacked) together:

I am very well versed in VBA and I don't see a way to eliminate all of the
GoTo lines. Another push in the right dircetion is always welcomed.



Sub ClearHL()
Dim fWord As String
Dim bExists As Boolean
Dim oVar As Variable
Dim cLastItem As VbMsgBoxResult
Dim cMoreItems As VbMsgBoxResult
Dim cOtherItem As VbMsgBoxResult
Dim cOtherItemRepeat As VbMsgBoxResult
Dim cAllItems As VbMsgBoxResult
' OMR means Other, More, or Repeat

cAllItems = MsgBox("Do you want to remove highlighting throughout the
document?", _
vbYesNoCancel, "Restore All")
If cAllItems = 6 Then
Selection.Find.ClearFormatting
Selection.Find.Highlight = True
Selection.Find.Replacement.Highlight = False
With Selection.Find
.Text = "*"
.Replacement.Text = "^&"
.Forward = True
.Wrap = wdFindContinue
.MatchWildcards = True
End With
Selection.Find.Execute Replace:=wdReplaceAll
Exit Sub
End If

For Each oVar In ActiveDocument.Variables
If oVar.Name = "fWord" Then
bExists = True
Exit For
End If
Next oVar

If bExists Then
fWord = ActiveDocument.Variables("fWord").Value
ActiveDocument.Variables("fWord").Delete

cLastItem = MsgBox("Do you want to restore normal formatting to " &
Chr$(34) & fWord & Chr$(34) & " the last word highlighted?", _
vbYesNoCancel, "Restore Last")
If cLastItem = 6 Then
Selection.HomeKey wdStory
Selection.Find.ClearFormatting
With Selection.Find
Do While .Execute(FindText:=fWord, Wrap:=wdFindStop, _
MatchWholeWord:=True, Forward:=True) = True
Selection.Range.HighlightColorIndex = wdNoHighlight
Selection.Collapse wdCollapseEnd
Loop
End With
cMoreItems = MsgBox("Do you want to restore normal formatting to other
words or phrases?", _
vbYesNo, "Restore Other")
If cMoreItems = 7 Then
Exit Sub
Else: GoTo OMR
End If
Else
OMR:
fWord = InputBox$("Type in the word or phrase that you want restore normal
formatting.")
Selection.HomeKey wdStory
Selection.Find.ClearFormatting
With Selection.Find
Do While .Execute(FindText:=fWord, Wrap:=wdFindStop, _
MatchWholeWord:=True, Forward:=True) = True
Selection.Range.HighlightColorIndex = wdNoHighlight
Selection.Collapse wdCollapseEnd
Loop
End With

cOtherItemRepeat = MsgBox("Do you want to restore normal formatting an
another individual phrase or character?", _
vbYesNoCancel, "Restore Formatting")
If cOtherItemRepeat = 6 Then GoTo OMR
End If
End If
End Sub
 
G

Greg Maxey

Jezebel,

After clearing my head, I think I have found a way to avoid GoTo statements
in the code I sent earlier. This is most likely still repleat with
inefficiencies and poor programing but it at least works without the GoTo.
Constructive comments encourages as always.

Sub ClearHL()
Dim fWord As String
Dim bExists As Boolean
Dim oVar As Variable
Dim cLastItem As VbMsgBoxResult
Dim UserQuerry As VbMsgBoxResult
Dim cAllItems As VbMsgBoxResult

cAllItems = MsgBox("Do you want to remove highlighting throughout the
document?", _
vbYesNoCancel, "Restore All")
If cAllItems = 6 Then
Selection.Find.ClearFormatting
Selection.Find.Highlight = True
Selection.Find.Replacement.Highlight = False
With Selection.Find
.Text = "*"
.Replacement.Text = "^&"
.Forward = True
.Wrap = wdFindContinue
.MatchWildcards = True
End With
Selection.Find.Execute Replace:=wdReplaceAll
Exit Sub
End If

For Each oVar In ActiveDocument.Variables
If oVar.Name = "fWord" Then
bExists = True
Exit For
End If
Next oVar

If bExists Then
fWord = ActiveDocument.Variables("fWord").Value
ActiveDocument.Variables("fWord").Delete

cLastItem = MsgBox("Do you want to restore normal formatting to " &
Chr$(34) & fWord & Chr$(34) & " the last word highlighted?", _
vbYesNo, "Restore Last")
If cLastItem = 6 Then
Selection.HomeKey wdStory
Selection.Find.ClearFormatting
With Selection.Find
Do While .Execute(FindText:=fWord, Wrap:=wdFindStop, _
MatchWholeWord:=True, Forward:=True) = True
Selection.Range.HighlightColorIndex = wdNoHighlight
Selection.Collapse wdCollapseEnd
Loop
End With
End If
UserQuerry = MsgBox("Do you want to restore normal formatting an another
individual phrase or character?", _
vbYesNoCancel, "Restore Formatting")
End If
If Not (bExists) Or UserQuerry = 6 Then
Do
fWord = InputBox$("Type in the word or phrase that you want restore normal
formatting.")
If LenB(fWord) > 0 Then
Selection.HomeKey wdStory
Selection.Find.ClearFormatting
With Selection.Find
Do While .Execute(FindText:=fWord, Wrap:=wdFindStop, _
MatchWholeWord:=True, Forward:=True) = True
Selection.Range.HighlightColorIndex = wdNoHighlight
Selection.Collapse wdCollapseEnd
Loop
End With
Else
Exit Sub
End If
UserQuerry = MsgBox("Do you want to restore normal formatting an another
individual phrase or character?", _
vbYesNoCancel, "Restore Formatting")
Loop Until UserQuerry > 6
End If
End Sub
 
G

Greg Maxey

Already found one efficiencies:

cAllItems = MsgBox("Do you want to remove highlighting throughout the
document?", _
vbYesNoCancel, "Restore All")
If cAllItems = 6 Then
Selection.WholeStory
Selection.Range.HighlightColorIndex = wdNoHighlight
Selection.Collapse Direction:=wdCollapseStart
Exit Sub
End If
 
J

Jezebel

Your example highlights delightfully the problem of GOTO ... it makes the
code damned hard to understand! :)
And I'm still not sure that I've got it. The point of the exercise is not to
'eliminate GOTOs' as such, but to write code that is easy to understand, and
thus easy to maintain. It's a bit like those guides for writers that say 'do
not split your infinitives' -- going through your text and eliminating split
infinitives doesn't turn bad writing into good; but it is true that in good
writing infinitives are generally unsplit.

The key part of your code, for the purposes of this question, is where
you're removing the highlighting from particular words -- fWord if defined,
then any word. You could structure it like this:

'Get fWord if defined
on error resume next
fWord = ActiveDocument.Variables("fWord")
On error goto 0

'If defined, check if the user wants to clear it
if len(fWord) > 0 then
if MsgBox("Do you want to clear the last word ...", vbYesNo) = vbNo then
fWord = ""
end if
end if


'Loop until the user has had enough
Do
'If we don't have a word to process, then prompt (ie no prompt on first
pass if
'we are clearing the pre-defined fWord)
If len(fWord) = 0 then
fWord = inputbox(...)

'If user cancelled then exit
if len(fWord) = 0 then
exit do
end if
end if

'Remove highlighting from fWord
....

'Clear fWord and go round again
fWord = ""

Loop


Note the named constants for the MsgBox return values. vbYes = 6, vbNo = 7,
vbCancel = 2, etc. (I had to look these up to understand your code.)
 
G

Greg Maxey

Jezebel,

Thanks for all the tips. I think some of our messages may have crossed. I
saw more simplification in your last and have adapted my code as follows to
provide a little more user information (e.g., the first mesage box displays
the last word if defined).

Sub ClearHL()
Dim fWord As String
Dim oVar As Variable
Dim UserQuerry As VbMsgBoxResult
Dim cAllItems As VbMsgBoxResult

cAllItems = MsgBox("Do you want to remove highlighting throughout the
document?", _
vbYesNoCancel, "Restore All")
If cAllItems = 6 Then
Selection.WholeStory
Selection.Range.HighlightColorIndex = wdNoHighlight
Selection.Collapse Direction:=wdCollapseStart
Exit Sub
End If

'I use this bit instead of the OnError because Errors still freak me out.
For Each oVar In ActiveDocument.Variables
If oVar.Name = "fWord" Then
fWord = ActiveDocument.Variables("fWord").Value
ActiveDocument.Variables("fWord").Delete
Exit For
End If
Next oVar

If Len(fWord) > 0 Then
If MsgBox("Do you want to restore normal formatting to " & Chr$(34) &
fWord & Chr$(34) & " the last word highlighted?", _
vbYesNo, "Restore Last") = vbYes Then
Selection.HomeKey wdStory
Selection.Find.ClearFormatting
With Selection.Find
Do While .Execute(FindText:=fWord, Wrap:=wdFindStop, _
MatchWholeWord:=True, Forward:=True) = True
Selection.Range.HighlightColorIndex = wdNoHighlight
Selection.Collapse wdCollapseEnd
Loop
End With
Else
UserQuerry = MsgBox("Do you want to restore normal formatting to another
individual phrase or character?", _
vbYesNo, "Continue")
End If
End If

If Len(fWord) = 0 Or UserQuerry = vbYes Then
Do
fWord = InputBox$("Type in the word or phrase that you want restore
normal formatting.")
If LenB(fWord) = 0 Then
Exit Do
End If
Selection.HomeKey wdStory
Selection.Find.ClearFormatting
With Selection.Find
Do While .Execute(FindText:=fWord, Wrap:=wdFindStop, _
MatchWholeWord:=True, Forward:=True) = True
Selection.Range.HighlightColorIndex = wdNoHighlight
Selection.Collapse wdCollapseEnd
Loop
End With
UserQuerry = MsgBox("Do you want to restore normal formatting an
another individual phrase or character?", _
vbYesNoCancel, "Continue")
Loop Until UserQuerry > 6
End If
End Sub
 
J

Jezebel

Don't be afraid of using errors as part of your code. The term 'error' is
misleading (and has been changed, I believe, in VB.Net) -- it's only humans
that think there's something 'bad' about it. As far as the computer is
concerned errors are instructions like any other. And for some purposes
there is really is NO alternative but to 'try it and see what happens' -- eg
reading from a network drive or website that might or might not be
available.
 
G

Greg Maxey

Jezebel,

I will try to be brave. I just noticed that I can eliminate the cAllItems
in the first IF and use the same construction as the 4th IF :)
 
J

Jezebel

Sooner or later braveness will be forced upon you :). Iterating the
collection is OK here because you've probably got only a very few variables
anyway; but it would hurt if the collection count was in six figures, which
is not so uncommon.

You should also find a way to eliminate the duplication of the 'remove
highlighting' code. Either design the loop so the code is needed only once,
or put that code into a separate Sub (that takes the word to deal with as an
argument).
 
G

Greg Maxey

Jezebel,

Ahead of you by nose this one time. I had thought of that:

Sub RemoveHighlight(fWord As String)
'Called by ClearHL
Selection.HomeKey wdStory
Selection.Find.ClearFormatting
With Selection.Find
Do While .Execute(FindText:=fWord, Wrap:=wdFindStop, _
MatchWholeWord:=True, Forward:=True) = True
Selection.Range.HighlightColorIndex = wdNoHighlight
Selection.Collapse wdCollapseEnd
Loop
End With
End Sub

It is a here is the whole mess if you care to see it all in one shot:
Option Explicit
Sub CountOccurrences()
Dim fWord
Dim iCount As Integer
Dim hLight As VbMsgBoxResult

Call ResetFRParameters

fWord = InputBox("Type in the word or phrase that you want to find and
count.")
If fWord = "" Then
Exit Sub
End If
iCount = 0
hLight = MsgBox("Do you want to highlight each occurrence?", vbYesNo,
"Highlight")
Selection.HomeKey wdStory
Selection.Find.ClearFormatting
With Selection.Find
.Text = fWord
.Wrap = wdFindStop
.MatchWholeWord = True
.MatchCase = False
.Forward = True
.MatchAllWordForms = False
Do While .Execute = True
If hLight = vbYes Then
Selection.Range.HighlightColorIndex = wdYellow
Selection.Collapse wdCollapseEnd
End If
Selection.Collapse wdCollapseEnd
iCount = iCount + 1
Loop
End With
If iCount > 1 Then
MsgBox Chr$(34) & fWord & Chr$(34) & " was found " & _
iCount & " times."
ElseIf iCount = 1 Then
MsgBox Chr$(34) & fWord & Chr$(34) & " was found " & _
iCount & " time."
Else
MsgBox Chr$(34) & fWord & Chr$(34) & " was not found."
End If
ActiveDocument.Variables("fWord").Value = fWord

End Sub
Sub ClearHL()
Dim fWord As String
Dim oVar As Variable
Dim UserQuerry As VbMsgBoxResult
Dim cAllItems As VbMsgBoxResult

If MsgBox("Do you want to remove highlighting throughout the document?", _
vbYesNoCancel, "Restore All") = vbYes Then
Selection.WholeStory
Selection.Range.HighlightColorIndex = wdNoHighlight
Selection.Collapse Direction:=wdCollapseStart
Exit Sub
End If

For Each oVar In ActiveDocument.Variables
If oVar.Name = "fWord" Then
fWord = ActiveDocument.Variables("fWord").Value
ActiveDocument.Variables("fWord").Delete
Exit For
End If
Next oVar

If Len(fWord) > 0 Then
If MsgBox("Do you want to restore normal formatting to " & Chr$(34) &
fWord & Chr$(34) & " the last word highlighted?", _
vbYesNo, "Restore Last") = vbYes Then
Call RemoveHighlight(fWord)


UserQuerry = MsgBox("Do you want to restore normal formatting to another
individual phrase or character?", _
vbYesNo, "Continue")
Else
fWord = ""
End If
End If

If Len(fWord) = 0 Or UserQuerry = vbYes Then
Do
fWord = InputBox$("Type in the word or phrase that you want restore
normal formatting.")
If LenB(fWord) = 0 Then
Exit Do
End If
Call RemoveHighlight(fWord)

UserQuerry = MsgBox("Do you want to restore normal formatting an
another individual phrase or character?", _
vbYesNoCancel, "Continue")
Loop Until UserQuerry > 6
End If
End Sub
Sub ResetFRParameters()

With Selection.Find
.ClearFormatting
.Replacement.ClearFormatting
.Text = ""
.Replacement.Text = ""
.Forward = True
.Wrap = wdFindStop
.Format = False
.MatchCase = False
.MatchWholeWord = False
.MatchWildcards = False
.MatchSoundsLike = False
.MatchAllWordForms = False
End With

End Sub
Sub RemoveHighlight(fWord As String)
Selection.HomeKey wdStory
Selection.Find.ClearFormatting
With Selection.Find
Do While .Execute(FindText:=fWord, Wrap:=wdFindStop, _
MatchWholeWord:=True, Forward:=True) = True
Selection.Range.HighlightColorIndex = wdNoHighlight
Selection.Collapse wdCollapseEnd
Loop
End With
End Sub
 
W

Word Heretic

G'day "Greg Maxey" <[email protected]>,

<grins>

Do not use
If cAllItems = 6 Then

When word ver changes it may not be that value anymore. Thus:
If cAllItems = vbYes Then

is safer AND more readable.

Now, our previous lesson used a With structure to avoid re-referencing
the same object over and over. With Selection is just begging
everywhere. Try that one on next.


Steve Hudson - Word Heretic
Want a hyperlinked index? S/W R&D? See WordHeretic.com

steve from wordheretic.com (Email replies require payment)


Greg Maxey reckoned:
 
G

Greg Maxey

Steve,

My brain is scattered worse than the trees and less solid structures here in
central Florida. I will go back and see if I can apply the lessons thought,
but not learned.

At least I make you grin.
 
G

Greg Maxey

Steve,

I have change my called macro to:

Sub RemoveHighlight(fWord As String)
With Selection
.HomeKey wdStory
.Find.ClearFormatting
With Selection.Find
Do While .Execute(FindText:=fWord, Wrap:=wdFindStop, _
MatchWholeWord:=True, Forward:=True) = True
Selection.Range.HighlightColorIndex = wdNoHighlight
Selection.Collapse wdCollapseEnd
Loop
End With
End With
End Sub
 
J

Jezebel

Since you seem to be in a tip-collecting mood (don't you ever sleep?) --

1. Don't use the Integer data type. That's included only for backward
compatibility. Since Windows is now a 32 bit operating system, there is
nothing to gain in using a 16 bit data type. On the contrary, it makes
*more* work for the operating system, because it allocates 32 bits anyway,
then has to zero-out the top 16 checking for 16-bit overflow.

2. Choose a better variable naming convention. Doesn't much matter which
convention you use as long as you're consistent. My preference is to
identify variables by scope (p for procedure level, m for module level, g
for global).

3. Follow Steve H's suggestions about avoiding the Selection object.
 
G

Greg Maxey

Jezebel

OK, replaced Integer with Long

New variables names
mFword 'can get you suspended from grammar school
Dim pCount As Long
Dim pHlight

Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)

Sleep 18000000 'average per day0
 
W

Word Heretic

G'day "Greg Maxey" <[email protected]>,

CLOSE! Damn close.

See how you have With Selection.Find?

Well, you have With Selection prior, so all you really need at that
point is With .Find. Cool hey :) However, we are only running one
statement off that .Find, so I would kill that particular With, add
the .Find before the .Execute, and kill the Selection. on the
following lines.

Heh, Ve Haf Vays of Making you Verk! VERK damn you!

Steve Hudson - Word Heretic
Want a hyperlinked index? S/W R&D? See WordHeretic.com

steve from wordheretic.com (Email replies require payment)


Greg Maxey reckoned:
 
G

Greg Maxey

Steve,

So like this:

Sub RemoveHighlight(mFword As String)
With Selection
.HomeKey wdStory
.Find.ClearFormatting
Do While .Find.Execute(FindText:=mFword, Wrap:=wdFindStop, _
MatchWholeWord:=True, Forward:=True) = True
Selection.Range.HighlightColorIndex = wdNoHighlight
Selection.Collapse wdCollapseEnd
Loop
End With
End Sub

Thank you.
 
J

Jezebel

Two mistakes. Score 6/10.

In the DoWhile Find loop you still have two superfluous mentions of the
Selection object.


Greg Maxey said:
Steve,

So like this:

Sub RemoveHighlight(mFword As String)
With Selection
.HomeKey wdStory
.Find.ClearFormatting
Do While .Find.Execute(FindText:=mFword, Wrap:=wdFindStop, _
MatchWholeWord:=True, Forward:=True) = True


**** Remove 'Selection' from these two lines *****
 
W

Word Heretic

G'day "Jezebel" <[email protected]>,

<Chuckles> You are a hard master :)

Steve Hudson - Word Heretic
Want a hyperlinked index? S/W R&D? See WordHeretic.com

steve from wordheretic.com (Email replies require payment)


Jezebel reckoned:
 

Ask a Question

Want to reply to this thread or ask your own question?

You'll need to choose a username for the site, which only take a couple of moments. After that, you can post your question and our members will help you out.

Ask a Question

Top