Error Handling in VBScript – Part I

Introduction

Over the last few months I have been sponsoring the development of a new Best Practice for the use of scripting for the automation of system administration. However in doing this I came across a gap in the existing Microsoft documentation and in many of the VBscripting books available (1). None seem to give a clear and coherent explanation of how error processing works in VBscript. I think that I’m still a competent VBscript programmer, yet as I dug deeper I found some features that surprised me and that most of our script coders knew even less about this than I did!

However, if you think that you already understand how error handling works in VBscript, then try your knowledge on the following example. Look at the code and write down the error codes that it outputs up to the point where it fails, then compare your list to the answers at the end of this paper(5). I might warn you that I have yet to find anyone who gets it 100% right on the first attempt.

On Error Resume Next
' Note that 1/0 generates error 11 -- division by zero
' Note that a(2) generates error 9 -- subscript out of range
a = Array (0,1)
b = 1/a(0) : Wscript.Echo "(a) = ", Err.Number
Err.Clear
c = a(2) : Wscript.Echo "(b) = ", Err.Number
b = 1/c : Wscript.Echo "(c) = ", Err.Number
b = 1/a(2) : Wscript.Echo "(d) = ", Err.Number
Wscript.Echo "(e) =", b , Err.Number
Wscript.Echo "(f) = ", a(2), Err.Number
b = a(0): Wscript.Echo "(g) = ", Err.Number
Blah a, 2, true, false : Wscript.Echo "(h) = ", Err.Number
Blah a, 2, false, true : Wscript.Echo "(i) = ", Err.Number
Blah a, 2, false, false : Wscript.Echo "(j) = ", Err.Number
Blah a, 1, true, false : Wscript.Echo "Overall Status =", Err.Number
Sub Blah(a, i, trap, cont)
If trap Then On Error Goto 0
If cont Then On Error Resume Next
b = a(i)
c = 1/b
End Sub

So this paper is really essential reading for anyone who uses VBscript for the automation of server or client administration, ASPs or any other purpose. It provides documentation and guidance on how to code to avoid the pitfalls whilst utilizing the strengths of VBscript error handling. It is divided into 3 sections:

  • Throwing and Catching Errors. This section discusses how the VBscripting engine handles errors when one occurs in a script. It draws heavily on Eric Lippert’s excellent blog series and specifically on a set of three blogs on the 19th, 20th and 23rd Aug 2004. I have expanded these and added various clarifications within my own overall structure (2).
  • Interpreting the Error Code and Description. Once the scripting engine detects an error, it records the details in the Err object. This section describes how this encoding of the error works and how you can usefully interpret this information.
  • Strategy for Handling Errors. This may seem trivial, but unless you are writing a script solely for your own convenience and use, you really need do a strategy for handling errors. In the worlds of enterprise system administration and ASP, the person who is running the script is not the same as its author. So it isn’t you, the script author, who has to deal with errors when they occur; it’s the poor user. You therefore have a responsibility to the user to address the question “what should the script do if an error occurs?”

Throwing and Catching Errors

I want to very carefully describe what the error handling semantics are in the language, because there is some confusion over how exactly it works. There are two statements that affect error handling in VBScript

        On Error Resume Next
        On Error Goto 0

The meaning of the first seems clear — if you get an error, ignore it and resume execution on the next statement. But as we’ll see, there are some subtleties. But before that, what the heck is up with the second statement?

The second statement turns off ‘resume next’ mode if it is on. Yes, the syntax is ridiculous — something like On Error Raise would be a whole lot more clear. But for historical purposes, this is what we’re stuck with. Visual Basic has an error handling mode which VBScript does not — VB can branch to a labelled or numbered statement. (Remember line numbers? Those were the days!) To tell VB that you no longer wish to branch to that statement, you give zero, an invalid line number. C’est super beaucoup de fromage, n’est-ce pas? But we’re stuck with it now.

The subtlety in the “resume next” mode is best illustrated with an example (3) .

Const InvalidCall = 5
Wscript.Echo "Global code start"
Blah1
Wscript.Echo "Global code end"
Sub Blah1()
   On Error Resume Next
   Wscript.Echo "Blah1 Start"
   Blah2
   Wscript.Echo "Blah1 End"
