Print

Print


Date sent:              Tue, 27 Mar 2001 11:29:47 -0500
Send reply to:          Fortran 90 List <[log in to unmask]>
From:                   Aleksandar Donev <[log in to unmask]>
Organization:           Physics & Astronomy Department
Subject:                Re: Pointers: Is this safe and legal?
To:                     [log in to unmask]

I understand your problem and have experienced the same problem myself.
The main difficulty I see with your solution is a reliance on somewhat obscure
side-effects on GLOBAL variables (e.g. the Graph pointer). Did you consider a
'conventional' reverse communication interface something like that shown below.
If so, what do you see as the main drawbacks?

MODULE OptimizeModule

   USE CGmodule    ! See below
   USE GraphMultiplyModule   ! See below

CONTAINS

   SUBROUTINE Optimize(...,graph,...,CGstate)

      TYPE(GraphType),   INTENT(INOUT) :: graph
      TYPE(CGstateType), INTENT(INOUT) :: CGstate

      ... Local Variables ...

      ....

      CALL CGforOptimize(...,graph,...CGstate,...)

      ....

   END SUBROUTINE Optimize

   SUBROUTINE CGforOptimize(...,graph,...CGstate,...)

      TYPE(GraphType),   INTENT(INOUT) :: graph
      TYPE(CGstateType), INTENT(INOUT) :: CGstate

      ! ... Conventional reverse communication interface to CG ...

      DO

         CALL CG(...,CGstate)
         SELECT CASE(CGstate%public%UserAction)
            CASE(CG_UserAction_Multiply)
               CALL GraphMultiply(...graph...)
               ...
            CASE(CG_UserAction_Precondition)
               ...
            CASE(CG_UserAction_EndSuccess)
               EXIT
            CASE(CG_UserAction_EndFailure)
               ... Process failure condition ...
         END SELECT

      END DO

   END SUBROUTINE CGforOptimize

END MODULE OptimizeModule

MODULE CGmodule

   INTEGER, PUBLIC, PARAMETER :: CG_UserAction_Multiply     = 1, &
                                 CG_UserAction_Precondition = 2, &
                                 CG_UserAction_EndSuccess   = 3, &
                                 CG_UserAction_EndFailure   = 4

   INTEGER, PRIVATE, PARAMETER :: CG_Return_Initialize        = 1, &
                                  CG_Return_AfterPreCondition = 2, &
                                  etc...

   TYPE, PUBLIC :: CGstate_public
      PUBLIC
      INTEGER :: UserAction  ! Value tells caller what action is needed
      ...
   END TYPE CGstate_public

   TYPE, PUBLIC :: CGstate_private
      PRIVATE
      ... stuff that is needed to continue next iteration ...
      ... but which is not meant to be visible to the user ...

      INTEGER :: Return = CG_Return_Initialize

   END TYPE CGstate_private

   TYPE CGstate
      PUBLIC
      public  :: CGstate_public
      private :: CGstate_private
   END TYPE CGstate

CONTAINS

   SUBROUTINE CG(...,state)

      ...
      TYPE(CGstateType), INTENT(INOUT) :: state

      ...

      SELECT CASE (state%private%Return)

         CASE(CG_ReturnTo_Initialize)
            ... First Call ... Do initialization ...
            state%private%Return    = CG_Return_AfterPrecondition
            state%public%UserAction = CG_UserAction_Precondition
         CASE(CG_Return_AfterPrecondition)
            ...
         CASE(CG_Return_xyz)
            ...

      END SELECT

      ...

   END SUBROUTINE CG

END MODULE CGmodule


MODULE GraphMultiplyModule

   TYPE, PUBLIC :: GraphType
      INTEGER, DIMENSION(:), POINTER :: graph
   END TYPE GraphType

CONTAINS

   SUBROUTINE GraphMultiply(graph)

      TYPE(GraphType), INTENT(INOUT) :: graph

      ...

   END SUBROUTINE GraphMultiply

END MODULE GraphMultiplyModule


module TrickyReverseCommunication
    integer, dimension(:), pointer [, save] :: graph ! How about SAVE here?
>
> contains
>
>     subroutine Initialize(Graph_)
>         integer, dimension(:), intent(in), target :: Graph_
>         Graph=>Graph_ ! Point to a graph data-structure
>     end subroutine Initialize
>
>     subroutine Optimize(...)
>         CALL CG(Multiply=GraphMultiply,...) ! We pass GraphMultiply to CG
>         ...
>     end subroutine Optimize
>
>     subroutine GraphMultiply()
>         ...=Graph... ! We use Graph here
>     end subroutine GraphMultiply
>
> ....
> end module TrickyReverseCommunication
>

> Hello,
>
> > IMHO, this approach is legal, but poor design. It is not thread safe
> > since there is only one copy of graph. I think a much better way is to
> > define a derived type:
> >
> >     type Opt_data
> >       integer, dimension(:), pointer :: graph
> >       ...
> >     end type Opt_data
> >
> > The user declares an object of this type, which is passed to
> > Optimize. And you need a similar design for CG.
>
> Both comments (from you and Kurt) are very correct. I am very (painfully)
> aware of the design flaw, but let me explain why I see no way out of it. If
> you do, I would appreciate any ideas. I already mentioned the problem
> earlier when I asked about ways to share an argument between two procedures.
> Also, I mentioned that what bothered me was the inexistence of an equivalent
> of C++'s classes in F90.
>
> Namely,  CG is really in a separate module and has nothing to do with
> Optimize. It is a plain Conjugate Gradient solver that should not know or
> care about what it is solving. So, changing it's design to include an
> argument Opt_data is in my opionion not a good choice. At the same time
> though, one wants to give enough freedom to the user to allow for a
> flexible, yet safe and elegant reverse communication interface for the
> preconditioner and matrix multiplication in CG. The example I showed is such
> an entangled "reverse communication" interface which uses modules to share
> data between procedures and a global pointer to share Graph between Optimize
> and GraphMultiply. *IF* we had a class-type derived data-type in which
> Opt_data would not just contain the data Graph, but also have an associated
> routine GraphMultiply that COULD be (i.e. the standard should allow this)
> passed on as an actual argument to Optimize, all would be great and the
> whole design thread safe and all. But for now modules are the only safe way
> I know of for sharing data-between procedures.
>
> Is the problem clear from this explanation? This is why I asked for a
> summary of proposed F2K changes, so I can write the code using modules for
> now, but in such a way that changing them to classes would be relatively
> easy.
>
> As to Kurt's advice, he was correct, I forgot to put TARGET on the actual
> argument, but I will do that for safety.
>
> Thanks,
> Aleksandar
>
> _____________________________________________
> Aleksandar Donev
> http://www.pa.msu.edu/~donev/
> [log in to unmask]
> (517) 432-6770
> Department of Physics and Astronomy
> Michigan State University
> East Lansing, MI 48824-1116
> _____________________________________________


Regards,
David.

----------------------------------------------------------

David Vowles
Research Officer
Department of Electrical and Electronic Engineering
The University of Adelaide
Australia 5005

Voice:     +61 8 8303 5416
Fax:       +61 8 8303 4360
Email:     [log in to unmask]
Home Page: http://www.eleceng.adelaide.edu.au/Personal/dvowles/home.html