Add-in function dialog boxes


Posted by Russell on September 10, 1999 7:25 AM

I have an add-in function (see below) in which
there is a dialog box
that asks the user to put in values for the variables "enter_range" and "med_count" (see below). My question is what I need
to do in order to add instructional text to the dialog
box. For example, I want the dialog box to say
"for med_count enter 1 to calculate median and 0
to calculate number of observations"

The following is my function:

Function testing(enter_range, med_count)
'enter_range is for user to enter range of cells
'med_count is for user to enter 1 to calculate
'median and 0 to calculate number of observations
Dim mkrange As Range
Set mkrange = enter_range
Number = med_count

If Number = 0 Then
testing = Application.Count(mkrange)
ActiveCell.Application.FixedDecimalPlaces = 0

End If

If Number = 1 Then
testing = Application.Median(mkrange)
Selection.NumberFormat = "0.0%"
End If

End Function

Posted by Ivan Moala on September 11, 1999 2:03 AM

Russell
When I first wanted to enter comments etc for UDF
I made up my own via Userforms and had it activate
via the application worksheet change event. This
proved to be hard work sometimes so the function
had to be worth while i.e if I couldn't find an
easier way or method I would do this.
However I have found a way thanks to Laurent Longre,
My thanks to him for his expertise.
The following routine has been adapted from his,
I have also fixed your formating.
The routine loads automatically and registers your
"testing" routine with the comments etc.
Copy & paste the following:

<START>
Const Lib = """c:\windows\system\user32.dll"""
Option Base 1

Function testing(enter_range, med_count As Integer)
'enter_range is for user to enter range of cells
'med_count is for user to enter 1 to calculate
'median and 0 to calculate number of observations
Dim mkrange As Range
Dim AC As String

Set mkrange = enter_range
Number = med_count

If Number = 0 Then
testing = Format(Application.Count(mkrange), "0")

End If

If Number = 1 Then
testing = Format(Application.Median(mkrange), "0.0%")
End If

End Function

Sub Auto_open()
'Adapted from Laurent Longre's Routine
'by Ivan Moala: All credit to Laurent Longre
Register "testing", 3, "Range,Median or Count", 1, "MyUDF", _
"for med_count enter 1 to calculate median and 0 to calculate number of observations", _
"""Evaluate"",""Option 1 or 0 """, "CharPrevA"

End Sub


Sub Register(FunctionName As String, NbArgs As Integer, _
Args As String, MacroType As Integer, Category As String, _
Descr As String, DescrArgs As String, FLib As String)

Application.ExecuteExcel4Macro _
"REGISTER(" & Lib & ",""" & FLib & """,""" & String(NbArgs, "P") _
& """,""" & FunctionName & """,""" & Args & """," & MacroType _
& ",""" & Category & """,,,""" & Descr & """," & DescrArgs & ")"

End Sub


Sub Auto_close()

Dim FName, FLib
Dim I As Integer
FName = Array("testing")
FLib = Array("CharPrevA")
I = 1
With Application
.ExecuteExcel4Macro "UNREGISTER(" & FName(I) & ")"
.ExecuteExcel4Macro "REGISTER(" & Lib & _
",""CharPrevA"",""P"",""" & FName(I) & """,,0)"
.ExecuteExcel4Macro "UNREGISTER(" & FName(I) & ")"
End With

End Sub
<END>


Regards


Ivan




Posted by Russell on September 14, 1999 5:48 AM

Wow! Thanks. The method that you suggested for doing the formatting does not allow the user to change the formatting. In my situation I'm looking for there to be a default formatting but that the end user should be able to change the formatting manually, if necessary. For instance, in most cases the user will need to format as a percentage, going out one decimal point. However, there will be instances in which a regular number formatting will be more appropriate.