Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations Shaun E on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Exit Sub vs. GoTo ProcExit: - Am I just being old-fashioned?

Status
Not open for further replies.

bjm1335

Programmer
Jan 25, 2002
44
US
I was taught a LONG time ago (before most of you were born, I'm sure) that there should be one entry point and one exit point to a proc/pgm/whatever. Being new to VB, I started using the the following "template" which is similar to what I've used in other languages:

Private Sub xxx_GotFocus()
On Error GoTo ErrRtn:

If Not blnEditRec And Not blnNewRec then GoTo ProcExit:
.
.
ProcExit:
Exit Sub

ErrRtn:
Call DisplayErrMsg(xxx, yy, zzz)
Resume ProcExit:
End Sub

Do you guys feel it's an OK practice to use:

"If Not blnEditRec And Not blnNewRec Then Exit Sub"

in place of the GoTo ProcExit:?

I actually just started implementing a CallStack which
REQUIRES I have 1 entry/exit in order to properly maintain the stack, but I just wondered in general about the process.

Any and all comments welcome.
 
I am in complete agreement that functions and procedures should have one entry point, and one exit point. I am not, and never have been a fan of the Exit Sub capability. I also don't like Exit Loop and Exit For for the same reasons.

And with the exception of the On Error Goto - I don't use goto's either.

I would replace your line

If Not blnEditRec And Not blnNewRec then GoTo ProcExit:

with

If blnEditRec or blnNewRec Then
<place code here>
End If

ProcExit:

Exit Sub

Good Luck
--------------
As a circle of light increases so does the circumference of darkness around it. - Albert Einstein


 
I agree to a large extent with your method. The ONLY reason I don't use that (and it may be a weak/lazy one) is that I try to avoid going too many layers deep with IF's in order to maintain readability and to avoid &quot;creep&quot; toward the right margin.
 
Readability should not be an issue provided that reasonable indendation is being done. As far as right margin creep, if it gets to deep, then the proc can be split into multiple procs, and of course, judicious use of the line continuation (_) can also aid in right margin creep.

IMHO, margin creep is preferable to spaghetti creep.

Now, if we had a COME_FROM command - that would be useful. How many times have you found yourself in an event handler, wondering, just where did I ComeFrom ?
Good Luck
--------------
As a circle of light increases so does the circumference of darkness around it. - Albert Einstein


 
Hmmmmmmmmmmmmmmmm,

CajunCenturion and bjm1335,

A BRIEF review of your code revels the dreaded EXIT SUB statement? I would like to see if either of you can set up a procedure with error trapping which DOES NOT use either &quot;EXIT SUB&quot; or GOTO (not on error)?

As for the other exits (LOOP | FOR), How else do you get out of the loop where the terminiation criteria may not be know at design time?

IMHO, the 'platitudes' re-programming style are intresting and useful guidelines - BUT - the language includes each statements for a reason. Mostly, the reason is some [necessary | useful] functionallity. To dismiss the functionallity for style considerations is -for me- NOT an option.

MichaelRed
m.red@att.net

There is never time to do it right but there is always time to do it over
 
Michael
As I stated, with the exception of the &quot;On Error Goto&quot;, I don't use Goto statements. And the premise is that a procedure and/or function should have only 1 entry point and 1 exit point. That 1 exit point is the one and only Exit Sub statemnt.

As far as Loop exits - the Do While and Do Until constructs should be used for unknown loop interations. So you set the conditions appropriatly to exit the loop at the desired time. The For loop should only be used when the number of iterations is both know and constant throughout the life of the loop.

Good Luck
--------------
As a circle of light increases so does the circumference of darkness around it. - Albert Einstein


 
Michael - You're exactly right - &quot;the 'platitudes' re-programming style are intresting and useful guidelines&quot;, and that's exactly what I'm using them as - and am just trying to &quot;set up&quot; the best guidelines I can for my use and to make sure that they, for the most part, are understandable and acceptable to whoever the lucky programmer is that inherits my code.

And if we're talking &quot;wish-I-hads&quot; - I wish there was a way in any of the looping mechanisms to skip to the next iteration of the loop without using a/many if stmts to skip around. IOW:

Do While x < y
.
.
Next <DO While Loop>
.
.
.
Loop

Anyway, thanks all for your feedback. And I look forward to anyone elses.
 
BTW CajunCenturion - you mentioned a &quot;COME_FROM&quot; command. That's a lot like my CallStack routine. I'd like your comments on my error handling routine (in progress):

***********************************
Just as an example, here's a typical sub with the error rtn in it
***********************************

Private Sub cboJobCd_GotFocus()
gstrChkPt = &quot;On Error GoTo ErrRtn:&quot;
On Error GoTo ErrRtn:

Const strProcName As String = &quot;cboJobCd_GotFocus&quot;

' I use this next var to &quot;back up&quot; to the last major
' check point in the call stack, so basically when
' I get an error, I start at the end of the call stack
' and look backwards to the the last &quot;True&quot; and then
' work forward to report everything from that point
' forward
gblnCallStackMajor = False

' I use this var to pass any record-specific, key or
' other unique info
gstrCallStackInfo = &quot;Job Cd &quot; & rs!JobCd & _
&quot; Rate &quot; CStr(rs!Rate)

Call CallStackAdd(strProcName, gstrCallStackInfo, _
gblnCallStackMajor)

.
.
.

ProcExit:
Call callStackDel
Exit Sub

ErrRtn:
Call ErrMsg(strModuleName, strProcName, gstrChkPt,_
Err.Number, Err.Description, Err.Source)
Resume ProcExit:
End Sub


**************************************************
This is the code in my error handler basErrMsg.bas
**************************************************

Option Explicit

Private Const strModuleName As String * 30 = &quot;basErrorMsg&quot;
Private strCompName As String * 15
Private strTime As String * 6
Private MSErrorMsg As String
Private strLogFileName As String

' following used to obtain MS error msg
Declare Function FormatMessage Lib &quot;kernel32&quot;_
Alias &quot;FormatMessageA&quot; _
(ByVal lngFlags As Long, _
ByVal lpSource As Any, _
ByVal lngMessageId As Long, _
ByVal lngLanguageId As Long, _
ByVal lpBuffer As String, _
ByVal nSize As Long, _
Arguments As Long) As Long

Const FORMAT_MESSAGE_ALLOCATE_BUFFER = &H100
Const FORMAT_MESSAGE_ARGUMENT_ARRAY = &H2000
Const FORMAT_MESSAGE_FROM_HMODULE = &H800
Const FORMAT_MESSAGE_FROM_STRING = &H400
Const FORMAT_MESSAGE_FROM_SYSTEM = &H1000
Const FORMAT_MESSAGE_IGNORE_INSERTS = &H200
Const FORMAT_MESSAGE_MAX_WIDTH_MASK = &HFF
Const LANG_USER_DEFAULT = &H400&

Public Function ErrMsg(_
Optional strModuleNameIn As String = &quot;Unknown&quot;, _
Optional strProcNameIn As String = &quot;Unknown&quot;, _
Optional strChkPtIn As String = &quot;Unknown&quot;, _
Optional lngErrNbrIn As Long = 0, _
Optional strErrDescIn As String = &quot;Unknown&quot;, _
Optional strErrSourceIn As String = &quot;Unkown&quot;, _
Optional strTableIn As String = &quot;&quot;, _
Optional strKeyIn As String = &quot;&quot;, _
Optional strMiscErrorInfo1 As String = &quot;&quot;, _
Optional strHelpFile As String = &quot;&quot;, _
Optional strHelpContext As String = &quot;&quot;)
' The strChkPtIn is used to pin an error down within a
' proc. If its a big proc, I'll put
' &quot;gstrChkpt = <a literal of the next command>&quot;
' so I could limit the possible area of the error

On Error GoTo ErrRtn:
gstrChkPt = &quot;On Error&quot;
Const strProcName As String = &quot;ErrMsg&quot;
Dim strHdr As String
Dim strMsg As String
Dim intMsgType As Integer
Dim intResponse As Integer
Dim intCntr As Integer
Dim intStartAt As Integer
Dim strCallStack As String

'****************************** Get Screen Shot Here
'****************************** Haven't done this yet

strHdr = &quot;Please Write Down Or Do A Screen Print Of This Screen And &quot; & _
&quot;Report This Error To The Person Responsible For Maintaining &quot; & _
&quot;This System &quot; & vbCrLf & vbCrLf

If lngErrNbrIn > vbObjectError Then
strMsg = strMsg & &quot;A Program &quot;
Else
strMsg = strMsg & &quot;A Visual Basic&quot;
End If

strCompName = basUtilities.ComputerName
strTime = Format(time, &quot;HHMMSS&quot;)

strMsg = strMsg & &quot; Error Has Occured: &quot; & _
vbCrLf & &quot; In Module: &quot; & strModuleNameIn & _
vbCrLf & &quot; Procedure: &quot; & strProcNameIn & _
vbCrLf & &quot; Check Point: &quot; & strChkPtIn & _
vbCrLf & &quot; Error Source: &quot; & strErrSourceIn & _
vbCrLf & &quot; Error Number: &quot; & str(lngErrNbrIn) & _
vbCrLf & &quot; Description: &quot; & strErrDescIn & _
vbCrLf & &quot; UserID: &quot; & gstrUserID & _
vbCrLf & &quot; Machine ID: &quot; & strCompName & _
vbCrLf & &quot; Date/Time: &quot; & str(Date) & &quot; &quot; & strTime

If strTableIn <> &quot;&quot; Then
strMsg = strMsg & vbCrLf & &quot; Table: &quot; & strTableIn
End If

If strKeyIn <> &quot;&quot; Then
strMsg = strMsg & vbCrLf & &quot; Key: &quot; & strKeyIn
End If

If strMiscErrorInfo1 <> &quot;&quot; Then
strMsg = strMsg & vbCrLf & &quot; Other Info: &quot; & strMiscErrorInfo1
End If

If strHelpFile <> &quot;&quot; Then
strMsg = strMsg & vbCrLf & &quot; Help File: &quot; & strHelpFile
End If

If strHelpContext <> &quot;&quot; Then
strMsg = strMsg & vbCrLf & &quot; Help Context: &quot; & strHelpContext
End If

intMsgType = vbExclamation

For intCntr = gintCallStackCnt To 0 Step -1
If gblnCallStackMajor(intCntr) = True Or _
intCntr = 0 Then
intStartAt = intCntr
End If
Next intCntr

strCallStack = &quot;Call Stack: &quot;
For intCntr = intStartAt To gintCallStackCnt
strCallStack = strCallStack & _
&quot;Proc: &quot; & gstrCallStackName(intCntr) & vbCrLf & _
&quot; Info: &quot; & gstrCallStackInfo(intCntr)
Next intCntr
If strCallStack = &quot;Call Stack: &quot; Then
strCallStack = &quot;Call Stack: None&quot;
End If

strMsg = strMsg & strCallStack

If lngErrNbrIn > vbObjectError Then
intResponse = MsgBox(strMsg, intMsgType, &quot;Program Error&quot;)
Else
MSErrorMsg = GetErrorMsg(lngErrNbrIn)
strMsg = strMsg & _
vbCrLf & &quot;MS Error Message: &quot; & MSErrorMsg & _
vbCrLf
If strHelpFile <> &quot;&quot; And _
strHelpContext <> &quot;&quot; Then
strMsg = strMsg & vbCrLf & &quot;Press Help button or F1 for the Visual Basic Help&quot; & _
&quot; topic for this error.&quot;
intResponse = MsgBox(strHdr & strMsg, intMsgType & vbMsgBoxHelpButton, &quot;Error&quot;, Err.HelpFile, Err.HelpContext)
Else
intResponse = MsgBox(strHdr & strMsg, intMsgType, &quot;Error&quot;)
End If
End If

' log error

strLogFileName = App.Path & &quot;/ErrorLogs&quot;
Call basFiles.CreateFolder(strLogFileName)

strLogFileName = strLogFileName & &quot;/&quot; & Format(Now, &quot;yyyymmdd&quot;) & &quot;.txt&quot;
Open strLogFileName For Append As #1

Write #1, &quot; ************************************************* &quot; & _
vbCrLf & strMsg
Close #1

' *********************** Send EMail
' *********************** Haven't completed this yet

ProcExit:
Err.Clear ' Clear Err object properties

' All of my maintenance pgms have &quot;Maint&quot; in the name. If I'm
' in a maint pgm, I want to undo the changes to the record
' that caused the error
If InStr(1, strModuleNameIn, &quot;Maint&quot;) Then
' awaiting logic - I have to pass the rst name and the
' mfnewrecord and mfeditrecord flags to do this centrally (ie, here)
' as opposed to having to code the logic into every proc on return
' from this error proc
End If

Exit Function

ErrRtn:
MsgBox (&quot;An error occured in the error handling routine (&quot; & Err.Source & &quot;)&quot; & _
vbCrLf & vbCrLf & str(Err.Number) & &quot; - &quot; & Err.Description)
Resume ProcExit:
End Function

Private Function GetErrorMsg(ErrNbr As Long) As String
On Error GoTo ErrRtn:
gstrChkPt = &quot;On Error&quot;: Const strProcName As String = &quot;GetErrorMsg&quot;

Static sMsgBuf As String * 257
Dim lngLen As Long

GetErrorMsg = &quot;Message Not Found&quot;
lngLen = FormatMessage(FORMAT_MESSAGE_FROM_SYSTEM Or _
FORMAT_MESSAGE_IGNORE_INSERTS Or _
FORMAT_MESSAGE_MAX_WIDTH_MASK, ByVal 0&, ByVal ErrNbr, _
LANG_USER_DEFAULT, ByVal sMsgBuf, 256&, 0&)
If lngLen Then GetErrorMsg = VBA.Left$(sMsgBuf, lngLen)

ProcExit:
Exit Function

ErrRtn:
Call ErrMsg(strModuleName, strProcName, gstrChkPt, Err.Number, Err.Description, Err.Source)
Resume ProcExit:
End Function


Public Sub CallStackAdd(ProcNameIn As String, _
Optional ProcInfoIn As String = &quot;None&quot;, _
Optional ProcMajorIn As Boolean = False)
gstrChkPt = &quot;On Error GOTo ErrRtn:&quot;: Const strProcName As String = &quot;CallStackAdd&quot;
On Error GoTo ErrRtn:
' gblnCallStackMajor = False: gstrCallStackInfo = &quot;&quot;
' Call CallStackAdd(strProcName, gstrCallStackInfo, gblnCallStackMajor)

ReDim Preserve gstrCallStackName(gintCallStackCnt)
ReDim Preserve gstrCallStackInfo(gintCallStackCnt)
ReDim Preserve gblnCallStackMajor(gintCallStackCnt)
gstrCallStackName(gintCallStackCnt) = ProcNameIn
gstrCallStackInfo(gintCallStackCnt) = ProcInfoIn
gblnCallStackMajor(gintCallStackCnt) = ProcMajorIn
gintCallStackCnt = gintCallStackCnt + 1

ProcExit:
' Call callstackdel
Exit Sub

ErrRtn:
Call ErrMsg(strModuleName, strProcName, gstrChkPt, Err.Number, Err.Description, Err.Source)
Resume ProcExit:
End Sub

Public Sub CallStackDel()
gstrChkPt = &quot;On Error GOTo ErrRtn:&quot;: Const strProcName As String = &quot;CallStackDel&quot;
On Error GoTo ErrRtn:
' gblnCallStackMajor = False: gstrCallStackInfo = &quot;&quot;
' Call CallStackAdd(strProcName, gstrCallStackInfo, gblnCallStackMajor)

If gintCallStackCnt = 0 Then
ReDim gstrCallStackName(0)
ReDim gstrCallStackInfo(0)
ReDim gblnCallStackMajor(0)
Else
ReDim gstrCallStackName(gintCallStackCnt - 1)
ReDim gstrCallStackInfo(gintCallStackCnt - 1)
ReDim gstrCallStackMajor(gintCallStackCnt - 1)
End If

gintCallStackCnt = gintCallStackCnt - 1

ProcExit:
' Call callstackdel
Exit Sub

ErrRtn:
Call ErrMsg(strModuleName, strProcName, gstrChkPt, Err.Number, Err.Description, Err.Source)
Resume ProcExit:
End Sub


 
bjm,
I am looking over what your doing and I see where you're going. I will go over it in more detail in the next day or so, but what strikes immediately is the potention performance hit that you'll incur. Considering the amount of traffic that will be going thru the CallStackAdd and CallStackDel functions, the number of redims involved doesn't feel right. I am not sure that using an array as the foundation structure for the stack is a wise choice. My gut reaction right now (its fairly late - so I may change my mind in the morning when I look at it again), but would be to use a global collection for the stack, with a User Type Structure as the elements to place in the collection. Collections lend themselves quite well to Push and Pop stack operations, but need to verify that updates to the entries aren't taking place. My 'update' concern revolves around the CallStackMajor boolean. The User Type structure would look something like

Type STACK_ENTRY
dim strProcName as string
dim gstrCallStackInfo as string
dim gblnCallStackMajor as boolean
End Type

Will check back in the morning
Good Luck
--------------
As a circle of light increases so does the circumference of darkness around it. - Albert Einstein


 
Since you are using this as a 'trace' mechanisim, I suggest that you simply dump the info to a text file. It is easily implememted and is quite useful for test / debug phases of development. I usually set up a flag system to toggle the trace, and set up a procedure to handle all of the actual writting. I can call the procedure from any point - and with any number of variables, so I 'log' the location with a unique tag / Id, as well as the name and value of variables of interest. While the file can get fairly large for a specific instantation, it is usually of little of no interest once the 'session' is complete, so it is usually discarded after review. In general, the disc (text) file can hold more information than a &quot;stack&quot; (in memory), so the trace can be much larger. I even set up a form to control the trace process. Of course this whole process is removed from the final production code.

MichaelRed
m.red@att.net

There is never time to do it right but there is always time to do it over
 
Thanks, Michael. Good Idea. Could you post an example of the code you use or EM to me at brucem@mail.org ?
 
Hi bjm,
After further review and some surprise, it really doesn't make any difference whether you use a collection or a redimmed array - the performance difference is nominal, and the procedures to keep a user-defined type in a collection are probably not worth the effort.

I still like the idea of the user defined type tho for a stack record - but keeping them in an array is fine. So define the type similar to what was shown above, adding additional elements as you see fit, then dim your stack array to the same type. We are dealing with one array rather then three or more.

In the CallStackDel routine, you allow the StackCount to go below zero. I would move the decrement into the else clause.

To deal with the recursive issue of pushing and pooping the CallStackAdd/Del calls, I agree with your decision not to include them in the call stack. You commented out the call which I agree is the best solution for this issue.

The other item that would prove useful, both in the call stack and in the error handler would be additional context sensitive information.

For example, your example was in a GotFocus event of a control. Suppose that were an array of controls. I would like to see the control index value on the array. Or lets say I had a CenterString function. I would like to know the contents of the String to be centered placed in the Stack Record, or the contents of that string at the time the error were raised.

Overall, I like what you're trying to do, and I wish you the best of luck. Depending on how detailed, this can get quite daunting. You may want to look at the ParamArray capabilities.
Good Luck
--------------
As a circle of light increases so does the circumference of darkness around it. - Albert Einstein


 
Thanks again, Cajun (may I call you Cajun, for short ?) for your input.
 
I have a quick question/comment about the general template function below (from the first poster).

Private Sub xxx_GotFocus()
On Error GoTo ErrRtn:

If Not blnEditRec And Not blnNewRec then GoTo ProcExit:
.
.
ProcExit:
Exit Sub

ErrRtn:
Call DisplayErrMsg(xxx, yy, zzz)
Resume ProcExit:
End Sub


What is the purpose of the Resume ProcExit: statement, when the next line is exiting the subroutine any way?

This is what I tend to do for error handling (using the same template outlined above)

Private Sub xxx_GotFocus()
On Error GoTo ErrRtn:

If Not blnEditRec And Not blnNewRec then GoTo ProcExit:
.
.

goto procExit
ErrRtn:
Call DisplayErrMsg(xxx, yy, zzz)

ProcExit:
'This is where I would perform all the cleanup that the
'sub requires like erasing local arrays, setting objects = nothing, etc.
'I also like to call this label &quot;CleanUp&quot;
End Sub

This way no exit subs or resumes are required. Is there anything wrong with this method? I still can't see what is wrong with a well placed goto? I too came from a school where the dreaded goto was to be avoided at all costs. I only use goto's in error handling situations, or &quot;hacks&quot; for my own personal use.

Regards,
Troy Williams B.Eng.
fenris@hotmail.com

 
Troy,

I prefer the original for the following reasons:

1. I like to have an exit sub statement at the end of each routine to make it clear that the exit is deliberate rather than just &quot;falling off the end&quot; of a procedure by mistake.

2. The usually executed code is all in-line, avoiding unnecessary branching.

3. Error handling can be included in any tidy up code (placed between proc_exit and exit sub).

With either approach you need to be careful about code executed in the error handler as it is not possible to reinstate error handling until you Resume. For this reason I sometimes use code such as the following:

on error goto Error_Handler
.
.
Exit_Routine:
'General tidy up
Exit Sub
Error_Handler:
'Display message
Resume Error_Routine
Error_Routine:
On Error Goto Error_Handler
'Additional code required after error
.
.
Go to Exit_Routine

You do need to be very careful to avoid loops with this sort of code, but you get an appropriate error message after every error.

Glyn.
 
Fenris,
The Resume statement actually performs a task which clears the current error exception. Its usually best the clear the err object with the resume statement after the error has been handled. Good Luck
--------------
As a circle of light increases so does the circumference of darkness around it. - Albert Einstein


 
I agree with GlynA - I just like to make it VERY clear that this stmt is leaving the sub. And since errorhandling is (hopefully) the exception cse, I prefer not to leave the error handling code &quot;in line&quot;.

And about clearing the error - you'll notice in the ProcExit: of my error rtn there is an Err.Clear just to be explicit about when it is cleared, even though I now it would be cleared by VB at the next Resume.

Thanks again to all of you for the input. This is/has been an interesting thread.
 
Thanks for the reponses, The tips will help me make more readable code!


So What would be a good template for a general subroutine/function with good error handling? Troy Williams B.Eng.
fenris@hotmail.com

 
CraigSander has written a nice FAQ on error handling. That would be a good place to start. Good Luck
--------------
As a circle of light increases so does the circumference of darkness around it. - Albert Einstein


 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top