Minimum and maximum values of numeric data types

There has been many an occasion when I have wanted programmatic access to the maximum or minimum or smallest value of a data type. Some programming languages have built-in support through names like MaxInt. VBA, unfortunately, is not one of them.

I decided to “translate” the documentation defining the different data types into code. The functions Max{datatype}, Min{datatype}, and Smallest{datatype} return the appropriate value. The Max and Min functions should be self-evident. The Smallest function returns the smallest non-zero value supported by the data type. Since this is simply 1 for all data types associated with integers (Byte, Integer, Long, LongPtr, LongLong, and Currency), Smallest is defined only for data types associated with real numbers (Single, Double, and Decimal).

For a version in a page by itself (i.e., not in a scrollable iframe as below) visit http://www.tushar-mehta.com/publish_train/xl_vba_cases/1003%20MinMaxVals.shtml

Tushar Mehta

Using the “short date”, “medium date” and “long date” formats

I came across a line of code that formatted a date in VBA like this: Format(aDate,”short date”). And I didn’t get it. So with a little investigation, it turns out that “short date” (and “medium date” and “long date”) relate to the specified system methods of expressing dates found in the regional settings. So I wrote this little bit of code:

Sub testit()
Dim aDate As Date
aDate = Date
Debug.Print Format(aDate, "short date")
Debug.Print Format(aDate, "medium date")
Debug.Print Format(aDate, "long date")
End Sub

This is what I got:
06/05/2012
5-Jun-12
Tuesday, June 5, 2012

On both my XP box and my Mac, except that on the Mac, “long date” maps to Full. Trouble is, on neither machine do I have a “medium” setting, or a setting that maps to “medium date”. So. it looks like “medium date” is XL internal.

I’m not sure what great good these choices do. It would appear to be full proof to just specify the format. This capability does not extend to the spreadsheet TEXT() function.

Here’s a page that covers it: http://www.techonthenet.com/excel/formulas/format_date.php
You can also do the same with Time.

…mrt
©¿©¬

Highlight row and column of active cell

By default, when the user selects a cell, Excel highlights the row and column by changing the color of the associated row and column headers. This tip shares multiple ways to highlight the row and column in more obvious ways as well as a way to highlight the cell in a specific column in the same row.


The emphasis is on the use of conditional formatting to accomplish the task. The minimal VBA code required to make it work is the same single executable statement for all of the different highlighting options!

For a version in a page by itself (i.e., not in a scrollable iframe as below) visit http://www.tushar-mehta.com/publish_train/xl_vba_cases/0121%20highlight%20row%20and%20col%20of%20selected%20cell.shtml

Tushar Mehta

Getting a Font List to a Combo Box

The other day a reader asked about how to get a font list to a combo box so his users could have a choice to specify. Borrowing shamelessly from John Walkenbach’s Tip 79, this is one way to do it. I use this approach when I take a spreadsheet to a web table and want to specify the font.

Font Sampler Image

From top to bottom, the form has:

  • A label, named lblFontcboOverLabel
  • A label, named lblFontcbo
  • A combo box, named cboFontOther
  • A frame, named Frame1
  • An option button, named btnAllFonts
  • An option button, named btnMonoFonts

This is the code behind the form:

Option Explicit
Private Fface As String, FaceNdx As Long
Private InstalledFonts As String

Public Property Get FontFace() As String
FontFace = FFace
End Property

Private Sub btnMonoFonts_Click()
Call AddFontBox(1)
Me.lblFontcbo = "Monospace Fonts"
End Sub

Private Sub btnAllFonts_Click()
Dim i As Long
Dim TempFonts As Variant

Me.cboFontOther.Clear

TempFonts = Split(InstalledFonts, ",")
For i = LBound(TempFonts) To UBound(TempFonts)
Me.cboFontOther.AddItem TempFonts(i)
Next i
Me.cboFontOther.Text = "Comic Sans MS"
Me.lblFontcbo = "All Fonts"
End Sub

