Too Many Cell Formats


Posted by Tony Delmin on October 18, 2000 7:34 PM

Every once in a while I come across an Excel that gives me the error message 'Too Many Cell Formats' when I try to open it. Is there something I can do to open this file to get to the data?

Posted by Ben O. on October 19, 2000 11:19 AM

This is from the Microsoft Knowledge Base. Check out support.microsoft.com for more info. I hope this helps:

XL2000: "Too Many Different Cell Formats" Error Formatting Cell or Range

--------------------------------------------------------------------------------
The information in this article applies to:

Microsoft Excel 2000

--------------------------------------------------------------------------------


SYMPTOMS
When you format a cell or a range of cells in Microsoft Excel, you may receive the following error message:

Too many different cell formats.

CAUSE
This problem occurs when the workbook contains more than approximately 4,000 different combinations of cell formats. A combination is defined as a unique set of formatting elements that are applied to a cell. A combination includes all font formatting (for example: typeface, font size, italic, bold, and underline), borders (for example: location, weight, and color), cell patterns, number formatting, alignment, and cell protection.

NOTE: If two or more cells share exactly the same formatting, they use one formatting combination. However, if there are any differences in formatting between the cells, each cell uses a different combination.

RESOLUTION
To resolve this problem, simplify the formatting in the workbook. For example, the following are suggestions for simplifying formatting:

Use a standard font.

Using the same font for all cells reduces the number of formatting combinations.


If you use borders in a worksheet, use them consistently.

NOTE: If you apply a border to the right side of a cell, it is not necessary to apply a border to the left side of the cell that is to the right because the borders overlap.


If you apply patterns to the cells, remove the patterns by clicking No Color in the Patterns tab of the Format Cells dialog box.

NOTE: After you simplify or standardize the formatting in the workbook, save, close, and then reopen the workbook before you apply additional cell formatting.

MORE INFORMATION
In most cases, the limit of approximately 4,000 different formatting combinations for a single workbook is sufficient. This problem is likely to occur only when the workbook contains a large number of worksheets that use different formatting, or when a large number of cells are all formatted differently.

Additional query words: XL2000

Keywords : kberrmsg _IK
Version : WINDOWS:2000
Platform : WINDOWS
Issue type : kbprb
Technology :



Posted by Ivan Moala on October 19, 2000 8:24 PM

To see these format or delete them try this routine;
'POWER PROGRAMMING TECHNIQUE

'By Leo Heuser

'This procedure provides a workaround for the glaring lack of accessibility
'in VBA for manipulating custom number formats. To do this, it hacks into
'the Number Format dialog box with SendKeys. It loops through each item,
'including those custom number formats that have been orphaned from the
'worksheet. The dialog box flickers upon each opening, but it works! If
'anyone comes up with a way to eliminate the flicker, let me know.

Sub DeleteUnusedCustomNumberFormats()
Dim Buffer As Object
Dim Sh As Object
Dim SaveFormat As Variant
Dim fFormat As Variant
Dim nFormat() As Variant
Dim xFormat As Long
Dim Counter As Long
Dim Counter1 As Long
Dim Counter2 As Long
Dim StartRow As Long
Dim EndRow As Long
Dim Dummy As Variant
Dim pPresent As Boolean
Dim NumberOfFormats As Long
Dim Answer
Dim c As Object
Dim DataStart As Long
Dim DataEnd As Long
Dim AnswerText As String

NumberOfFormats = 1000
ReDim nFormat(0 To NumberOfFormats)
AnswerText = "Do you want to delete unused custom formats from the workbook?"
AnswerText = AnswerText & Chr(10) & "To get a list of used and unused formats only, choose No."
Answer = MsgBox(AnswerText, 259)
If Answer = vbCancel Then GoTo Finito

Application.ScreenUpdating = False
On Error GoTo Finito
Worksheets.Add.Move after:=Worksheets(Worksheets.Count)
Worksheets(Worksheets.Count).Name = "CustomFormats"
Worksheets("CustomFormats").Activate
Set Buffer = Range("A2")
Buffer.Select
nFormat(0) = Buffer.NumberFormatLocal
Counter = 1
Do
SaveFormat = Buffer.NumberFormatLocal
Dummy = Buffer.NumberFormatLocal
DoEvents
SendKeys "{tab 3}{down}{enter}"
Application.Dialogs(xlDialogFormatNumber).Show Dummy
nFormat(Counter) = Buffer.NumberFormatLocal
Counter = Counter + 1
Loop Until nFormat(Counter - 1) = SaveFormat

ReDim Preserve nFormat(0 To Counter - 2)

Range("A1").Value = "Custom formats"
Range("B1").Value = "Formats used in workbook"
Range("C1").Value = "Formats not used"
Range("A1:C1").Font.Bold = True

StartRow = 3
EndRow = 16384

For Counter = 0 To UBound(nFormat)
Cells(StartRow, 1).Offset(Counter, 0).NumberFormatLocal = nFormat(Counter)
Cells(StartRow, 1).Offset(Counter, 0).Value = nFormat(Counter)
Next Counter

Counter = 0
For Each Sh In ActiveWorkbook.Worksheets
If Sh.Name = "CustomFormats" Then Exit For
For Each c In Sh.UsedRange.Cells
fFormat = c.NumberFormatLocal
If Application.WorksheetFunction.CountIf(Range(Cells(StartRow, 2), Cells(EndRow, 2)), fFormat) = 0 Then
Cells(StartRow, 2).Offset(Counter, 0).NumberFormatLocal = fFormat
Cells(StartRow, 2).Offset(Counter, 0).Value = fFormat
Counter = Counter + 1
End If
Next c
Next Sh

xFormat = Range(Cells(StartRow, 2), Cells(EndRow, 2)).Find("").Row - 2
Counter2 = 0
For Counter = 0 To UBound(nFormat)
pPresent = False
For Counter1 = 1 To xFormat
If nFormat(Counter) = Cells(StartRow, 2).Offset(Counter1, 0).NumberFormatLocal Then
pPresent = True
End If
Next Counter1
If pPresent = False Then
Cells(StartRow, 3).Offset(Counter2, 0).NumberFormatLocal = nFormat(Counter)
Cells(StartRow, 3).Offset(Counter2, 0).Value = nFormat(Counter)
Counter2 = Counter2 + 1
End If
Next Counter
With ActiveSheet.Columns("A:C")
.AutoFit
.HorizontalAlignment = xlLeft
End With
If Answer = vbYes Then
DataStart = Range(Cells(1, 3), Cells(EndRow, 3)).Find("").Row + 1
DataEnd = Cells(DataStart, 3).Resize(EndRow, 1).Find("").Row - 1
On Error Resume Next
For Each c In Range(Cells(DataStart, 3), Cells(DataEnd, 3)).Cells
ActiveWorkbook.DeleteNumberFormat (c.NumberFormat)
Next c
End If
Finito:
Application.ScreenUpdating = True
Set c = Nothing
Set Sh = Nothing
Set Buffer = Nothing
End Sub


Ivan