Libclasses
Programming the Classes Library
_*Memory Management*_ Large array objects in types are declared as FORTRAN pointers to arrays; this is done so that we can share memory between matlab and fortran in the fortran interface. If you need to allocate such an array in code that might be called from the matlab interface, you must use the [IXFalloc] function which allocates MATLAB memory and then associates the fortran pointer with this. If you need memory temporarily within a subroutine and will not be returning it to matlab, you can instead use the standard fortran ALLOCATE statement.
_*Adding a New Type and Operations*_
The IXMtestclass module is defined in the *'IXMtestclass.f90'* file, which should be consulted concurrently with this page. The IXTtestclass type is defined in the first section of the module, it contains examples of all the currently used types of variable (real and integer single variables and arrays, character strings, logicals and nested structures; allocatable arrays of structures are a simple extension). Below the type definition the #define and #include lines direct the preprocessor to include the *'class_header.f90'* file which contains interface statements to all the standard subroutines of the module which are included in the file *'class_base.f90'*. These are used for generating template code to save on “cut and paste”. The 'contains' line defines the section of the module which holds the module specific subroutines.
module IXMtestclass
! include the modules which are relied upon by the module
use IXMtype_definitions
use IXMbase
use IXMspectra
!declare the type which is public
type IXTtestclass
private ! all component elements of the module are private
type(IXTbase) :: base
real(dp) :: val !! real variable
integer(i4b) :: nx !! integer variable
real(dp), pointer :: val_array(:) => NULL() !! variable length 1d real array, always declared as NULL by default
real(dp), pointer :: err_array(:) => NULL() !! variable length 1d real array, always declared as NULL by default
real(dp) :: val_stat(3)=0.0 !! static real array
integer(i4b),pointer :: int_arr(:,:)=>NULL() !! variable length 2d integer array, always declared as NULL by default
type(IXTspectra):: spectra !! nested object
logical :: xhist=.FALSE. !! logical variable
character(len=short_len) :: label='x-label' !! character string variable
end type IXTtestclass
!! include the interfaces required by routines declared in class_base.f90
#define IXD_TYPE testclass
#include "class_header.f90"
contains
!! include the generic subroutines every class requires
#define IXD_DESCRIPTION "IXTtestclass class"
#define IXD_TYPE testclass
#define IXD_SQTYPE 'testclass'
#include "class_base.f90"
To add a new type IXT{your_module_name} you should
- Create a module IXM{your_module_name} to define type IXT{your_module_name} in file IXM{your_module_name}.f90
- Include “class_header.f90” and “class_base.f90” at the appropriate points with IXD_TYPE set to the name of the type (with the IXT removed) and IXD_DESCRIPTION to the text describing the clas
Subroutines which must be included in the new module. All descriptions below use IXMtestclass as an example.
IXFoperation_run_{your_module_name}
When manipulating class objects you often need to loop through and apply the same operation to all of the data members of that object. The IXFoperation_run interface splits what you want to do (IXFoperation_make) from the looping through of the class members (IXFOperation_run_Testclass). The advantage of this is that you only need to set up the “loop through the class” once and not for everything that you might want to do; also if you were to change the class layout you only have one function to change. We will ignore IXFoperation_make and just show IXFoperation_run_testclass as the “operation run” function is what you must provide for each class.
!-----------------------------------------------------------------------------------------------------------------------
! All classes must provide this operation; it loops through
! all members of the class doing the supplied operation
recursive subroutine IXFoperation_run_testclass(op, field, arg, status)
implicit none
type(IXTtestclass) :: arg
type(IXToperation) :: op
type(IXTstatus) :: status
character(len=*) :: field
call IXFoperationStart(op, 'IXTtestclass', field, status)
! this order must match the declaration order in matlab as it is
! used when parsing argemnts passed in class creation with vargin
call IXFoperation_run(op, 'base', arg%base, status)
call IXFoperation_run(op, 'val', arg%val, status)
call IXFoperation_run(op, 'nx', arg%nx, status)
call IXFoperation_run_ptr(op, 'val_array', arg%val_array, status) ! this is a pointer array so the ptr suffix is used
call IXFoperation_run_ptr(op, 'err_array', arg%err_array, status) ! this is a pointer array so the ptr suffix is used
call IXFoperation_run(op, 'val_stat', arg%val_stat, status)
call IXFoperation_run_ptr(op, 'int_arr', arg%int_arr, status) ! this is a pointer array so the ptr suffix is used
call IXFoperation_run(op, 'spectra', arg%spectra, status)
call IXFoperation_run(op, 'xhist', arg%xhist, status)
call IXFoperation_run(op, 'xlabel', arg%label, status)
call IXFoperationFinish(op, field, status)
end subroutine IXFoperation_run_testclass
As you see, all we do is re-apply the same IXFoperation_run interface function to each data member. The hierarchy will be descended recursively until a simple type (i.e. integer, real array etc) is reached – then the appropriate final function is called (e.g. runOperationInteger) to do the real work. See the IXMoperation module for details of these final functions. Currently matlab reading, writing and printing to the screen (display) are all handled via this general mechanism – later file access will be added through it.
IXFcreate_{your_module_name}
!-----------------------------------------------------------------------------------------------------------------------
!!The IXFcreate subroutine STRICTLY takes all the elements required to define a class and creates the resulting
!! object. If an element of the object is another class then it must be initialised.
subroutine IXFcreate_testclass(arg, base, val, nx, val_array, err_array,val_stat, int_arr,spectra, xhist,label, status)
implicit none
type(IXTtestclass) :: arg
type(IXTstatus) :: status
type(IXTbase)::base
real(dp),intent(in):: val,val_stat(3)
real(dp),intent(in) :: val_array(:), err_array(:)
integer(i4b),intent(in):: nx,int_arr(:,:)
type(IXTspectra),intent(in):: spectra
logical,intent(in) :: xhist
character(len=*) :: label
! nested objects should be tested for initialisation, this shows they have been created properly
if( IXFinitialised(spectra) /= .true.)then
call IXFadd_status(status, IXCfacility_libisis, IXCseverity_error, &
IXCerr_outofmem, 'IXTspectra failure, all nested objects MUST be initialised (IXFset_testclass)')
endif
!-----------------------------------------------------------------------------------------------------------------------
!should IXTbase be an argument to create....
!-----------------------------------------------------------------------------------------------------------------------
! the set routine can ONLY be called on an initialised object
! so in this SPECIAL case it is initialised before it is filled
call IXFmark_init(arg)
! set is called with all the components of the object
call IXFset_testclass(arg,status,base,val, nx, val_array, err_array,val_stat, int_arr,spectra, xhist,label)
!check is called in the set routine
end subroutine IXFCreate_testclass
IXFdestroy_{your_module_name}
!-----------------------------------------------------------------------------------------------------------------------
!!IXFdestroy routine deallocates any pointer arrays in the type, and calls the destroy function on any nested
!!objects, could also be used to set variables back to their default values.
!!If one of the objects is an array of structures, then each structure will be recursively destroyed by the
!!IXFdealloc function.
subroutine IXFdestroy_testclass(arg, status)
implicit none
type(IXTtestclass),intent(inout) :: arg
type(IXTstatus) :: status
call IXFdealloc(arg%val_array,status)
call IXFdealloc(arg%err_array,status)
call IXFdealloc(arg%int_arr,status)
! for nested objects check it hasn't been destroyed already
! IXFinitialised is valid for an array of structures, allocatable or static
if(IXFinitialised(arg%spectra))call IXFdestroy(arg%spectra,status)
! the initialised status is now revoked for the object
! this statement MUST exist in all destroy routines
call IXFclear_init(arg)
end subroutine IXFdestroy_testclass
IXFcheck_{your_module_name}
!-----------------------------------------------------------------------------------------------------------------------
!! IXFcheck will make internal consistency checks in the object, such as array length checking to make
!! sure the object is properly filled.
subroutine IXFcheck_testclass(arg, status)
implicit none
type(IXTtestclass) ::arg
type(IXTstatus) :: status
if (size(arg%val_array) /= size(arg%err_array)) then
call IXFadd_status(status, IXCfacility_libisis, IXCseverity_error, &
IXCerr_outofmem, 'lengths of value and error arrays do not match(IXFcheck_testclass)')
endif
end subroutine IXFcheck_testclass
IXFset_{your_module_name}
!-----------------------------------------------------------------------------------------------------------------------
!!The IXFset operation can only be performed on a properly filled or initialised object. It takes an optional number of
!! arguments to modify the object contents. A check is made at the end to determine that the edited object is correctly
!! formed. Error flags are raised if there is any inconsistency. The optional arguments must always be specified by keywords.
!! The order of arguments should match the order of declaration. The 'ref' argument is used to copy the values of a
!! reference object to another. In this case the object being modified does not have to be initialised, but the refence object
!! must be initialised instead.
recursive subroutine IXFset_testclass(arg, status,base, val,nx, val_array, err_array, val_stat, int_arr, spectra, xhist, label, ref)
implicit none
type(IXTtestclass) :: arg
type(IXTstatus) :: status
! all the supplied variables are declared as optional with intent(in)
type(IXTtestclass),intent(in),optional :: ref
type(IXTbase),intent(in),optional::base
real(dp),intent(in),optional:: val, val_stat(3)
real(dp),intent(in),optional :: val_array(:), err_array(:)
integer(i4b),intent(in),optional::int_arr(:,:),nx
type(IXTspectra),intent(in),optional:: spectra
logical,intent(in), optional:: xhist
! input strings are treated as an unknown length, if the supplied string is longer than the declared length
! then it will be truncated. If it is shorter, then the new variable will be padded with spaces.
character(len=*),optional,intent(in) :: label
! check that either the reference object is initialised
! or that object to be modified is initialised
if(present(ref))then
if (IXFinitialised(ref) /= .true.)then
call IXFadd_status(status, IXCfacility_libisis, IXCseverity_error, &
IXCerr_outofmem, 'Reference object MUST be initialised (IXFset_testclass)')
endif
if(status == IXCseverity_error)return
! now initialise object to be modified, not necessary to check its value
call IXFinitialize(arg)
else
if(IXFinitialised(arg) /= .true.) then
call IXFadd_status(status, IXCfacility_libisis, IXCseverity_error, &
IXCerr_outofmem, 'Set can only be called on an initialised object (IXFset_testclass)')
endif
if(status == IXCseverity_error)return
endif
! This command will copy all of the attributes of the reference object to the object being modified
if (present(ref))call IXFset_testclass(arg,status,ref%base,ref%val,ref%nx,ref%val_array,ref%err_array, &
ref%val_stat,ref%int_arr,ref%spectra,ref%xhist)
! for nested objects the set command of the nested object is called, equally valid is a call to IXFcopy
! call IXFcopy(base,arg%base,status)
! which in turn will make the same call to IXFset_base
if (present(base))call IXFset_base(arg%base,status,ref=base)
! single variables are simply overwritten by the supplied variables
if (present(val))arg%val=val
if (present(nx))arg%nx=nx
! 1D variable length arrays
! IXFrealloc is called to make the modified array the same length as the supplied array
! if the array pointer is not allocated, then allocation is performed
call IXFset_real_array(arg%val_array,status,val_array)
! as above
call IXFset_real_array(arg%err_array,status,err_array)
! static arrays are simply copied
! if the length of val_stat is not 3, then the program will break at
! runtime, a check cannot be made for this
if (present(val_stat)) arg%val_stat=val_stat
!2D variable length arrays
! IXfreallocdims is called, this takes the shape of the supplied array. The same checks are made on the status
! of the array pointer as for 1D arrays
call IXFset_integer_array(arg%int_arr,status,int_arr)
! for nested objects the set command of the nested object is called, equally valid is a call to IXFcopy
! call IXFcopy(spectra,arg%spectra,status)
! which in turn will make the same call to IXFset_spectra
if (present(spectra))call IXFset_spectra(arg%spectra,status,ref=spectra)
! logicals and strings are treated in the same way as single variables
if(present(xhist))arg%xhist=xhist
if(present(label))arg%label=label
! the check routine MUST always be called at the end of the set routine
call IXFcheck(arg,status)
end subroutine IXFset_testclass
IXFget_{your_module_name}
!-----------------------------------------------------------------------------------------------------------------------
!! The IXFget subroutine will return elements of an object to an optional supplied arrays/variables. The supplied variables
!! should be referrred to by keyword to avoid errors. The 'wout' variable is special and can be used to copy the
!! contents of a whole object to a new one.
subroutine IXFget_testclass(arg,status,base, val, nx, val_array, err_array,val_stat, int_arr,spectra, xhist,label,wout)
implicit none
type(IXTtestclass) :: arg
type(IXTstatus) :: status
! all the supplied variables are declared as optional with intent(out)
type(IXTtestclass),intent(out),optional::wout
type(IXTbase),intent(out),optional::base
real(dp),intent(out),optional:: val, val_stat(3)
real(dp),intent(out),optional :: val_array(:), err_array(:)
integer(i4b),intent(out),optional::nx,int_arr(:,:)
type(IXTspectra),intent(out),optional:: spectra
logical,intent(out), optional:: xhist
!output strings are again treated as an unknown length. If they are shorter than the object string then the output
!will be truncated. If they are longer then the output will be padded with spaces.
character(len=*),optional,intent(out) :: label
! this makes a call to the appropriate set routine. The IXFcopy routine calls
! the same routine underneath.
if (present(wout))then
call IXFset_testclass(wout,status,ref=arg)
endif
! supplied nested objects are filled with an appropriate set routine
if (present(base))call IXFset_base(base,status,ref=arg%base)
! single variables are copied into the supplied arrays
if (present(val))val=arg%val
if (present(nx))nx=arg%nx
! 1D variable length arrays
! The supplied array must be the same length as the object array. this test is made and the array filled
call IXFget_real_array(arg%val_array,status,val_array)
! as above
call IXFget_real_array(arg%err_array,status,err_array)
!checks are not made on static arrays, since the routine will break at runtime if a supplied array is not
!the same length as that declared
if (present(val_stat))val_stat=arg%val_stat
! 2D variable length arrays
! The supplied array must now be the same shape as the object array. this test is made and the object is filled
call IXFget_integer_array(arg%int_arr,status,int_arr)
! supplied nested objects are filled with an appropriate set routine
if(present(spectra))call IXFset_spectra(spectra,status,ref=arg%spectra)
! logicals and strings are treated as single variables, with strings being truncated where appropriate
if(present(xhist))xhist=arg%xhist
if(present(label))label=arg%label
end subroutine IXFget_testclass
IXFget_ptr_{your_module_name}
!-----------------------------------------------------------------------------------------------------------------------
!! IXFget_ptr will return a pointer to a structure or an array, from an optional argument.
!! The pointer arguments are generally the same name as the object elements they are pointing to.
!! Care must be taken since if the pointers are edited, then the data in the structure will also be edited.
subroutine IXFget_ptr_testclass(arg,val_array,err_array,int_arr,spectra)
implicit none
type(IXTtestclass),intent(in),target :: arg
type(IXTspectra),optional,pointer::spectra
real(dp),optional,pointer::val_array(:),err_array(:)
integer(i4b),optional,pointer:: int_arr(:,:)
if (present(spectra))spectra=>arg%spectra
if (present(val_array))val_array=>arg%val_array
if (present(err_array))err_array=>arg%err_array
if (present(int_arr))int_arr=>arg%int_arr
end subroutine IXFget_ptr_testclass
IXFget_alloc_{your_module_name}
!-----------------------------------------------------------------------------------------------------------------------
!! IXFget_alloc will fill optionally supplied allocatable arrays with the data contained in the
!! object array elements. The supplied arrays can be either allocated or not. If they are the wrong
!! length then they are adjusted accordingly. This is a routine only for internal Fortran use.
subroutine IXFget_alloc_testclass(arg,val_array,err_array,int_arr)
implicit none
type(IXTtestclass),intent(in) :: arg
real(dp),allocatable,optional::val_array(:),err_array(:)
integer(i4b),allocatable,optional:: int_arr(:,:)
! 1D arrays
if (present(val_array))then
call IXFreallocFortran(val_array,shape(arg%val_array),.false.,status)
val_array=arg%val_array
endif
if (present(err_array))then
call IXFreallocFortran(err_array,shape(arg%err_array),.false.,status)
err_array=arg%err_array
endif
! for the 2D array we have to check if the shape is exactly the same using the sum
! of the absolute of the difference of the shape output
if (present(int_arr))then
call IXFreallocFortran(int_arr,shape(arg%int_arr),.false.,status)
int_arr=arg%int_arr
endif
end subroutine IXFget_alloc_testclass