problem redim an array


Posted by Edward C. on April 04, 2001 6:41 AM

Hi,
I have an array which gets dimensioned in my general declaration section of my code and then gets redim'ed inside one of my sub's.
I am getting a compile error related to the array "sChartSheetNames". It does not seem to like the way I have declared it. I do not have much experience with going from sub to sub with arrays. Can anyone tell me what I am doing wrong. If anyone has the O'Reilly book by Steven Roman, I am following his example on page#265 and 266 ex#18-4 and ex#18-5.
I have tried to paste in the relevent code below, using a dotted line to separate the different sections ( ie: subs, etc ).
Thanks a lot,
Edward
ps. ( i have listed codes in order of most revelent )

-------------------------------------------------------
Option Explicit
Dim cChartSheets As Integer
Public sChartSheetNames As String
-------------------------------------------------------
Private Sub cmdCancel_Click()
Unload Me
End Sub
-------------------------------------------------------
Private Sub cmdPrint_Click()
PrintSelectedChartSheets
Unload Me
End Sub
-------------------------------------------------------
Public Sub UserForm_Initialize()
Dim ws As Object ' Worksheet
ReDim sChartSheetNames(1 To 10)

lstChartSheets.Clear
cChartSheets = 0
For Each ws In ActiveWorkbook.Charts
cChartSheets = cChartSheets + 1

'Redimension arrays if necessary
If UBound(sChartSheetNames) < cChartSheets Then
ReDim Preserve sChartSheetNames(1 To cChartSheets + 5)
End If

' Save name of chart sheet
sChartSheetNames(cChartSheets) = ws.Name

' Add chart sheet name to list box
lstChartSheets.AddItem sChartSheetNames(cChartSheets)
Next
End Sub
-------------------------------------------------------
Public Sub PrintChartSheet()
dlgPrintChartSheet.Show
End Sub
-------------------------------------------------------
Public Sub PrintSelectedChartSheets()
Dim i As Integer
Dim bNoneSelected As Boolean

bNoneSelected = True

If cChartSheets = 0 Then
MsgBox "There are no Chart Sheets in this workbook.", vbExclamation
Exit Sub
Else
For i = 0 To lstChartSheets.ListCount - 1
If lstSheets.Selected(i) Then
bNoneSelected = False
' List box is 0-based, arrays are 1-based
ActiveWorkbook.Charts(sChartSheetNames(i + 1)).PrintOut
End If
Next
End If

If bNoneSelected Then
MsgBox "No Chart Sheets have been selected from the list box.", vbExclamation
End If

End Sub
-------------------------------------------------------
The End.



Posted by Tim Francis-Wright on April 04, 2001 12:38 PM

lstChartSheets.Clear cChartSheets = 0 For Each ws In ActiveWorkbook.Charts cChartSheets = cChartSheets + 1 'Redimension arrays if necessary If UBound(sChartSheetNames) < cChartSheets Then ReDim Preserve sChartSheetNames(1 To cChartSheets + 5) End If ' Save name of chart sheet sChartSheetNames(cChartSheets) = ws.Name ' Add chart sheet name to list box lstChartSheets.AddItem sChartSheetNames(cChartSheets) Next


VBA won't let you declare a public array in an
object module (like the modules associated with
forms). You can, however, make that declaration
in a regular module (assuming you do not include
Option Private Module in that code).

You'll need to make one change:
Public sChartSheetNames() As String
' otherwise, VBA doesn't set it up as an array.

Hope this helps.