End Sub
Sub Blah2()
   Wscript.Echo "Blah2 Start"
   Err.Raise InvalidCall
   Wscript.Echo "Blah2 End"
End Sub

This prints out

Global code start
Blah1 Start
Blah2 Start
Blah1 End
Global code end

Hold on a minute — when the error happened, Blah1 had already turned ‘resume next’ mode on. The next statement after the error raise is Wscript.Echo “Blah2 End” but that statement never got executed. What’s going on?

What’s going on is that the error mode is effect a hidden boolean flag that is local to the procedure, not a global variable. Like all variables in VBscript it has a default value, and this is “Raise”. So if you want to handle errors then you need to include an On Error Resume Next in each procedure where you want to use If Err.Number… because the default is that the error will be raised to the calling procedure.

Note that this functionality is not explicitly documented in the Microsoft documentation.

If it were on a global basis, all kinds of bad things could happen — think about how you’d have to design a program to have consistent error handling in a world where that setting is global, and you’ll see why it’s per-procedure.) In this case, Blah2 gets an error. Blah2 is not in ‘resume next’ mode, so it aborts itself, records that there was an error situation, and returns to its caller. The caller sees the error, but the caller is in ‘resume next’ mode, so it resumes.

In short, the propagation model for errors in VBScript is basically the same as traditional structured exception handling — the exception is thrown up the stack until someone catches it, or the program terminates. However, the error information that can be thrown, and the semantics of the catcher are quite a bit weaker than, say, JScript’s structured exception handling.

Also, remember that the ‘next’ in ‘resume next’ mode is the next statement. Consider these three programs, for example. Do they have the same semantics?

On Error Resume Next
Temp = CInt(Foo.Bar(123))
Blah Temp
Wscript.Echo "Done"
On Error Resume Next
Blah CInt(Foo.Bar(123))
Wscript.Echo "Done"
On Error Resume Next
Temp = CInt(Foo.Bar(123)) : Blah Temp
Wscript.Echo "Done”

No! If Foo.Bar raises an error, then the first one passes Empty to Blah. The second one never calls Blah at all if an error is raised, because it resumes to the next statement. The third is the same semantically as the first: next statement means just that and not next line. Statements are separated by either a line break or a : delimiter.

You can get into similar trouble with other constructs. For example, these two do have the same semantics:

On Error Resume Next
If Blah Then
Wscript.Echo "Hello"
End If
Wscript.Echo "goodbye"
On Error Resume Next
If Blah Then Wscript.Echo "Hello"
Wscript.Echo "goodbye"

If Blah raises an error then it resumes on the Wscript.Echo “Hello” in either case. You can also get into trouble with loops:

On Error Resume Next
For index = 1 to Blah
        Wscript.Echo TypeName(index)
Next
Wscript.Echo "Goodbye"

If Blah raises an error, this resumes into the loop, not after the loop. This prints out

  Empty
  Goodbye

The next thing I want to discuss is how you can programmatically interrogate errors after they have occurred. When an error occurs the scripting engine maintains some context information relating to the error, and it uses the Err object to expose this information, though for various historic reasons some of the properties that would be very helpful such as the procedure name and line number are not made available through Err. I will discuss how the Err object can be interpreted later, but now I focus on some scoping issues.

Unlike the error mode flag, the Err object is global and unique. Whenever the scripting engine processes an error it aborts interpreting the current statement at the point of the error and set the Err status overwriting any previous content. To demonstrate this:

On Error Resume Next
a = Array (0,1)
b = a(1)/a(0) ' This generates a division by zero error
c = a(2) ' This generates a subscript out of range error
Wscript.Echo Err.Description
Blah
Wscript.Echo Err.Description
Sub Blah()
   a = Array (0,1)
   b = a(1)/a(0) ' This generates a division by zero error:
   c = a(2) ' This generates a subscript out of range error
End Sub

In the main routine the script errors at the zero divide, and then resumes and errors at the invalid subscript reference. ‘Resume next’ is still in force so Blah is called. In Blah, the error mode now defaults to ‘raise’ so this time the zero divide throws an exception which is then picked up in the main routine because in it ‘resume next’ mode applies. Hence the print out is:

      Subscript out of range
      Division by zero

