Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Object Oriented Optimization

154 views
Skip to first unread message

relaxmike

unread,
Nov 22, 2007, 10:03:45 AM11/22/07
to
Hi,

I have the following problem with re-using a fortran 77 optimization
method in the context of an object-oriented (more precisely object-
based) fortran 90
software. The goal of my message is to submit the solution that I
found
and the problem that I did not solve to the fortran gurus of the
forum,
especially fortran 90 object-based gurus. The problem that I have is
on how to design a re-usable optimization method.

I have an existing fortran 77 optimization method in which the user
must
provide a function which role is to compute the objective and the
constraints.
This function must follow a given template with a pre-defined name :

double precision function fonc ( x , co , ifonc )
implicit none
double precision, dimension (:), intent(in) :: x
double precision, dimension (:), intent(out) :: co
integer, intent(inout) :: ifonc
end function fonc

The array "x" is the parameter, the value of "fonc" is the objective,
the
array "co" is the constraints and ifonc is an error flag. This an
overview of the call tree :

client code
|
+- f77_solver ()
|
+ < ... bla ...>
|
+ fonc

The problem is that we have to use the same optimization method with
several objectives and constraints. But if we put specific code in the
function "fonc", we can only have one optimization problem available
for
one executable because all this is defined in a static way.

One solution would have been to modify the optimization fortran 77
source
code, so that the "solve" subroutine takes as an argument the "fonc"
function. This would have been solved at compile-time to call the
specific function. A template "solve" subroutine would be this one :

subroutine f77_solver ( fonc_function )
implicit none
interface
double precision function fonc_function ( x , co , ifonc )
implicit none
double precision, dimension (:), intent(in) :: x
double precision, dimension (:), intent(out) :: co
integer, intent(inout) :: ifonc
end function fonc_function
end interface
! Sometime later :
obj = fonc_function ( x , co , ifonc )
end subroutine f77_solver

In the client code, one pass the function to the optim_solve
subroutine :

call optim_solve ( myfonc1 )
call optim_solve ( myfonc2 )
etc...

This method must not be confused with the function pointers, as they
are
defined in the C language. All this fortran source is defined in a
static way, which is pre-defined at compile-time. It is not defined at
run-time, as in can be in C.

The problem is that the "optim_solve" subroutine does not do the
resolution by itself. Instead, it uses a complex call tree in which
the
"fonc" function is called several times by several subroutines at
different levels. This solution would imply to modify the complex
fortran 77 source code, which would have been time-consuming and which
could have created (additional) bugs.

Another solution to that problem is the "reverse communication"
pattern.
In that type of method, each time that the solver needs to compute the
objective, the solver sets an output flag to a particular value, then
returns. See Dongarra's article :
http://citeseer.ist.psu.edu/dongarra95reverse.html
A sample use of reverse communication is NLPQL :
http://www.old.uni-bayreuth.de/departments/math/~kschittkowski/nlpqlp22.htm
A discussion on reverse-communication has allready been done on
comp.lang.fortran :
http://groups.google.fr/group/sci.math.num-analysis/browse_frm/thread/23453d99f75a5f27/5c17ca0ddc199e33?lnk=gst&q=reverse+communication#5c17ca0ddc199e33
Depending on the returning value of flag of the solver, the
client code knows the current situation :
- the algorithm is finished (and, may be, converged),
- one has to compute the objective.
If one has to compute the objective, one does so and calls the solver
again. This is an elegant method to create an optimization method
which
has no static link to the computation method. The optimization solver
is,
with reverse communication, really re-usable, without any modification
by
the client code. But the problem is for us that we should modify the
existing fortran 77 source code. The algorithm which is behind reverse
communication seems to imply a lot of modifications, which is time-
consuming etc...

I also thought about a pre-processing trick, based on macro
definitions.
But I haven't found anything simple with that idea.

In fact, what we really need is a function pointer similar to what
exist in C.
This would allow to set the pointer before calling the solver, then
call the solver which can evaluate the objective whenever and wherever
it has to.
But function pointers do not exist in fortran 77, 90, 95 (2000 ?) so I
had to
find another solution.

I got to the following solution, where the function pointer is
emulated
by an integer flag. The idea is to define a unique external function
"fonc", which then calls a function "optdrive_fonc" which is located
in a
fortran 90 module. The function "optdrive_fonc" changes its behaviour
depending on the value of the integer flag (=the function pointer).

