Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
28440 Discussions

Building a level-one equation solver from a level-zero equation solver

NotThatItMatters
Beginner
705 Views

I have a function class which takes some parameters as arguments and returns functional values.  This is something along the lines of

TYPE, EXTENDS(FuncBase) :: FuncBunch
    INTEGER, PRIVATE :: Nn
    INTEGER, DIMENSION(:), ALLOCATABLE, PRIVATE :: Data_Set
    ! 0 = first constraint, 1 = second constraint
    INTEGER, PRIVATE :: DataConstraint
    ! 0 = single bunch constraint, 1 = two bunch constraints
    INTEGER, PRIVATE :: IConstraint ! Constraint_Type
    ...
CONTAINS
    PROCEDURE :: Func => Func_Bunch
    PROCEDURE :: FuncV => FuncV_Bunch
    PROCEDURE :: FDJAC => FDJAC_Bunch
    PROCEDURE :: MaximumStep => MaximumStep_Bunch
    PROCEDURE, ...
END TYPE FuncBunch

The idea here is that there are scalar functions Func and vector functions FuncV both of which need to be solved (values == 0.0).  I have some basic root solvers in a separate class to solve the single-variable and multi-variable cases.  The solver itself lies in a module with solvers for this class and other classes.  This module has a subroutine of the form

SUBROUTINE SOLVE_BUNCH(FBUNCH, Parameter1, Parameter2, ...)
    TYPE (FuncBunch), INTENT(INOUT) :: FBUNCH
    ...
END SUBROUTINE SOLVE_BUNCH

I need to extend this example to solve many sets of FuncBunch equations (Func_Bunch or FuncV_Bunch) with an overriding constraint.  The idea I had was to create a new class of the form

TYPE, EXTENDS(FuncBase) :: FuncMultiBunch
    INTEGER, PRIVATE :: Nn
    INTEGER, DIMENSION(:), ALLOCATABLE, PRIVATE :: DataSet
    INTEGER, DIMENSION(:), ALLOCATABLE, PRIVATE :: Topology
    ! 0 = first constraint, 1 = second constraint
    INTEGER, PRIVATE :: DataConstraint
    ! 0 = single rate constraint, 1 = two rate constraints
    INTEGER, PRIVATE :: IConstraint ! Constraint_Type
    ...
    INTEGER, PRIVATE :: NFB
    CLASS (FuncBunch), DIMENSION(:), ALLOCATABLE, PRIVATE :: mFB
    ...
CONTAINS
    PROCEDURE :: Func => Func_MultiBunch
    PROCEDURE :: FuncV => FuncV_MultiBunch
    PROCEDURE :: FDJAC => FDJAC_MultiBunch
    PROCEDURE :: MaximumStep => MaximumStep_MultiBunch
    ...
END TYPE FuncMultiBunch

The idea would be to use a similar solver as the first, only the internals of the SOLVE_MULTIBUNCH would be to solve each FuncBunch individually with the level-one constraints involving sums or maxima applying.

The trouble I am having lies in getting the MULTIBUNCH to talk with the underlying SOLVE_BUNCH routine.  I cannot seem to use the mFB from FuncMultiBunch within SOLVE_BUNCH because FBUNCH is INTENT(INOUT) and any accessors I use would only be expressions or constants.  How might I accomplish this?  Might function pointers, a concept of which I am unfamiliar, help?

0 Kudos
1 Solution
andrew_4619
Honored Contributor II
705 Views

Module_A  Submod_A1 Submod_A2 Submod_A3

Module_B  Submod_B1 Submod_B2 

module A contains shared data and interfaces for A1, A2, A3 that have the contained routines

module B contains shared data and interfaces for B1, B2 that have the contained routines

So routines in A1 A2 and A3 can all see each other and can USE routines in B
routines in B1 and  B2 can all see each other and can USE routines in A
Arrange the modules in anyway that is logical you are not restricted by dependencies.
 
 

View solution in original post

0 Kudos
18 Replies
Li_L_
New Contributor I
705 Views

in type <FuncMultiBunch>

you can write a procedure to throw a mFB pointer

then 

CLASS (FuncBunch),pointer:: ptr => <funcmultibunch>%throw_mfb_ptr(i)

