Input/Message/List box style that goes to sheet


Posted by Danny on July 06, 2000 7:06 AM

Is there an application that if you say click a button an input/message or list style box pops up with a list of sheet names, so all you have to do is highlight it and it goes to that page.

Any suggestions.

Thank you,

Danny

Posted by Danny on July 07, 0100 8:35 AM

Macro to do this?

Not that I'm Macro mad or anything, But Is there a Macro that can do this??

Thanks for the advice, unfortunatly some of the people that use my spreadsheets seem to overlook that even though I tell them.

Danny.

Posted by mads on July 07, 0100 11:00 AM

Perhaps someone else can help.

Must be possible, but I can't write the code without researching it. Perhaps someone else can help.
mads

Posted by mads on July 06, 0100 11:02 AM

Right click on any of the sheet navigation arrows (at the left hand side of the sheet tabs) and a list of the sheets will appear.
mads



Posted by Ryan on July 07, 0100 12:12 PM

Re: Macro to do this?

Danny,
I modified this code from www.j-walk.com. It creates a userform on the fly and then deletes it when done. You'll have to set up the button, either on a sheet, or on a commandbar to run the macro. Let me know how it works!

Ryan

Option Explicit

'Passed back to the function from the UserForm
Public GETOPTION_RET_VAL As Variant

Sub GoToSheet()
Dim Ops() As String
Dim NumOfSheets As Integer
Dim i As Integer
Dim UserChoice As Variant
' Create an array of month names
NumOfSheets = Sheets.Count
ReDim Ops(1 To NumOfSheets)
For i = 1 To NumOfSheets
Ops(i) = Sheets(i).Name
Next i
UserChoice = GetOption(Ops, 1, "Select a month")
If UserChoice = False Then
Range("A6") = ""
Else
Sheets(Ops(UserChoice)).Select
End If
End Sub


Function GetOption(OpArray, Default, Title)
Dim TempForm 'As VBComponent
Dim NewOptionButton As Msforms.OptionButton
Dim NewCommandButton1 As Msforms.CommandButton
Dim NewCommandButton2 As Msforms.CommandButton
Dim TextLocation As Integer
Dim X As Integer, i As Integer, TopPos As Integer
Dim MaxWidth As Long
Dim WasVisible As Boolean

' Hide VBE window to prevent screen flashing
Application.VBE.MainWindow.Visible = False

' Create the UserForm
Set TempForm = ThisWorkbook.VBProject.VBComponents.Add(3)
TempForm.Properties("Width") = 800

' Add the OptionButtons
TopPos = 4
MaxWidth = 0 'Stores width of widest OptionButton
For i = LBound(OpArray) To UBound(OpArray)
Set NewOptionButton = TempForm.Designer.Controls.Add("forms.OptionButton.1")
With NewOptionButton
.Width = 800
.Caption = OpArray(i)
.Height = 15
.Left = 8
.Top = TopPos
.Tag = i
.AutoSize = True
If Default = i Then .Value = True
If .Width > MaxWidth Then MaxWidth = .Width
End With
TopPos = TopPos + 15
Next i

' Add the Cancel button
Set NewCommandButton1 = TempForm.Designer.Controls.Add("forms.CommandButton.1")
With NewCommandButton1
.Caption = "Cancel"
.Height = 18
.Width = 44
.Left = MaxWidth + 12
.Top = 6
End With

' Add the OK button
Set NewCommandButton2 = TempForm.Designer.Controls.Add("forms.CommandButton.1")
With NewCommandButton2
.Caption = "OK"
.Height = 18
.Width = 44
.Left = MaxWidth + 12
.Top = 28
End With

' Add event-hander subs for the CommandButtons
With TempForm.CodeModule
X = .CountOfLines
.InsertLines X + 1, "Sub CommandButton1_Click()"
.InsertLines X + 2, " GETOPTION_RET_VAL=False"
.InsertLines X + 3, " Unload Me"
.InsertLines X + 4, "End Sub"

.InsertLines X + 5, "Sub CommandButton2_Click()"
.InsertLines X + 6, " Dim ctl"
.InsertLines X + 7, " GETOPTION_RET_VAL = False"
.InsertLines X + 8, " For Each ctl In Me.Controls"
.InsertLines X + 9, " If ctl.Tag <> """" Then If ctl Then GETOPTION_RET_VAL = ctl.Tag"
.InsertLines X + 10, " Next ctl"
.InsertLines X + 11, " Unload Me"
.InsertLines X + 12, "End Sub"
End With

' Adjust the form
With TempForm
.Properties("Caption") = Title
.Properties("Width") = NewCommandButton1.Left + NewCommandButton1.Width + 10
If .Properties("Width") < 160 Then
.Properties("Width") = 160
NewCommandButton1.Left = 106
NewCommandButton2.Left = 106
End If
.Properties("Height") = TopPos + 24
End With

' Show the form
VBA.UserForms.Add(TempForm.Name).Show

' Delete the form
ThisWorkbook.VBProject.VBComponents.Remove VBComponent:=TempForm

' Pass the selected option back to the calling procedure
GetOption = GETOPTION_RET_VAL
End Function