See for example the function fonc calling the function optdrive_fonc :

double precision function fonc ( x , co , ifonc )
use m_driver_optim, only : optdrive_fonc
implicit none
double precision, dimension (:), intent(in) :: x
double precision, dimension (:), intent(out) :: co
integer, intent(inout) :: ifonc
fonc = optdrive_fonc ( x , co , ifonc )
end function fonc

The function optdrive_fonc let us choose between several optimization
functions where each one corresponds to a specific optimization
problem.

module m_driver_optim
! Objective function to optimize
integer, public :: objective_function
integer, parameter, public :: PB1 = 1
integer, parameter, public :: PB2 = 2
contains
double precision function optdrive_fonc ( x , co , ifonc )
implicit none
double precision, dimension (:), intent(in) :: x
double precision, dimension (:), intent(out) :: co
integer, intent(inout) :: ifonc
external test_fonc
double precision :: test_fonc
external optm_fonc2
double precision :: optm_fonc2
select case ( objective_function )
case ( PB1 )
optdrive_fonc = test_fonc1 ( x , co , ifonc )
case ( PB2 )
optdrive_fonc = test_fonc2 ( x , co , ifonc )
case default
! TODO : generate an exception.
end select
end function optdrive_fonc
end module m_driver_optim

In the client of the optimization method, it is easy to configure the
problem by a simple set of the objective_function variable.

use m_driver_optim, only : objective_function, PB1, PB2
objective_function = PB1
call f77_solver ()

This solution is simple and efficient. But the problem which remains
is
that the evaluation of the objective cannot be done with the parameter
array "x" by itself. Some additional data have to be provided. The
traditional "fortran 77" way is to put additional data in a global
variable, accessed with a COMMON. In Fortran 90, this can be done with
a
derived-type. That derived-type can be defined in the "test_fonc1"
function or in the "m_driver_optim" module itself. For example :

module m_driver_optim
use m_fonc_module, only : test_fonc3, DATATYPE
type ( DATATYPE ) , save :: mydata
contains
double precision function optdrive_fonc ( x , co , ifonc )
implicit none
double precision, dimension (:), intent(in) :: x
double precision, dimension (:), intent(out) :: co
integer, intent(inout) :: ifonc
external test_fonc
double precision :: test_fonc
select case ( objective_function )
case ( FONC1 )
optdrive_fonc = test_fonc1 ( x , co , ifonc )
case ( FONC3 )
optdrive_fonc = test_fonc3 ( mydata , x , co , ifonc )
case default
! TODO : generate an exception.
end select
end function optdrive_fonc
end module m_driver_optim

That solution is used in the context of an optimization fortran 90
module, developed
following the ideas of object-based programming. That module is based
on personal ideas and external influences, but I recently discovered
(!) that
similar ideas have been presented in
http://www.ccs.lanl.gov/CCS/CCS-4/pdf/obf90.pdf
or since at least 10 years :
http://exodus.physics.ucla.edu/Fortran95/PSTIResearchLecSeries1.html
or :
http://www.cs.rpi.edu/~szymansk/oof90.html
and that a discussion on this subject has taken place here :
http://groups.google.fr/group/comp.lang.fortran/browse_frm/thread/9c13f0b670831908/8f6808345655d24c?lnk=gst&q=object+oriented#8f6808345655d24c
While my message is not completely linked to that subject, it is not
independent.

I think that I am not alone to have these kinds of "how to re-use a
fortran 77 code" problems.
Any comments or suggestions are welcomed.

Best regards,
Michaël

Reinhold Bader

unread,
Nov 22, 2007, 10:18:25 AM11/22/07
to
-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1


[snip]


> But function pointers do not exist in fortran 77, 90, 95 (2000 ?) so I
> had to
> find another solution.

Pointers to procedures (including functions) are allowed by the Fortran
2003 standard, but not widely available in compilers yet. g95 does have
a partial implementation, though.

>
> Best regards,
> Michaël
>

Regards
Reinhold
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.4.2 (GNU/Linux)
Comment: Using GnuPG with SUSE - http://enigmail.mozdev.org

iD8DBQFHRZ3BFVLhKuD7VgsRAgi6AJsGF+CjTS3T/b2TZbK8lmDOo9h2SgCfQhh8
iMX/z2/40+gZVcLxnpZf9YQ=
=4d7/
-----END PGP SIGNATURE-----