Got that? This underlines a general technique that allows you to implement ‘try catch’ style semantics in VBscript allowing you to construct a code block where you can abort at the first error but then resume after the block. You do this by moving the code block into a subroutine. If you then precede the call to the code block by an On Error Resume Next, you will always return to the statement following the call to allow you to process the first error thrown.

I will also emphasise what may seem an obvious point because I have also seen this one missed in some scripts that I have looked at: you must ensure that the statement path before the error within the same procedure includes an On Error Resume Next before you can meaningfully refer to Err or its properties in your script. The reason for this is simple: if you don’t, you will only get to your if Err… code if you haven’t had one, and this makes the code a bit pointless.

Now to the next startling feature of VBscript error handling :

Both On Error statements clear the recorded error information buffer (4).

Not only is this feature undocumented by Microsoft (except, as far as I can see, as a passing reference in Eric Lippert’s blog), but most Computer Science buffs would regard this as a bad practice — what we have here is that two statements which nominally toggle a local frame error mode flag, also clear the global Err object as a side effect! Hence the following two function calls are not the same:

On Error Resume Next
a = 0
b = 1/ a ' This generates a zero divide error:
Wscript.Echo "dbl1 = " & dbl1(b) & ", Err = "& Err.Number
Wscript.Echo "dbl2 = " & dbl2(b) & ", Err = "& Err.Number
Function dbl1(n)
  dbl1 = 2*n
End Function
Function dbl2(n)
  On Error Goto 0
  dbl2 = 2*n
End Function

Though you might assume that errors are latched, as you can see from the output adding the On Error Goto 0 to the second function call results in you loosing the first error:

   dbl1 = 0, Err = 11
   dbl2 = 0, Err = 0

This also means that if you have a error handler that catches a specific error, say, and you want to throw an exception up the call stack you have to go through some convolved high-jinks to save and restore the contents Err as the following code fragment demonstrates.

Const FILE_NO_PERM = 70
On Error Resume Next
Do
   Set logFile = openLogFile
   If Err.Number <> FILE_NO_PERM Then Exit Do
   Err.Clear
   Wscript.Sleep 1000
Loop
If Err.Number <> 0 Then
   oldErr = Array(Err.Number, Err.Source, Err.Description, _
   Err.HelpFile, Err.HelpContext)
   On Error GoTo 0
   Err.Raise oldErr(0), oldErr(1), oldErr(2), _
   oldErr(3), oldErr(4)
End If
On Error GoTo 0

This is an example where a ‘permission denied’ error may be a valid response (because some other process has the log file open) and you have a rule for processing this particular error (wait a bit and try again). Note the use of a variant to collect the properties of Err. Just doing a Set lastErr = Err wont work because Err is an object, and all the Set does is to point lastErr to Err; it isn’t a copy. After a On Error GoTo 0 then lastErr.Number would be zero because lastErr still points to Err which has now been cleared.

Footnotes

(1) Clearly I can’t know about all available books, but I have checked the ones available online at Books24x7 and none cover off this subject fully. Ditto the output of the Microsoft Scripting Guys, though I see that their December 2005 Doctor Scripto’s Script Shop covers some of this.

(2) However as he has done such a good job in laying out the ground work, I have wherever practical left his text intact and used a mauve colour to denote his extracts — credit where credit is due

(3) A little health warning here — this and all the other examples in this note are each designed to demonstrate a specific feature; so brevity and simplicity win over good programming practice here. In production code, I would always adopt a more robust stance such and always use Option Explicit and follow my own rules laid out in the final section.

(4) In fact I have only found one book that documents this fact, but it also incorrectly claims that Exit Sub and Exit Function clear the Record Information Buffer.

(5) It doesn’t fall over. It runs to completion, so (a) = 11, (b) = 9 (c) = 11, (d) = 9, (e) = 9, <missing>, (g) = 9, (h) = 9, (i) = 11, (j) = 9 and the overall status = 0 which should means that we had no errors. Oops ?

Leave a Reply