Private Sub cboFontOther_Change()
Me.lblFontcboOverLabel = Me.cboFontOther.Text
Me.lblFontcboOverLabel.Font = Me.cboFontOther.Text
Me.lblFontcboOverLabel.Font.Size = 12
Fface = Me.cboFontOther.Text
End Sub

Private Sub UserForm_Initialize()
Dim FontList As CommandBarControl
Dim Tempbar As CommandBar, i As Long
'http://www.j-walk.com/ss/excel/tips/tip79.htm

Set FontList = Application.CommandBars("Formatting").FindControl(Id:=1728)
If FontList Is Nothing Then
Set Tempbar = Application.CommandBars.Add
Set FontList = Tempbar.Controls.Add(Id:=1728)
End If
Me.cboFontOther.Clear

For i = 1 To FontList.ListCount
If Left$(FontList.List(i), 1) Like "[A-Za-z0-9]" Then
Me.cboFontOther.AddItem FontList.List(i)
InstalledFonts = InstalledFonts & FontList.List(i)
If i <> FontList.ListCount Then InstalledFonts = InstalledFonts & ","
End If
Next i
Me.lblFontcbo = "All Fonts"

Me.cboFontOther.Text = "Impact"

On Error Resume Next
Tempbar.Delete
End Sub

Private Sub AddFontBox(i As Long)
Dim MonoFont As Variant
'etc

Dim TempFont As Variant, TempStr As String, Str1 As String, Str2 As String

MonoFont = "Monaco,Courier New,Courier,Lucida Sans Typewriter," & _
"Lucida Console,Nimbus Mono L,DejaVu Sans Mono,Andale Mono," & _
"Liberation Mono,Consolas,Courier 10 Pitch,FreeMono," & _
"Menlo Bold,Menlo Bold Italic,Menlo Italic,Menlo Regular," & _
"OCR A Extended,Tlwg Typist,TlwgMono,TlwgTypewriter," & _
"Tlwg Typo,Bitstream Vera Sans Mono"

Select Case i
Case 1: TempFont = Split(MonoFont, ",")
'etc
End Select

Me.cboFontOther.Clear

For i = LBound(TempFont) To UBound(TempFont)
Str1 = TempFont(i) & ","
Str2 = "," & TempFont(i)
If InStr(1, InstalledFonts, Str1, vbTextCompare) Or _
InStr(1, InstalledFonts, Str2, vbTextCompare) Then
TempStr = TempStr & TempFont(i)
If i <> UBound(TempFont) Then TempStr = TempStr & ","
End If
Next i
TempFont = Split(TempStr, ",")

For i = LBound(TempFont) To UBound(TempFont)
Me.cboFontOther.AddItem TempFont(i)
Next i

Me.cboFontOther.Text = TempFont(0)
End Sub

It has the “Get Property” at the top. I screen the installed fonts to filter the Asian fonts from my list. Remove the “Like” operator if you need them. I capture the the installed fonts as a global string variable in a comma-delimited list. The list of monospaced fonts came from here, and represents the fonts installed as a minimum on ⅓ of all Windows, Mac, and Unix computers. They’re listed in percentage order irrespective of machine and not by installation count.

As I use the full form, the Over Label lies atop the combo box. But if you want to see more than the font’s name in its own font, modify the combo box change to something like this:

Private Sub cboFontOther_Change()
Me.lblFontcboOverLabel = "Jackdaws love my big sphinx of quartz."
Me.lblFontcboOverLabel.Font = Me.cboFontOther.Text
Me.lblFontcboOverLabel.Font.Size = 12
Fface = Me.cboFontOther.Text
End Sub

…mrt
©¿©¬

Making a Wiki Table