Arjen Markus

unread,
Nov 23, 2007, 7:10:07 AM11/23/07
to

If you pass the name of the function around as a dummy argument,
adding it
to each subroutine and function that uses "fonc", I doubt this would
introduce many bugs. It would actually be the simplest solution and
compatible with FORTRAN 77 at that.

But if, indeed, you can not change the source code for this reason or
others, then an implementation with a run-time parameter that selects
the actual function to do the work is the best you can achieve, IMHO.

It is not a bad solution either, even though function pointers like
Reinhold suggests are more elegant.

One alternative, but do not take it too seriously, is to use
something like this:

! Objective function A
module optim_a

contains
double precision fonc( ... )
... objective function A
end function

include 'source-for-optimisation.f'

end module

! Objective function B
module optim_b

contains
double precision fonc( ... )
... ojective function B
end function

include 'source-for-optimisation.f'

end module

module optimise
use optim_a, solver_a => solver
use optim_b, solver_b => solver
end module

Then you can use solver_a to solve the problem with objective function
A
and solver_b to solve it with objective function B.

Drawbacks are of course:
- Your code must use "end subroutine" and "end function" instead of
merely "end"
- The source code must be available to any user who programs another
objective
function.
- The program becomes larger than necessary due to all the copies of
the
optimisation code. But that is probably a very minor issue.

Regards,

Arjen

alexzenk

unread,
Nov 23, 2007, 3:28:01 PM11/23/07
to
On Nov 22, 6:03 pm, relaxmike <michael.bau...@gmail.com> wrote:

> In fact, what we really need is a function pointer similar to what
> exist in C.
> This would allow to set the pointer before calling the solver, then
> call the solver which can evaluate the objective whenever and wherever
> it has to.
> But function pointers do not exist in fortran 77, 90, 95 (2000 ?) so I
> had to
> find another solution.

> Any comments or suggestions are welcomed.
>
> Best regards,
> Michaël

I do not know what Fortran 90 compiler you use.
But existing Fortran compilers (Compaq Visual Fortran, gfortran and
other) allow to use integer pointers (or Cray Pointers). They are
similar to pointers in C .(Fortran pointers and Cray pointers are
different statement).
They are not enclosed in standard Fortran 90 and are an Fortran
compiler extension . The example of their use, as well as possible
realization object oriented approach you may find in http://alexzenk.nightmail.ru
Best Regards,
Alex

alexzenk

unread,
Nov 23, 2007, 3:46:57 PM11/23/07
to

Richard Maine

unread,
Nov 23, 2007, 3:51:53 PM11/23/07
to
alexzenk <zenk...@mail.ru> wrote:

> On Nov 22, 6:03 pm, relaxmike <michael.bau...@gmail.com> wrote:
>
> > In fact, what we really need is a function pointer similar to what
> > exist in C.

> But existing Fortran compilers (Compaq Visual Fortran, gfortran and
> other) allow to use integer pointers (or Cray Pointers)...


> They are not enclosed in standard Fortran 90 and are an Fortran
> compiler extension .

And the details of the extension vary from one compiler to another, that
being one of the probelms with such extensions. One particular detail
that varies is in whether they can point to functions. Just because your
compiler supports Cray pointers doesn't mean that it supports them
pointing to functions. My understanding is that most implementations of
Cray pointers have not allowed this. In fact, I have been told by people
who should know that Cray pointers as implemented by Cray did not
support pointing to functions.

--
Richard Maine | Good judgement comes from experience;
email: last name at domain . net | experience comes from bad judgement.
domain: summertriangle | -- Mark Twain

Gary Scott

unread,
Nov 23, 2007, 3:56:57 PM11/23/07
to
Richard Maine wrote:

> alexzenk <zenk...@mail.ru> wrote:
>
>
>>On Nov 22, 6:03 pm, relaxmike <michael.bau...@gmail.com> wrote:
>>
>>
>>>In fact, what we really need is a function pointer similar to what
>>>exist in C.
>
>
>>But existing Fortran compilers (Compaq Visual Fortran, gfortran and
>>other) allow to use integer pointers (or Cray Pointers)...
>>They are not enclosed in standard Fortran 90 and are an Fortran
>>compiler extension .
>
>
> And the details of the extension vary from one compiler to another, that
> being one of the probelms with such extensions. One particular detail
> that varies is in whether they can point to functions. Just because your
> compiler supports Cray pointers doesn't mean that it supports them
> pointing to functions. My understanding is that most implementations of
> Cray pointers have not allowed this. In fact, I have been told by people
> who should know that Cray pointers as implemented by Cray did not
> support pointing to functions.
>

