The Genie Module Interface

This section will answer the following questions:

What is a module?

A module is a compiled FORTRAN program that can be loaded into, and become part of, a running Genie process. Subroutines in the module, provided they follow a given set of rules, can be called to manipulate arbitrary Genie variables (similar to a Genie-II transform command, but much more powerful and flexible). A module is usually implemented as a shared library or DLL.

When would i want to use modules?

Modules are used when:

How do i write a module

A module consists of subroutines only - there is NO main program. These subroutines can be divided into two types: those that perform the actual calculations, and those that pass data to/from Genie and the calculation routines; we shall call the latter "wrappers" as they provide a jacket for the original calculation routines.

1. Write FORTRAN Subroutines to do your tasks

The subroutines can take any parameters you desire. Our example will be based on the following:

C
C *** The function - just square the X array (from "myfunc.for" in the examples directory) 
C 
SUBROUTINE MYFUNC(X, Y, NPT) 
IMPLICIT NONE 
INTEGER NPT, I 
REAL X(NPT), Y(NPT)
DO I=1,NPT 
Y(I) = X(I) * X(I) 
ENDDO 
RETURN
END 

2. Write a FORTRAN "wrapper" subroutine to interface between Genie and your calculation subroutine

Genie variables are passed to and from the module using a temporary workspace. Data is placed into the input workspace with chosen field names, and then access in FORTRAN by using this field name and an access routine appropriate for the data type being sent. For example, the frame count could be stored in field "NRAW" and access by the module_get_integer() function in FORTRAN. Returning data is similar - various module_put() FORTRAN subroutines allow the construction of a returned workspace with various data types at named filed positions.The wrapper subroutine must obey the following rules:

For a full list of module_...() functions see the Module FORTRAN interface reference

For our example "myfunc" the wrapper would be:

C
C *** the wrapper subroutine for MYFUNC
C *** input into array X, output into array Y
C
SUBROUTINE DO_MYFUNC(PARS_GET, PARS_PUT)
IMPLICIT NONE INTEGER NPT_MAX, NPT
C *** We can handle NPT_MAX data points
PARAMETER(NPT_MAX=1000)
REAL X(NPT_MAX), Y(NPT_MAX)
EXTERNAL PARS_GET, PARS_PUT
C *** print a "blue" message to the user
CALL MODULE_INFORMATION('Inside module --- MYFUNC called!!!')
C *** Set NPT to the max size of the array
C *** On return, NPT will be the number of data points passed
NPT = NPT_MAX
C *** The input was placed in a workspace field called 'XVALS' in GCL
CALL MODULE_GET_REAL_ARRAY(PARS_GET, 'XVALS', X, NPT)
IF (NPT .GT. NPT_MAX) THEN
CALL MODULE_ERROR('myfunc module', 'Too many points passed', ' ')
RETURN
ENDIF
CALL MYFUNC(X, Y, NPT)
C *** now return the result (Y) in a workspace field called 'YVALS' CALL MODULE_PUT_REAL_ARRAY(PARS_PUT, 'YVALS', Y, NPT)
RETURN
END

3. Make the Module Library

You need to compile the file containing the "function" and its accociated "wrapper" using the MODULE/COMPILE command --- this will produce a ".so" file to load into Genie.

>> MODULE/COMPILE "myfunc.for" SYMBOLS="do_myfunc"

This command first runs a FORTRAN compiler on the code, then it produces a shared library from the object code. If the compilation fails for any reason you will see various error messages on the screen and the creation of the shared library will be aborted. On a successful run, you wil see a message similar to the following:

*** Module now compiled - load with: MODULE/LOAD "myfunc.so"

The SYMBOLS parameter must be set to a comma separated list of "wrapper" subroutines that you wish to call from genie (via MODULE/EXECUTE)

4. Load the module into genie

To load the module, use MODULE/LOAD command with the name of the ".so" file created by the MODULE/COMPILE. You can also supply a comment that will be displayed when you later type MODULE/LIST

>> MODULE/LOAD "myfunc.so" "My function module!"

You only need to re-load a module if you change the source code and have executed another MODULE/COMPILE command.

5. Package function arguments into a workspace

You now need to create a workspace to hold the parameters of the SUBROUTINE you wish to call in the module. The fields in the workspace must have the same names as those you specified in the second argument of your "module_get_..." calls above. In our case, we only have one variable and we called it "XVALS", so assuming X is the array we wish to send:

>> X=DIMENSIONS(10) # create a new array
>> FILL X 1.0 1.0 # Fill array with numbers 1.0 to 10.0
>> PARS=FIELDS() # create an empty workspace for module arguments
>> PARS.XVALS = X # add X to workspace as field "XVALS"

6. Execute the module and get the result

This is achieved by:

>> MY_RESULT = MODULE:EXECUTE("my_func", PARS)

where "my_func" is the name of the FORTRAN wrapper routine you wrote, and PARS is the packaged arguments workspace created above. The values specified in "module_put_..." calls will appear in the returned workspace MY_RESULT; in the above case MY_RESULT will contain one entry called YVALS, so we can type:

>> PRINTN SOME_VARIABLE.YVALS