Writing for Wikipedia is a bit like writing in your third language—you know there are words for it, but your guides are from your second language—Wiki pour Les Nuls or maybe Wiki para Maniquíes. It’s a different dialect of HTML. Having done it for several years, Wikipedia’s goal seems to be a reduction in keystrokes to be saved on its servers. For example, to italicize, rather than using the i- or em- tags, you use paired apostrophes (not double-quotes) to lead and close, saving at least three key strokes. To embolden, you use three apostrophes to lead and close, saving at least one stroke over the b- or strong- tags. And bold italics is thus five apostrophes leading, five apostrophes closing, saving at least four strokes. An unordered list’s members are just lines started with an asterisk, and an ordered list’s members are lines started with a pound sign. This economy follows into Wiki tables, where pipes (“|”) and curly braces (“{}”)are used for all the tags. There is a good summary of the table markup differences here. This little table:

1 2
3 4

 
In Wiki is this:

{|
| 1 || 2
|-
| 3 || 4
|}

as opposed to this:

1 2
3 4


If you have a table like this is in your spreadsheet:

Sports Teams    
  Boston New York
Baseball Boston Red Sox New York Yankees<br />New York Mets
Football New England Patriots New York Giants<br />New York Jets
Basketball Boston Celtics New York Knicks<br />New York Nets
Hockey Boston Bruins New York Rangers<br />New York Islanders

 
The MakeWikiTable() macro will make a table like this for Wikipedia:

Sports Teams
  Boston New York
Baseball Boston Red Sox New York Yankees
New York Mets
Football New England Patriots New York Giants
New York Jets
Basketball Boston Celtics New York Knicks
New York Nets
Hockey Boston Bruins New York Rangers
New York Islanders

And this table G33:H38

  G H I J K
32 Testing Sorting        
33 Coins Value      
34 Pennies 0.01<font color=white>[-]</font>   0.01 <font color=white>[-]</font>
35 Nickels 0.05<font color=white>[-]</font>   0.05 <font color=white>[-]</font>
36 Dimes 0.10<font color=white>[-]</font>   0.1 <font color=white>[-]</font>
37 Quarters 0.25<ref name=two>Two bits</ref>   0.25 <ref name=two>Two bits</ref>
38 Halves 0.50<ref name=four>Four bits</ref>   0.5 <ref name=four>Four bits</ref>

 
where H34: = Text(J34, "0.00") & K34 is aligned right and filled down, looks like this:

Testing Sorting
Coins Value
Pennies 0.01[-]
Nickels 0.05[-]
Dimes 0.10[-]
Quarters 0.25[1]
Halves 0.50[2]

Tapping into the class = “wikitable”, MakeWikiTable() can make any combination of sortable, collapsible, and collapsed tables. It invokes the class if the upper left table cell is not empty, and thus your (literally) first column is data vice row headers. There is a longstanding bug in the wikitable class that disables sorting if there is too much adornment given the table, no matter if the table is set as “sortable” or not. The combinations look like this in Wikipedia:

Only
Sorting
With Sorting
Collapsible
With Sorting
Collapsed
No Sorting
Collapsible
No Sorting
Collapsed
Coins Coins [hide] Coins [show] Coins [hide] Coins [show]

All these examples are available here. You’ll see the footnotes you created in Excel are at the bottom of the Wiki page. It looks different at Wiki Commons, but the code still works. Examples of a tables I made there with MakeWikiTable() are these. You’ll see it uses a sideways arrow instead of text for hide and show.

This is the MakeWikiTable code:

Public Sub MakeWikiTable()
Const DQ As String * 1 = """" 'double double double-quotes
Dim DataObj As New MSForms.DataObject
'Check VBE Tools/References Microsoft Forms 2.0 Object Library
Dim Rng As Range
Dim Cell As Range
Dim sReturn As String
Dim TextAlign As String
Dim CellContents As String
Dim UseRowHeaders As Boolean
Dim R As Long, C As Long
Dim IsSortable As Long, IsCollapsible As Long, IsCollapsed As Long
Dim Caption As String
Dim BgColor As String, FontColor As String

Set Rng = Selection
R = Rng.Rows.Count
C = Rng.Columns.Count

Caption = Rng.Cells(1, 1).Offset(-1, 0).Text 'Don't start the table in Row(1)
If Len(Rng.Cells(1.1)) = 0 Then
UseRowHeaders = True
IsSortable = vbNo
Else
IsSortable = MsgBox("Use Sortable Headers for your " & R & "-row by " & C & "-column table?", _
vbYesNoCancel + vbQuestion, "MRT's Wiki Table Maker")
If IsSortable = vbCancel Then Exit Sub
IsCollapsible = MsgBox("Do you want your table to collapse?", _
vbYesNoCancel + vbQuestion + vbDefaultButton1, "MRT's Wiki Table Maker")
If IsCollapsible = vbCancel Then Exit Sub
If IsCollapsible = vbYes Then
IsCollapsed = MsgBox("Do you want your table to load as collapsed?", _
vbYesNoCancel + vbQuestion + vbDefaultButton1, "MRT's Wiki Table Maker")
If IsCollapsed = vbCancel Then Exit Sub
End If
End If

If IsSortable = vbYes Or IsCollapsible = vbYes Then
sReturn = "{|class=" & DQ & "wikitable" & IIf(IsSortable = vbYes, " sortable", "") & _
IIf(IsCollapsible = vbYes, " collapsible", "") & _
IIf(IsCollapsed = vbYes, " collapsed", "") & DQ & _
" style=" & DQ & "margin: 1em auto 1em auto;" & DQ & vbNewLine
Else
sReturn = "{|border=" & DQ & "1" & DQ & " cellpadding=" & DQ & "5" & DQ & " cellspacing=" & DQ _
& "0" & DQ & " style=" & DQ & "margin: 1em auto 1em auto;" & DQ & vbNewLine
End If
sReturn = sReturn & "|+'''" & Caption & "'''" & vbNewLine
sReturn = sReturn & "|-" & vbNewLine

For Each Cell In Rng.Rows(1).Cells
CellContents = Cell.Text
If Len(CellContents) = 0 Then
CellContents = " "
Else
CellContents = Application.WorksheetFunction.Trim(CellContents)
End If
BgColor = HexColor(Cell.Interior.Color)
FontColor = HexColor(Cell.Font.Color)
sReturn = sReturn & "!scope=" & DQ & "col" & DQ & " style=" & DQ & "background-color:" & _
BgColor & "; color:" & FontColor & ";" & DQ & "| " & _
CellContents & vbNewLine
Next Cell

For R = 2 To Rng.Rows.Count
sReturn = sReturn & "|-" & vbNewLine
For C = 1 To Rng.Columns.Count

Set Cell = Rng.Cells(R, C)
CellContents = Cell.Text
If Len(CellContents) = 0 Then CellContents = " "

CellContents = MakeFracs(CellContents)
CellContents = Application.WorksheetFunction.Trim(CellContents)
CellContents = VBA.Replace(CellContents, "0 / 0", "zero / zero", 1, 1, vbTextCompare)

If C = 1 And UseRowHeaders Then
BgColor = HexColor(Cell.Interior.Color)
FontColor = HexColor(Cell.Font.Color)
sReturn = sReturn & "!scope=" & DQ & "row" & DQ & " style=" & DQ & "background-color:" & _
BgColor & "; color:" & FontColor & ";" & DQ & "| " & _
CellContents & vbNewLine
Else
Select Case Cell.HorizontalAlignment
Case xlGeneral
TextAlign = "left"
If IsNumeric(Cell.Value) Then TextAlign = "right"
If IsError(Cell.Value) Then TextAlign = "center"
Case xlLeft
TextAlign = "left"
Case xlCenter
TextAlign = "center"
Case xlRight
TextAlign = "right"
Case xlJustify
TextAlign = "center"
End Select

sReturn = sReturn & "|align=" & TextAlign & "| "
With Cell.Font
If .Italic Then sReturn = sReturn & "''"
If .Bold Then sReturn = sReturn & "'''"
End With

sReturn = sReturn & CellContents

With Cell.Font
If .Bold Then sReturn = sReturn & "'''"
If .Italic Then sReturn = sReturn & "''"
End With

sReturn = sReturn & vbNewLine
End If
Next C
Next R

sReturn = sReturn & IIf(IsSortable = vbYes, "|-class=sortbottom" & vbNewLine, "")
sReturn = sReturn & "|}" & vbNewLine

DataObj.SetText sReturn
DataObj.PutInClipboard

End Sub

Function HexColor(Color As Long) As String
Dim Red As String, Green As String, Blue As String
Red = VBA.Hex(Color And 255)
Green = VBA.Hex(Color \ 256 And 255)
Blue = VBA.Hex(Color \ 256 ^ 2 And 255)
If Len(Red) = 1 Then Red = "0" & Red
If Len(Green) = 1 Then Green = "0" & Green
If Len(Blue) = 1 Then Blue = "0" & Blue
HexColor = "#" & Red & Green & Blue
End Function

Note that the Caption is at Offset(1,0) from the your selected table. Wikipedia’s examples all use muted grays for the headers. The first two of the following are the provided colors, the third, aka “silver” is what I used above.

#EFEFEF #CFCFCF #C0C0C0

The macro should be invoked from a form instead of daisy-chained message boxes. I got lazy. The MakeFracs() function is here. If you want to put something in the upper-left cell, and still get row headers, put it in after you paste your table into Wikipedia.

… mrt
©¿©¬

Using HTML5 Fractions in Exported Excel Tables

HTML5 provides for fractional representation of halves, thirds, fourths, fifths, sixths, no sevenths, and eighths. Excel has a fractional number format. This post is about bringing these concepts together for exporting an Excel table into Wiki or HTML designs. The basic representations are:

Name Hex Dec Result
&frac12; U+000BD 189 ½
&frac13; U+02153 8531
&frac14; U+000BC 188 ¼
&frac15; U+02155 8533
&frac16; U+02159 8537
&frac18; U+0215B 8539
&frac23; U+02154 8532
&frac25; U+02156 8534
&frac34; U+000BE 190 ¾
&frac35; U+02157 8535
&frac38; U+0215C 8540
&frac45; U+02158 8536
&frac56; U+0215A 8538
&frac58; U+0215D 8541
&frac78; U+0215E 8542

 
The format for the name is &fracnd; where n is the numerator and d is the denominator. Thus &frac12; is a half, and &frac78; is seven-eighths. The HTML code representations for these are:

Result Named
Code
Hex
Code
Dec
Code
½ &frac12; &#X00BD; &#189;
&frac13; &#X2153; &#8531;
¼ &frac14; &#X00BC; &#188;
&frac15; &#X2155; &#8533;
&frac16; &#X2159; &#8537;
&frac18; &#X215B; &#8539;
&frac23; &#X2154; &#8532;
&frac25; &#X2156; &#8534;
¾ &frac34; &#X00BE; &#190;
&frac35; &#X2157; &#8535;
&frac38; &#X215C; &#8540;
&frac45; &#X2158; &#8536;
&frac56; &#X215A; &#8538;
&frac58; &#X215D; &#8541;
&frac78; &#X215E; &#8542;

 
In theory (more on “in practice” later) every representation in a row is equivalent. This is our test table to export to Wiki or HTML format:

D E F G H I J K L
1 1/1 1/2 1/3 1/4 1/5 1/6 1/7 1/8 1/80
2 2/1 2/2 2/3 2/4 2/5 2/6 2/7 2/8 2/8.
3 3/1 3/2 3/3 3/4 3/5 3/6 3/7 3/8 3/8A
4 4/1 4/2 4/3 4/4 4/5 4/6 4/7 4/8 6 4/8
5 5/1 5/2 5/3 5/4 5/5 5/6 5/7 5/8 7 5/8
6 6/1 6/2 6/3 6/4 6/5 6/6 6/7 6/8 8 6/8
7 7/1 7/2 7/3 7/4 7/5 7/6 7/7 7/8 9 7/8
8 8/1 8/2 8/3 8/4 8/5 8/6 8/7 8/8 10 8/8

 
Cell D1: =CHAR(32)&ROW()&”/”&COLUMN()-3, then fill down and right. The right hand column has a few test cases. I used that formulaic construction to keep Excel from doing the divisions. The Excel fractional format is “# ?/?” for single digit denominators. The intermediary space is important. It indicates that a fraction may follow, just as a forward slash indicates a fraction may be present. And a format of /?? is a fraction not translatable into HTML5. Turning these patterns into VBA, this is my MakeFracs() function. It checks that there is a slash, then that there is not a slash–digit–digit pattern, and finally that there is a “space–digits 1 through 7–slash–digits 2, 3, 4, 5, 6, 8” pattern to screen out sevenths and ninths. If all of those pass, it substitutes in the &fracnd; formulation for the fraction.

Function MakeFracs(Arg As String) As String
Dim sIN As String
Dim sOUT As String
Dim i As Long, j As Long
Dim n As Long, d As Long
Dim Fracs(1 To 15, 1 To 3) As String

Fracs(1, 1) = "½": Fracs(1, 2) = "½": Fracs(1, 3) = "½"
Fracs(2, 1) = "⅓": Fracs(2, 2) = "⅓": Fracs(2, 3) = "⅓"
Fracs(3, 1) = "¼": Fracs(3, 2) = "¼": Fracs(3, 3) = "¼"
Fracs(4, 1) = "⅕": Fracs(4, 2) = "⅕": Fracs(4, 3) = "⅕"
Fracs(5, 1) = "⅙": Fracs(5, 2) = "⅙": Fracs(5, 3) = "⅙"
Fracs(6, 1) = "⅛": Fracs(6, 2) = "⅛": Fracs(6, 3) = "⅛"
Fracs(7, 1) = "⅔": Fracs(7, 2) = "⅔": Fracs(7, 3) = "⅔"
Fracs(8, 1) = "⅖": Fracs(8, 2) = "⅖": Fracs(8, 3) = "⅖"
Fracs(9, 1) = "¾": Fracs(9, 2) = "¾": Fracs(9, 3) = "¾"
Fracs(10, 1) = "⅗": Fracs(10, 2) = "⅗": Fracs(10, 3) = "⅗"
Fracs(11, 1) = "⅜": Fracs(11, 2) = "⅜": Fracs(11, 3) = "⅜"
Fracs(12, 1) = "⅘": Fracs(12, 2) = "⅘": Fracs(12, 3) = "⅘"
Fracs(13, 1) = "⅚": Fracs(13, 2) = "⅚": Fracs(13, 3) = "⅚"
Fracs(14, 1) = "⅝": Fracs(14, 2) = "⅝": Fracs(14, 3) = "⅝"
Fracs(15, 1) = "⅞": Fracs(15, 2) = "⅞": Fracs(15, 3) = "⅞"

i = VBA.InStr(1, Arg, "/", vbTextCompare)
If i = 0 Then 'there's no fraction
MakeFracs = Arg
ElseIf Mid$(Arg, i, 3) Like "/##" Then 'not HTML5
MakeFracs = Arg
ElseIf Mid$(Arg, i - 2, 4) Like " [1-7]/[234568]" Then
sOUT = Mid$(Arg, i - 1, 3)
n = VBA.Val(Left$(sOUT, 1)) 'numerator
d = VBA.Val(Right$(sOUT, 1)) 'denominator
If n < d Then If d Mod n = 0 Then d = d / n n = 1 ElseIf d Mod 2 = 0 And n Mod 2 = 0 Then d = d / 2 n = n / 2 End If sIN = "&frac" & n & d & ";" For j = 1 To 15 If Fracs(j, 1) = sIN Then sIN = Fracs(j, 2) '<-or Fracs(j, 3) for HEX Exit For End If Next j MakeFracs = VBA.Replace(Arg, sOUT, sIN) Else MakeFracs = Arg End If Else MakeFracs = Arg End If End Function


 
At least that's all I wanted it to do. In practice, Wikipedia and WordPress seem to be not fully onboard with HTML5 and do not handle all fifteen &fracnd; formats (I confirmed Firefox does). That added "j-loop" in the middle translates the &fracnd;'s into Dec code. This works fine, though it's a step back from HTML5. Option is given to use Hex if desired. Your Excel table then looks like this:

N O P Q R S T U V
1 1/1 &#189; &#8531; &#188; &#8533; &#8537; 1/7 &#8539; 1/80
2 2/1 2/2 &#8532; &#189; &#8534; &#8531; 2/7 &#188; &#188;.
3 3/1 3/2 3/3 &#190; &#8535; &#189; 3/7 &#8540; &#8540;A
4 4/1 4/2 4/3 4/4 &#8536; &#8532; 4/7 &#189; 6 &#189;
5 5/1 5/2 5/3 5/4 5/5 &#8538; 5/7 &#8541; 7 &#8541;
6 6/1 6/2 6/3 6/4 6/5 6/6 6/7 &#190; 8 &#190;
7 7/1 7/2 7/3 7/4 7/5 7/6 7/7 &#8542; 9 &#8542;
8 8/1 8/2 8/3 8/4 8/5 8/6 8/7 8/8 10 8/8

 
Where N1: =MakeFracs(D1) filled down and right. Arranged that way you can see the HTML5 design thoughts. The very ugly website would look like this:

1/1 ½ ¼ 1/7 1/80
2/1 2/2 ½ 2/7 ¼ ¼.
3/1 3/2 3/3 ¾ ½ 3/7 ⅜A
4/1 4/2 4/3 4/4 4/7 ½ 6 ½
5/1 5/2 5/3 5/4 5/5 5/7 7 ⅝
6/1 6/2 6/3 6/4 6/5 6/6 6/7 ¾ 8 ¾
7/1 7/2 7/3 7/4 7/5 7/6 7/7 9 ⅞
8/1 8/2 8/3 8/4 8/5 8/6 8/7 8/8 10 8/8

 
Frankly, I'm not sure that this is an improvement. You'll come across Wikipedia editors, however, who are convinced of it. I thought about adding a trailing space, as in MakeFracs = VBA.Replace(Arg, sOUT, sIN & Chr(32)), but for every time I wanted to, I thought of an example where I didn't, and the logic got very convoluted. Better I decided to put the space in the table where wanted and not in the function. My HTML tablemaker is here, but it's being overcome by the hard steady march of technology. Wiki and CSS tablemakers are coming up. I used MakeFracs() in the above. No fractions were harmed in the making of this post.

…mrt
©¿©¬

Testing for Empty Cells

To test for empty cells, use the IsEmpty function. IsEmpty takes one argument, a variable, and returns True if that variable contains nothing (Technically, I think it returns True if the variable is uninitialized). While it’s true that you can pass variables to IsEmpty, you can also pass object’s properties, specifically the Value property of the Range object.

Many times you will see programmers test for a zero length string, like this

If Range(“A10”).Value = “” Then

In 99% of the cases, that will work. However, if the cell contains a single quote and nothing else, then it will contain a zero length string, but will not really be empty. To test for true emptiness, use IsEmpty on the Value property.

Sub TestForEmpty()

Dim sPrompt As String
Dim rRng As Range

Set rRng = Sheet1.Range("A10")
sPrompt = "Range contains "

rRng.ClearContents

MsgBox sPrompt & "nothing = " & IsEmpty(rRng.Value) & vbNewLine & _
sPrompt & "a zero length string = " & CBool(rRng.Value = "")

rRng.Value = "'" 'single quote

MsgBox sPrompt & "nothing = " & IsEmpty(rRng.Value) & vbNewLine & _
sPrompt & "a zero length string = " & CBool(rRng.Value = "")

End Sub

Update: A newsgroup post by Otto Moehrbach prompted me to look a little deeper into how IsEmpty works. I wanted to determine why a cell with a formula that returns an empty string behaves differently than an empty cell. I set up a watch for A1 and B1 to see what was going on. A1 contains the formula =”” and B1 contains nothing at all.

watch window showing status of A1 and B1

A1 is a Variant/String and B1 is a Variant/Empty which obviously accounts for the difference. There’s nothing too shocking here, it’s just an interesting glimpse into the inner workings of VBA. Although the “interesting” part is debatable.