The most widely used compiler does support pointing to functions, and
others implementing this extension should take note and correct their
deficiency.

--

Gary Scott
mailto:garylscott@sbcglobal dot net

Fortran Library: http://www.fortranlib.com

Support the Original G95 Project: http://www.g95.org
-OR-
Support the GNU GFortran Project: http://gcc.gnu.org/fortran/index.html

If you want to do the impossible, don't hire an expert because he knows
it can't be done.

-- Henry Ford

relaxmike

unread,
Dec 7, 2007, 7:32:17 AM12/7/07
to
Thank you to all for these answers.

In fact, it is true that Cray Pointers are supported in gfortran.
This work is not completely new (2005 at least) :
http://gcc.gnu.org/onlinedocs/gfortran/Cray-pointers.html
This is a work from Asher Langton :
http://coding.derkeiler.com/Archive/Fortran/comp.lang.fortran/2005-10/msg00850.html
http://www.math.wisc.edu/~langton/
Last week, I was able to find a poster with some more informations,
but now it seems
that this pdf is not available anymore.

Cray pointers are a great solution for my problem.
It provides the last brick that I needed for the design of
a generic framework to re-use an old fortran 77 optimization
method into a OO fortran 90 code.

With that, I was able to define the following derived-type.
It contains an integer "fonc_address" which is the address of the
objective function of the problem. This is familiar to
C developers.

module m_optim
type, public :: T_OPTIM
private
! Number of variables (this is the "size" of the problem)
integer :: nbvariables = -1
! Other options are to be stored here
! double precision :: epsilon1, etc...
! default value set to -1, can be used to detect non initialized
type
! Initial guess for the optimization process
double precision, dimension(:), pointer :: initial_guess =>
NULL()
! Solution of the optimization problem
double precision, dimension(:), pointer :: solution => NULL()
! Number of constraints
integer :: nbconstraints
! Number of equality constraints
integer :: nbconstraints_equality
! Number of inequality constraints
integer :: nbconstraints_inequality
! value of the objective function after optimization
double precision :: optimized_objective
! value of the constraints after optimization
double precision, dimension(:), pointer :: optimized_constraints
=> NULL()
! If the optimization was fine, status = .true. (default).
! If the optimization went wrong, status = .false.
logical :: status = .true.
! 1 : converged
! 0 : not converged
! State flag after optimization
integer :: status_detailed =0
! Display messages to the user
logical :: display_messages = .false.
! Objective function address
integer :: fonc_address
end type T_OPTIM
end module module m_optim

Of course I do not detail the optim_new, optim_free,
optim_set_initial_guess, etc... subroutines that come
in the module m_optim to create, destroy, set and get
the object.

It is then easy to define one setter to configure the function to
optimize. The client code gives a function as an input argument.
The intrinsic "loc" function computes the address of the function,
which is then stored in the "fonc_address".
One can even check that the given function
does corresponds with the expected interface.

!
! Set the objective function to optimize
!
subroutine optim_set_objective_function ( this ,
new_objective_fonc )
implicit none
type ( T_OPTIM ), intent(inout) :: this
interface new_objective_fonc_interface
double precision function new_objective_fonc ( x , co , ifonc )
implicit none
double precision, dimension (1:), intent(in) :: x
double precision, dimension (1:), intent(out) :: co
integer, intent(inout) :: ifonc
end function new_objective_fonc
end interface new_objective_fonc_interface
this % fonc_address = loc ( new_objective_fonc )
end subroutine optim_set_objective_function

This setter can be used as in the following example.
I suppose here that there is a function new_objective_fonc
which interface is the same as the expected one.

use m_optim, only : T_OPTIM , optim_set_objective_function
type ( T_OPTIM ) :: myoptim
call optim_set_objective_function ( myoptim, new_objective_fonc )

Now that the optimized objective is set, one can define an optimize
function which is just a layer over the real function to evaluate.
This allows to compute the real objective, but also to check that
the objective has allready been defined.

