Visual Basic (VB) versions 4/5/6 and Visual Basic for Applications (VBA) have many similarities, so much of the VBA-specific information above applies directly to VB. Note especially the remarks about array conventions and string handling. Neither VBA nor VB 4 provides a mechanism for passing procedure arguments to a DLL. To overcome this the following mechanism is suggested: If you are a Fortran user, take the appropriate jacket routine from the files provided. Typically the jacket routine looks like:
SUBROUTINE N_C05ADF(A,B,EPS,ETA,X,IFAIL) DOUBLE PRECISION A DOUBLE PRECISION B DOUBLE PRECISION EPS DOUBLE PRECISION ETA DOUBLE PRECISION F EXTERNAL F DOUBLE PRECISION X INTEGER IFAIL CALL C05ADF (A,B,EPS,ETA,F,X,IFAIL) END
VB and VBA are interfaced to a routine, which has a similar parameter list to the original, but with the subroutine and function arguments removed. In this case the user-provided function F is removed. The new routine simply calls the original NAG routine, but with fixed name arguments for the functions and subroutines used as parameters. To use the jacket routine the user has to create it as a DLL. This is explained by example.
First compile a typical user function F using the CVF compiler, as the first step to producing a DLL exporting F:
DF /c /Op /Ox /Tf F.FOR Link the function: LINK @F.LNK where F.LNK is the file /DLL /OUT:F.DLL F.OBJ /EXPORT:_F@4 /EXPORT:_F=_F@4 /EXPORT:F=_F@4
Ignoring the detail for a moment, this will produce two files in addition to the DLL in F.DLL: an import library, F.IMP and a library file F.LIB. The latter will be used to produce a DLL containing N_C05ADF as follows:
Compile the routine: DF /c /Op /Ox /Tf N_C05ADF.FOR Link the routine: LINK @NAG.LNK where NAG.LNK is the file: /DLL /OUT:NAG.DLL f.lib DLL20DDS.LIB N_C05ADF.OBJ /EXPORT:_N_C05ADF@24 /EXPORT:Alias=_N_C05ADF@24
Points to note here are the /EXPORTS lines and the use of the library files. The library files tell the DLL where to find symbols which it would otherwise be unable to resolve. In this example it is told to find C05ADF in a DLL named DLL20DDS and that it can find the user-defined function F in a DLL called F.DLL. This information is written to the library files at the time of creation. The /EXPORT line tells the DLL to export the named symbol. Note however that this symbol consists firstly of an underscore, then the routine name followed immediately by an @ sign and a number. The number conveys information about the number and type of the parameters and is used by the CVF compiler. This name is termed the 'decorated name'. The number may be determined by using the utility DUMPBIN:
DUMPBIN /SYMBOLS N_C05ADF.OBJ
Because the decorated name may be cumbersome to use, the second /EXPORT line enables another name 'Alias' to be used instead.
VB, version 5 introduced a mechanism for passing procedure arguments to DLLs, the AddressOf function. To see how this works, consider the following example, which illustrates the use of E04UCF by translating the NAG example program into VB, version 5:
Option Explicit Private Sub Command1_Click( ) 'Starting values of variables x(1) = 1 x(2) = 5 x(3) = 5 x(4) = 1 'Bounds of the variables bl(1) = 1: bu(1) = 5 bl(2) = 1: bu(2) = 5 bl(3) = 1: bu(3) = 5 bl(4) = 1: bu(4) = 5 'Coefficients of the general linear constraint a(1, 1) = 1 a(1, 2) = 1 a(1, 3) = 1 a(1, 4) = 1 'Bounds of the general linear constraint bl(n + 1) = -1E+21: bu(n + 1) = 20 'Bounds of the nonlinear constraints bl(n + nclin + 1) = -1E+21: bu(n + nclin + 1) = 40 bl(n + nclin + 2) = 25: bu(n + nclin + 2) = 1E+21 'Solve the problem Label1.Caption = "" ifail = +1 mode=1 Call X04ACF(NOUT, "\results.lis", 12, mode, ifail) 'X04ACF opens the file \results.lis and connects it to Fortran channel 6 'Note that the "12" refers to the length of the string "\results.lis" Call E04UEF("NoList", 6) Call E04UEF("Major Print Level=9", 19) Call E04UEF("Minor Print Level=9", 19) Call E04UEF("Der=0", 5) ifail = +1 Call E04UCF(n, nclin, ncnln, lda, ldcj, ldr, a(1, 1), bl(1), bu(1), _ AddressOf confun, AddressOf objfun, iter, istate(1), c(1), cjac(1, 1), _ clamda(1), objf, objgrd(1), r(1, 1), x(1), iwork(1), liwork, work(1), _ lwork, iuser, user, ifail) Label1.Caption = "E04UCF Example Program Results" + Chr(13) + _ "------------------------------------------------------" + Chr(13) + _ "Value of objective function:"+Str(objf)+Chr(13)+"x1 = " + Str(x(1)) + _ Chr(13)+"x2 = "+Str(x(2)) + Chr(13) + "x3 = " + Str(x(3)) + Chr(13) + _ "x4 = " + Str(x(4)) + Chr(13) + "IFAIL = " + Str(ifail) Call X04ADF(NOUT, ifail) 'X04ADF closes the file on channel 6 (NOUT) End Sub Option Explicit Option Base 1 Global Const _ n As Long = 4, _ nclin As Long = 1, _ ncnln As Long = 2, _ NOUT = 6, _ ldr As Long = n, _ lda As Long = nclin, _ ldcj As Long = ncnln, _ liwork As Long = 100, _ lwork As Long = 1000 Public _ a(lda, n) As Double, _ bl(n + nclin + ncnln) As Double, _ bu(n + nclin + ncnln) As Double, _ iter As Long, _ istate(n + nclin + ncnln) As Long, _ c(ncnln) As Double, _ cjac(ldcj, n) As Double, _ clamda(n + nclin + ncnln) As Double, _ objf As Double, _ objgrd(n) As Double, _ r(ldr, n) As Double, _ x(n) As Double, _ iwork(liwork) As Long, _ work(lwork) As Double, _ iuser As Long, _ user As Double, _ ifail As Long, _ mode As Long #If Win32 Then Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" ( _ ByRef hpvDest As Any, ByVal hpvSource As Any, ByVal cbCopy As Long) #Else Declare Sub CopyMemory Lib "KERNEL" Alias "hmemcpy" ( _ ByRef hpvDest As Any, ByVal hpvSource As Any, ByVal cbCopy As Long) #End If Declare Sub E04UCF Lib "DLL20DD.DLL" _ (n As Long, nclin As Long, ncnln As Long, lda As Long, ldcj As Long, _ ldr As Long, a As Double, bl As Double, bu As Double, ByVal confun As Any, _ ByVal objfun As Any, iter As Long, istate As Long, con As Double, _ cjac As Double, clamda As Double, objf As Double, objgrd As Double, _ r As Double, x As Double, iwork As Long, liwork As Long, work As Double, _ lwork As Long, iuser As Long, user As Double, ifail As Long) Declare Sub E04UEF Lib "DLL20DD.DLL" (ByVal optparam As String, _ ByVal stringlength As Long) Declare Sub X04ACF Lib "DLL20DD.DLL" (NOUT As Long, ByVal file As String, _ ByVal length_string As Long, mode As Long, ifail As Long) Declare Sub X04ADF Lib "DLL20DD.DLL" (NOUT As Long, ifail As Long) Sub objfun(mode As Long, nb As Long, ByVal ptr_x As Long, objf As Double, _ ByVal ptr_objgrd As Long, nstate As Long, iuser As Long, user As Double)
'Routine to evaluate objective function and its 1st derivatives.
'..Local variables. Dim x(n) As Double 'values for which the function is to be evaluated Dim objgrd(n) As Double 'first derivatives of the function Dim address As Long 'Address to fetch/store data Dim i As Integer 'counter 'Copy elements pointed to by ptr_x into local array x. For i = 1 To n address = ptr_x + 8 * (i - 1) Call CopyMemory(x(i), address, 8) Next i 'Calculate value of objective function if necessary. If mode = 0 Or mode = 2 Then objf = x(1)*x(4)*(x(1) + x(2) + x(3)) + x(3) 'Calculate values of 1st derivatives if necessary. If mode = 1 Or mode = 2 Then objgrd(1) = x(4) * (2 * x(1) + x(2) + x(3)) objgrd(2) = x(1) * x(4) objgrd(3) = x(1) * x(4) + 1 objgrd(4) = x(1) * (x(1) + x(2) + x(3)) 'Copy values to the memory pointed to by ptr_objgrd. For i = 1 To n address = ptr_objgrd + 8 * (i - 1) Call CopyMemory(ByVal (address), VarPtr(objgrd(i)), 8) Next i End If End Sub Sub confun(mode As Long, ncnlnb As Long, nb As Long, ldcjb As Long, _ ByVal ptr_needc As Long, ByVal ptr_x As Long, ByVal ptr_c As Long, _ ByVal ptr_cjac As Long, nstate As Long, iuser As Long, user As Double)
'Routine to evaluate the nonlinear constraints and their 1st derivatives.
'..Local variables.. Dim x(n) As Double 'Values for which the constraints are to be evaluated. Dim needc(ncnln) As Long 'If needc(i)>0 then data on the ith constraint is required. Dim con As Double 'Value of a constraint. Dim cjac(n) As Double 'First derivatives of a constraint. Dim address As Long 'Address to fetch/store data. Dim store As Double 'Data element to store. Dim i, j As Integer 'Counters. 'copy elements pointed to by ptr_x into local array x For i = 1 To n address = ptr_x + 8 * (i - 1) Call CopyMemory(x(i), ByVal address, 8) Next i 'copy elements pointed to by ptr_needc into local array needc For i = 1 To ncnln address = ptr_needc + 4 * (i - 1) Call CopyMemory(needc(i), address, 4) Next i If nstate = 1 Then 'First call to CONFUN. Set all Jacobian elements to zero. 'Note that this will only work when 'Derivative Level = 3' '(the default; see Section 11.2). store = 0 For i = 1 To ncnln For j = 1 To n address = ptr_cjac + 8 * ncnln * (j - 1) + 8 * (i - 1) Call CopyMemory(ByVal (address), VarPtr(store), 8) Next Next End If If needc(1) > 0 Then If mode = 0 Or mode = 2 Then 'Value of first constraint is required con = x(1) * x(1) + x(2) * x(2) + x(3) * x(3) + x(4) * x(4) Call CopyMemory(ByVal (ptr_c), VarPtr(con), 8) End If If mode = 1 Or mode = 2 Then 'Derivatives of first constraint required cjac(1) = 2 * x(1) cjac(2) = 2 * x(2) cjac(3) = 2 * x(3) cjac(4) = 2 * x(4) For i = 1 To n address = ptr_cjac + 8 * ncnln * (i - 1) Call CopyMemory(ByVal (address), VarPtr(cjac(i)), 8) Next End If End If If needc(2) > 0 Then If mode = 0 Or mode = 2 Then 'Value of second constraint is required con = x(1) * x(2) * x(3) * x(4) Call CopyMemory(ByVal (ptr_c + 8), VarPtr(con), 8) End If If mode = 1 Or mode = 2 Then 'Derivatives of second constraint required cjac(1) = x(2) * x(3) * x(4) cjac(2) = x(1) * x(3) * x(4) cjac(3) = x(1) * x(2) * x(4) cjac(4) = x(1) * x(2) * x(3) For i = 1 To n address = ptr_cjac + 8 * ncnln * (i - 1) + 8 Call CopyMemory(ByVal (address), VarPtr(cjac(i)), 8) Next End If End If End Sub
The salient features to note here are that the user functions CONFUN and OBJFUN are written in VB. They are passed into the DLL by using the AddressOf operator. These routines must be programmed in such a way that they can take information from the Fortran DLL and, where appropriate, write information back to the Fortran routine. The API function CopyMemory is required to do this. Its first parameter is the base address of the destination, the second parameter the base address of the source to be copied over and the third parameter the number of bytes to be copied. The task of writing information back to the Fortran routine requires a means of getting the address of a VB variable. This is achieved by using an undocumented (and therefore formally unsupported) feature of VB, the VarPtr function. We are advised that this is used extensively by Microsoft programmers themselves and is therefore unlikely to be withdrawn. However, NAG obviously cannot guarantee this.