From: Enthalpy on
Hello all!

This is my first message to the group although since now I read
several interesting discussions here. I'm not a professional
programmer but I have some experience of computational programming.

I'm working on the code to solve sets of non-linear equations. I'm
writing the module that provides to the root-finding algorithm the
values of the equations to solve (stored in the array f_vect)
evaluated in the input point x (an array containing the guess for the
unknowns).

Here you can see a "static" version of the module; it's just able to
provide to the root-finding routine a fixed set of equations:

MODULE equations
IMPLICIT NONE

REAL, PARAMETER :: ONE = 1.

CONTAINS

FUNCTION f_vect(x)
REAL, DIMENSION(:), INTENT(IN) :: x
REAL, DIMENSION(SIZE(x)) :: f_vect
REAL, PARAMETER :: mp = 1.5, pmec = 1445422., a = 0.746E5, b = 0.55E5
REAL, PARAMETER :: pmi = 963329., Ta = 288., pa = 1E5, eta_is_c = 0.8
REAL, PARAMETER :: k = 1.4, eta_m_t = 0.95 , eta_is_t = 0.85, Ts =
700.
REAL, PARAMETER :: eta_m_c = 0.95, rho = 9.
!
! x(1): l'v/lv x(2): ps x(3): pc x(4): mu x(5): Tc
!
f_vect(1) = ONE + ONE / (rho-ONE) * ( ONE-( x(2)/x(3) )**(ONE/mp) ) -
x(1)
f_vect(2) = x(4) * x(1) * pmi + x(3) - x(2) - a - b*x(4)*x(1) - pmec
f_vect(3) = SQRT( Ta / x(5) ) * x(3) / pa - x(4)
f_vect(4) = Ta * ( ONE + ONE/eta_is_c * ( ( x(3)/pa )**( (k-ONE)/k ) -
ONE ) ) - x(5)
f_vect(5) = eta_m_t * eta_is_t * Ts * (ONE - ( pa/x(2) )**( (k-ONE)/
k ) ) - ( x(5)-Ta )/eta_m_c

END FUNCTION f_vect

END MODULE equations


This works great with my program.

Now I'd like to edit the module in order to select at runtime the sets
of equations and the unknowns (reading an input file, for example). I
don't know how to do that.