!
! This fonction allows the generic module m_optim to compte the
objective
! and the constraints.
!
double precision function optim_fonc ( this , x , co , ifonc )
implicit none
type ( T_OPTIM ), intent(inout) :: this
double precision, dimension (1:), intent(in) :: x
double precision, dimension (1:), intent(out) :: co
integer, intent(inout) :: ifonc
double precision :: fonc_pointee
external fonc_pointee
pointer ( fonc_pointer , fonc_pointee )
!
! Check that there is a fonction pointer
!
if (this % fonc_address == 0) then
! Raise your error !
endif
!
! Evaluate the objective
!
fonc_pointer = this % fonc_address
optim_fonc = fonc_pointee ( x , co , ifonc )
end function optim_fonc

One can also think about counting the number of evaluations
of that function, in order to measure the performance of the
optimization method. One could also check that the size
of the given x correspondinds with the number of variables
of the problem.

From that, it is easy to derive a specific optimize
module from the general one. We must do that in that order,
following the OO principles stating that the class must be
created from the more general toward the more specific.

module m_specific_optim
[...]
type, public :: T_OPTIMSPECIFIC
private
integer :: my_specific_variable
!
! A specific solver is a specialized kind of optim solver
!
type (T_OPTIM) :: myoptim
end type T_OPTIMSPECIFIC
end module m_specific_optim

I was able to define an external function named "fonc", with global
scope,
which is called from the old fortran 77 optimization
method. In that function "fonc", it is easy to compute the objective
function
by calling the objective function defined in the module m_optim.

double precision function fonc ( x , co , ifonc )

use m_optim, only : optim_fonc
use m_optim_nlpgr, only : myoptim_function
[...]
fonc = optim_fonc ( myoptim_function , x , co , ifonc )
end function fonc

The fact that the fortran 77 function does not provide the
object "myoptim" is not a problem. One cas easily create a
static optim member, called here "myoptim_function".
The fortran "save" attribute allows to store the optim object
from the time is is set to the time it is used. The small
ugly thing is that it is public for the direct access from
the fonc function.

module m_specific_optim
[...]
type (T_OPTIM), save, public :: myoptim_function
end module m_specific_optim

In the module m_specific_optim, I defined a subroutine
"specific_solve",
which job is to run the old-fashioned fortran 77 optimization method.
Just before the launch of the specific solve method,
one stores the myoptim object for later re-use in the "fonc"
function :

subroutine specific_solve ( this )
implicit none
type(T_OPTIMSPECIFIC), intent(inout) :: this
myoptim_function = this % myoptim
call my_old_fashioned_fortran77_code ()
end subroutine specific_solve

I think that the current solution provides an extensible
pattern for the development and use of an optimization method
in fortran.
I am opened to comments on that way of designing a fortran 90
optimization method.

Best regards,
Michaël

glen herrmannsfeldt

unread,
Dec 7, 2007, 7:54:40 AM12/7/07
to
relaxmike wrote:

> In fact, it is true that Cray Pointers are supported in gfortran.

(snip)

> Cray pointers are a great solution for my problem.
> It provides the last brick that I needed for the design of
> a generic framework to re-use an old fortran 77 optimization
> method into a OO fortran 90 code.

> With that, I was able to define the following derived-type.
> It contains an integer "fonc_address" which is the address of the
> objective function of the problem. This is familiar to
> C developers.

Yes, function pointers didn't appear until Fortran 2003.
I would hope that they would be a better solution to your problem,
but until they are available, I suppose Cray pointers are fine.
Fortran 2003 also has C pointers, I believe including function
pointers, but they might also not be available yet.

(The ability to pass a subroutine or function name as an
actual argument, and call that function from the called routine
has been part of Fortran probably since the beginning of user
written functions. The ability to store that in a variable,
unfortunately, took a little longer.)

> Of course I do not detail the optim_new, optim_free,
> optim_set_initial_guess, etc... subroutines that come
> in the module m_optim to create, destroy, set and get
> the object.

(snip)

> I think that the current solution provides an extensible
> pattern for the development and use of an optimization method
> in fortran.
> I am opened to comments on that way of designing a fortran 90
> optimization method.

I would hope that when Fortran 2003 function pointers are
available you would find those an even better, and
more standard, solution.

-- glen

0 new messages