call SUBROUTINE SOLVE_BUNCH(ptr,parameters...)

 

is that ok?

0 Kudos
NotThatItMatters
Beginner
705 Views

Sounds good.  How would that change the original implementation and call sequence for SOLVE_BUNCH?  Do I need to explicitly call it with pointers to FuncBunch rather than FuncBunch targets?

I'm a little new to this concept.

0 Kudos
Arjen_Markus
Honored Contributor I
705 Views

No, you don't need any special syntax to call a function via a function pointer (or a subroutine via a subroutine pointer). I find that a very elegant feature :).

0 Kudos
Li_L_
New Contributor I
705 Views

NotThatItMatters wrote:

Sounds good.  How would that change the original implementation and call sequence for SOLVE_BUNCH?  Do I need to explicitly call it with pointers to FuncBunch rather than FuncBunch targets?

I'm a little new to this concept.

i think i'm not completely got your meaning

in my understanding, if you wanna solve <mfb> in module funcMultiBunch, you can call solve_bunch(funcMultibunch%mfb...) directly, because private attr wouldn't stop the access from the same module

if you want call solve_bunch from the son module of funcMultiBunch, you have to write a pointer procedure to access the <mfb>

 

solver module is the ancient module of all other type modules.

0 Kudos
NotThatItMatters
Beginner
705 Views

I am calling SOLVE_BUNCH from another module, call it the MultipleBunchConstraint module.  SOLVE_BUNCH itself exists in the SingleBunchConstraint module.  The definition of FuncBunch exists in the FuncBunch_Module module.  The definition of FuncMultiBunch exists in the FuncMultiBunch_Module module.

I know this seems a little extreme, but I have designed this to keep the class (type) definitions separate from the solvers and ultimately keep them separate from the modules which use the solvers.  This is to keep away from circular module and class references which have plagued the code in the past.

0 Kudos
andrew_4619
Honored Contributor II
705 Views

SUBMODULE is the future it gets rid of all that circular dependence problem and stops you wasting your life on build cascades.

0 Kudos
NotThatItMatters
Beginner
705 Views

So, with SUBMODULEs the idea is MultipleBunchConstraint is the module with SingleBunchConstraint the SUBMODULE?  Is accessibility from the outside of SingleBunchConstraint straightforward?

If you thought I was new to pointers, the newness with SUBMODULEs is quite a bit more.

0 Kudos
andrew_4619
Honored Contributor II
706 Views

Module_A  Submod_A1 Submod_A2 Submod_A3

Module_B  Submod_B1 Submod_B2 

module A contains shared data and interfaces for A1, A2, A3 that have the contained routines

module B contains shared data and interfaces for B1, B2 that have the contained routines

So routines in A1 A2 and A3 can all see each other and can USE routines in B
routines in B1 and  B2 can all see each other and can USE routines in A
Arrange the modules in anyway that is logical you are not restricted by dependencies.
 
 
0 Kudos
NotThatItMatters
Beginner
705 Views

Thank you.  I read a bit after I posted that last (idiotic) post and realized my idiocy.  You have described it in such a way that even I can understand.

0 Kudos
NotThatItMatters
Beginner
705 Views

Okay, my code has come upon another impasse.  The FuncMultiBunch class is defined as follows:

TYPE, EXTENDS(FuncBase) :: FuncMultiBunch
    INTEGER, PRIVATE :: Nn
    INTEGER, DIMENSION(:), ALLOCATABLE, PRIVATE :: DataSet
    INTEGER, DIMENSION(:), ALLOCATABLE, PRIVATE :: Topology
    INTEGER, PRIVATE :: NFB
    CLASS (FuncBunch), DIMENSION(:), POINTER, PRIVATE :: mFB
CONTAINS
    PROCEDURE :: Func => Func_MultiBunch
    PROCEDURE :: FuncV => FuncV_MultiBunch
    PROCEDURE :: FDJAC => FDJAC_MultiBunch
    PROCEDURE :: MaximumStep => MaximumStep_MultiBunch
    ...
    PROCEDURE :: Get_FB
    ...