I thought to put together several module procedures comprising all the
possible solvable equations plus the f_vect function above that this
time should select in some way the sets of the equations (again, I
don't know how).

For what concerns the unknowns, I thought to declare all the
parameters (like mp, pmec, a, b, pmi, Ta,...) in the global module
area and to set the vector x as a pointer linking to the unknowns
specified by the input file (a select case should work well on this).
Although it's not an elegant solution, it may work. Any suggestions
also on that?

Thanks for your time reading my long post and...for my English!


Emanuele
From: glen herrmannsfeldt on
Enthalpy <epagone(a)email.it> wrote:

> I'm working on the code to solve sets of non-linear equations. I'm
> writing the module that provides to the root-finding algorithm the
> values of the equations to solve (stored in the array f_vect)
> evaluated in the input point x (an array containing the guess for the
> unknowns).

> Here you can see a "static" version of the module; it's just able to
> provide to the root-finding routine a fixed set of equations:

> MODULE equations
> IMPLICIT NONE
(snip)

> REAL, PARAMETER :: pmi = 963329., Ta = 288., pa = 1E5, eta_is_c = 0.8
> REAL, PARAMETER :: k = 1.4, eta_m_t = 0.95 , eta_is_t = 0.85, Ts =
(snip)

> This works great with my program.

> Now I'd like to edit the module in order to select at runtime the sets
> of equations and the unknowns (reading an input file, for example). I
> don't know how to do that.

In the case where the equations stayed the same, but some parameters
changed, traditionally that was done through COMMON. More recently
it would be done through MODULE variables, as you seem to indicate.

Normally just about all constants, what you have in PARAMETER
statements, would be variables in the called function.

For more complicated changes you could, as you mention, use CASE
(or traditionally computed GOTO) to select between different
sets of equations.

For the most general case, you could write an interpreter for
a specialized language, or an intermediate representation of that
language, that would then evaluate any desired expression(s)
as needed.

Another possibilty, relatively easy on current systems, is to at
run time generate and compile the appropriate Fortran code,
then link it into a DLL (or .SO) and dynamically link it.

> I thought to put together several module procedures comprising all the
> possible solvable equations plus the f_vect function above that this
> time should select in some way the sets of the equations (again, I
> don't know how).

The above mentioned methods allow for just about all possible
solvable (and not solvable) equations.

> For what concerns the unknowns, I thought to declare all the
> parameters (like mp, pmec, a, b, pmi, Ta,...) in the global module
> area and to set the vector x as a pointer linking to the unknowns
> specified by the input file (a select case should work well on this).
> Although it's not an elegant solution, it may work. Any suggestions
> also on that?

More usual would be to pass an array (through MODULE) with the
parameters in it. Less self documenting, but more general and
often easier to work with. If, for example, your function was
a polynomial then a simple loop over the coefficients is all
that is needed instead of a large expression with a fixed degree.

Many non-linear optization algorithms also use partial derivatives.
You don't mention that, so I presume yours don't.

-- glen
From: Jugoslav Dujic on
Enthalpy wrote:
> Hello all!
>
> This is my first message to the group although since now I read
> several interesting discussions here. I'm not a professional
> programmer but I have some experience of computational programming.
>
> I'm working on the code to solve sets of non-linear equations. I'm
> writing the module that provides to the root-finding algorithm the
> values of the equations to solve (stored in the array f_vect)
> evaluated in the input point x (an array containing the guess for the
> unknowns).
x(2): ps x(3): pc x(4): mu x(5): Tc
> !
> f_vect(1) = ONE + ONE / (rho-ONE) * ( ONE-( x(2)/x(3) )**(ONE/mp) ) -
> x(1)
>
> END FUNCTION f_vect
>
> END MODULE equations
>
>
> This works great with my program.
>
> Now I'd like to edit the module in order to select at runtime the sets
> of equations and the unknowns (reading an input file, for example). I
> don't know how to do that.
>
> I thought to put together several module procedures comprising all the
> possible solvable equations plus the f_vect function above that this
> time should select in some way the sets of the equations (again, I
> don't know how).

I admit I didn't delve too deeply into your problem, but I suppose that
you will find Stuart Midgley's Fortran function parser (interpreter):

http://stu.ods.org/fortran/

quite useful. I have used the "lite" version myself, and the "advanced"
version seems lot more efficient. It depends on your needs of course.

Sure, using the run-time interpreter would be much slower than
precompiled functions, but much more flexible as well.

--
Jugoslav
www.xeffort.com
Please reply to the newsgroup.
You can find my real e-mail on my home page above.
From: Eli Osherovich on
On Mar 24, 1:38 am, Enthalpy <epag...(a)email.it> wrote:
> Hello all!
>
> This is my first message to the group although since now I read
> several interesting discussions here. I'm not a professional
> programmer but I have some experience of computational programming.
>
> I'm working on the code to solve sets of non-linear equations. I'm
> writing the module that provides to the root-finding algorithm the
> values of the equations to solve (stored in the array f_vect)
> evaluated in the input point x (an array containing the guess for the
> unknowns).

[skipped]

> Emanuele

I am also new to Fortran thus my advice may not be the best possible
way to implement it.
What I did in a similar situation. I implemented each function as a
separate shared library. Then, the main program gets a list of the
function that comprise the relevant set of equations and load them
using dlopen().

In my approach, each function knows to compute its value and gradient
at given x. Hence, it is easy to construct the Jacobian matrix and use
some sort of optimization algorithm.



From: Arjen Markus on
On 24 mrt, 00:38, Enthalpy <epag...(a)email.it> wrote:
> Hello all!
>
> This is my first message to the group although since now I read
> several interesting discussions here. I'm not a professional
> programmer but I have some experience of computational programming.
>
> I'm working on the code to solve sets of non-linear equations. I'm
> writing the module that provides to the root-finding algorithm the
> values of the equations to solve (stored in the array f_vect)
> evaluated in the input point x (an array containing the guess for the
> unknowns).
>
> Here you can see a "static" version of the module; it's just able to
> provide to the root-finding routine a fixed set of equations:
>
> MODULE equations
> IMPLICIT NONE
>
> REAL, PARAMETER :: ONE = 1.
>
> CONTAINS
>
> FUNCTION f_vect(x)
> REAL, DIMENSION(:), INTENT(IN)  :: x
> REAL, DIMENSION(SIZE(x))                :: f_vect
> REAL, PARAMETER :: mp = 1.5, pmec = 1445422., a = 0.746E5, b = 0.55E5
> REAL, PARAMETER :: pmi = 963329., Ta = 288., pa = 1E5, eta_is_c = 0.8
> REAL, PARAMETER :: k = 1.4, eta_m_t = 0.95 , eta_is_t = 0.85, Ts =
> 700.
> REAL, PARAMETER :: eta_m_c = 0.95, rho = 9.
> !
> ! x(1): l'v/lv          x(2): ps                x(3): pc                x(4): mu                x(5): Tc
> !
> f_vect(1) = ONE + ONE / (rho-ONE) * ( ONE-( x(2)/x(3) )**(ONE/mp) ) -
> x(1)
> f_vect(2) = x(4) * x(1) * pmi + x(3) - x(2) - a - b*x(4)*x(1) - pmec
> f_vect(3) = SQRT( Ta / x(5) ) * x(3) / pa - x(4)
> f_vect(4) = Ta * ( ONE + ONE/eta_is_c * ( ( x(3)/pa )**( (k-ONE)/k ) -
> ONE ) ) - x(5)
> f_vect(5) = eta_m_t * eta_is_t * Ts * (ONE - ( pa/x(2) )**( (k-ONE)/
> k ) ) - ( x(5)-Ta )/eta_m_c
>
> END FUNCTION f_vect
>
> END MODULE equations
>
> This works great with my program.
>
> Now I'd like to edit the module in order to select at runtime the sets
> of equations and the unknowns (reading an input file, for example). I
> don't know how to do that.
>
> I thought to put together several module procedures comprising all the
> possible solvable equations plus the f_vect function above that this
> time should select in some way the sets of the equations (again, I
> don't know how).
>
> For what concerns the unknowns, I thought to declare all the
> parameters (like mp, pmec, a, b, pmi, Ta,...) in the global module
> area and to set the vector x as a pointer linking to the unknowns
> specified by the input file (a select case should work well on this).
> Although it's not an elegant solution, it may work. Any suggestions
> also on that?
>
> Thanks for your time reading my long post and...for my English!
>
> Emanuele

Just an idea, but what you might do to be both flexible and efficient
is:

1. Write a small program that reads simplified code like:

mp = 1.0
...

f(1) = ONE + ONE / (rho-ONE) * ( ONE-( x(2)/x(3) )**(ONE/mp) ) -
x(1)
f(2) = ...
...
f(10) = ...

2. This program then writes a small self-contained Fortran routine
with that
code:

subroutine evalf( f, n )
real, dimension(10) :: f
integer :: n

n = 10 ! The number of equations

mp = 1.0
...
f(1) = ...
...

end subroutine evalf

3. Create a makefile that builds a DLL/shared object from this code

4. Run your actual program using that DLL/shared object

The makefile could be something like (using Linux style makefiles and
compilers):

all: runprog

runprog: runprog.o evalf.so
$(LD) -o runprog runprog.o evalf.so
runprog

evalf.so: function.inp
convinput
$(FC) -shared -o evalf.so evalf.f90

where convinput is the small program to convert the input into a
(valid) Fortran routine.

This may look a bit cumbersome, but it is actually quite flexible,
though there are other possibilities too.

You may even read the values for the formula parameters from a
different file (the first time the subroutine is called for instance),
so that you do not need to rebuild the library.

Regards,

Arjen