and see out squared X values!

A Real-Life Sample Module

The following "module" was created by Spencer Howells at ISIS - the code is available in the "ex2" subdirectory of the examples area as "g2s.gcl" and "g2s.for"

First the GCL procedure that calls the module:
#
# Procedures for G2S
#
PROCEDURE g2s
PARAMETERS
wg=workspace
RESULT ws
LOCAL g2s res
ws=wg
g2s=fields() ; g2s.lptin=wg.ntc
g2s.Xin=wg.x ; g2s.Yin=wg.y ; g2s.Ein=wg.e
g2s.qmax=inquire("g2s> qmax ")
g2s.npt =inquire("g2s> number of points ")
g2s.ic =inquire("g2s> window function code ")
g2s.rho =inquire("g2s> number density ")
module/load "g2s.so" ;
res=module:execute("g2s", g2s)
ws.ntc=res.lptout
ws.x=res.Xout ; ws.y=res.Yout ; ws.e=res.Eout
ws.xlabel=res.xcaptout ; ws.ylabel=res.ycaptout
ENDPROCEDURE

Now the FORTRAN program that performs the actual calculation:

SUBROUTINE G2S(g2s_get, g2s_put)
EXTERNAL g2s_get, g2s_put
INTEGER mn, lptin, lptout
PARAMETER (mn=33000)
REAL*4 Xin(mn),Yin(mn),Ein(mn),Xout(mn),Yout(mn),Eout(mn)
REAL*4 xnew(mn),yw(mn)
CHARACTER*40 xcaptout, ycaptout
CHARACTER*10 char
LOGICAL LMOD
DANGLE=38.1*1.112/150.0/150.0
PI=4.0*ATAN(1.0D0)

call module_get_int(g2s_get, 'lptin', lptin)
call module_get_real_array(g2s_get, 'Xin', Xin, lptin)
call module_get_real_array(g2s_get, 'Yin', Yin, lptin)
call module_get_real_array(g2s_get, 'Ein', Ein, lptin)
call module_get_real(g2s_get, 'qmax', QMAX)
call module_get_int(g2s_get, 'npt', npt)
call module_get_int(g2s_get, 'ic', ichar)
call module_get_real(g2s_get, 'rho', RHO)
if(lptin.eq.0)then
call module_error(" G2S", 1 "ERROR ** No input data", " ")
endif

if(npt.eq.0)then
call module_error(" G2S>", 1 "ERROR ** Number of output points zero", " ")
RETURN
endif

lptout=npt
if(lptout.GT.mn)then
call module_error(" G2S>", 1 "#points reduced from 33000", " ")
lptout=mn
endif
delq=QMAX/lptout

if(rho.lt.1e-10)then
call module_error(" G2S>", 1 "ERROR ** rho is zero", " ")
RETURN
endif

if(ichar.eq.0)then
LMOD=.false.
else
if(ichar.eq.1)then
LMOD=.true.
else
LMOD=.false.
endif
endif
if(LMOD)then
A=PI/xin(lptin)
do nn=1,lptin
yw(nn)=SIN(xin(nn)*A)/xin(nn)/A
end do
else
do nn=1,lptin
yw(nn)=1.0
end do
endif
C
C FORM VECTOR OF EQUALLY-SPACED R'S AT WHICH THE FOURIER TRANSFORM C IS TO BE COMPUTED (RMAX IN ANGSTROMS), AND THE NUMBER OF R-POINTS.
C
DO NR=1,lptout
xout(NR)=delq*NR
end do
C
C THE NUMBER OF POINTS IN THE RANGE OF DATA TO BE TRANSFORMED.
C
xd=(xin(2)-xin(1))/2. !half x-channel
do n=1,lptin
c xnew(n)=xin(n) +xd !offset - mid channel
xnew(n)=xin(n)
yw(n)=yw(n)*(yin(n)-1.)*xnew(n)
end do
C
C COMPUTE FOURIER TRANSFORM OF THE DATA
C
delr=(xin(lptin)-xin(1))/(lptin-1)
AFACT=delr*2.0/PI
DO 35 NR=1,lptout
FS=0.0
RP=xout(NR)
DO N=2,lptin
SINUS1=SIN(xnew(N-1)*RP)
SINUS=SIN(xnew(N)*RP)
FS=FS+ (SINUS*yw(N)+ 1 SINUS1*yw(N-1))/2.0
end do
yout(NR)=FS*AFACT
35 CONTINUE
C

pir=PI*PI*2.*RHO
do n=1,lptout
yout(n)=yout(n)*pir/xout(n) +1.
end do

xcaptout=' Q (Angstrom-1) ' ycaptout=' Structure Factor S of Q '

call module_put_int(g2s_put, 'lptout', LPTOUT)
call module_put_real_array(g2s_put, 'Xout', Xout, lptout)
call module_put_real_array(g2s_put, 'Yout', Yout, npt)
call module_put_real_array(g2s_put, 'Eout', Eout, npt)
call module_put_string(g2s_put, 'ycaptout', ycaptout)
call module_put_string(g2s_put, 'xcaptout', xcaptout)
call module_information(' G2S> output is in point mode')

RETURN
END