END TYPE FuncMultiBunch
TYPE (FuncBunch), DIMENSION(:), ALLOCATABLE, TARGET, PRIVATE :: FBactual

The PROCEDURE Get_FB is defined as follows:

FUNCTION Get_FB(this, N) RESULT(ptr)
    CLASS (FuncMultiBunch), INTENT(IN) :: this
    INTEGER, INTENT(IN) :: N

    TYPE (FuncBunch), POINTER :: ptr
    IF (N > 0 .AND. N <= this%Nn) THEN
        ptr => this%mFB(N)
    ELSE
        ptr => NULL()
    END IF
END FUNCTION Get_FB

The question lies in the use of Get_FB.  I am using it in various places within the enclosing module without compilation trouble.  However, in attempting to use it outside the module proper, I am getting Error #8346, A function reference cannot be used as the leftmost part-ref of structure component.  What am I missing?

0 Kudos
IanH
Honored Contributor II
705 Views

Could you show a typical line of code that the error is reported against?  The message suggests that you have syntax akin to `object%Get_FB()%xyz`, which is not permitted.

Functions with a data pointer result that can sensibly return dissociated pointers make me a little nervous... it suggests to me that the function should instead be a subroutine.

0 Kudos
NotThatItMatters
Beginner
705 Views

Here is a "one-liner" that fails.  As you might have guessed, I am changing the names to protect the ....

SUBROUTINE DO_SOMETHING(FMB, ...)
USE FuncMultiBunch_Module, ONLY : FuncMultiBunch
TYPE (FuncMultiBunch), INTENT(INOUT) :: FMB
REAL QFloat
QFloat = 0.0
QFloat = QFloat + FMB%Get_FB(M)%Get_A_Float()
END SUBROUTINE DO_SOMETHING

This line is giving me the headache.

0 Kudos
NotThatItMatters
Beginner
705 Views

The following "equivalent" code compiles without error:

SUBROUTINE DO_SOMETHING(FMB, ...)
USE FuncMultiBunch_Module, ONLY : FuncMultiBunch
USE FuncBunch_Module, ONLY : FuncBunch
TYPE (FuncMultiBunch), INTENT(INOUT) :: FMB
REAL QFloat
TYPE (FuncBunch) :: FBlocal
QFloat = 0.0
FPlocal = FMB%Get_FB(M)
QFloat = QFloat + FPlocal%Get_A_Float()
END SUBROUTINE DO_SOMETHING

The creation of a local version of the FuncBunch TYPE allows the code compilation.  Now, provided I am not leaving uninitialized pointers or similar, will this actually work?  Is there anything inherently wrong with what I am trying to do?

0 Kudos
NotThatItMatters
Beginner
705 Views

There is a typo here: FPlocal in the last line should be FBlocal.

0 Kudos
IanH
Honored Contributor II
705 Views

Line 6 of the code in #13 has the invalid syntax I was referring to - you are not permitted to have a function reference to the left of the % .

Your function returns a pointer, which presumably (?) means that you want to reference the original object.  An assignment statement creates a copy of the value that is returned by the function reference.  Perhaps you want the temporary to be a pointer, and define it through pointer association.

TYPE (FuncBunch), POINTER :: FBLocal
FBLocal => FMB%Get_FB (M)
QFloat = QFloat + FBLocal%Get_A_Float ()

You can also use the associate construct to achieve the equivalent.

You need to think about what will happen when your function reference returns a dissociated pointer.

0 Kudos
NotThatItMatters
Beginner
705 Views

What is the difference between my line and a reference within a PROCEDURE that is part of FuncMultiBunch which says

iItem = this%Get_FB(M)%Get_A_Number()

Are these items trouble?  They compile up fine.

I understand the idea of disassociation.  I have several catches.

0 Kudos
IanH
Honored Contributor II
705 Views

If Get_FB really is a binding in the code in #17 (and not an array component reference), then the code should not compile. If the compiler is compiling such code, then I expect that would be regarded by the compiler support people as a bug.

0 Kudos
NotThatItMatters
Beginner
705 Views

Sorry, that was not what I have in code.  What I have in code is

this%mFB(M)%Get_A_Number()

This is much different.  Sorry.

0 Kudos
Reply