Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations strongm on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Deferred Procedures and/or Procedure Pointers

Status
Not open for further replies.

xcboxer

Programmer
Nov 12, 2012
1
US
Hey Guys,

I don't think I'm asking for much, so let me describe what functionality I need (slash hope exists!) and see if anybody know something about it! The basic idea is that in large scale computations avoiding unnecessary if statements is a must, hence a lot of procedures are initialized at the beginning of the simulation via procedure pointers. We want to clean up this process by using classes, but are running into a wall as to whether or not Fortran supports the functionality we need. A basic example before I get to what I really want...the following code will compile, i.e., gfortran/ifort -c test.F90 has no issues:

Code:
MODULE test_m

IMPLICIT NONE

TYPE,PUBLIC :: test
  PROCEDURE(test1),NOPASS,POINTER :: test1ptr
END TYPE test

ABSTRACT INTERFACE
  SUBROUTINE test1()
    IMPLICIT NONE
  END SUBROUTINE test1
END INTERFACE

END MODULE test_m

Now let's imagine a more realistic scenario...perhaps one in which the test type contains variables that we would like to have access to when calling that procedure pointer test1ptr. The following code will compile and run with gfortran, but not ifort. Note that the only change is that we want to PASS the object into the procedure.

test.F90:
Code:
MODULE test_m

IMPLICIT NONE

TYPE,PUBLIC :: test
  PROCEDURE(test1),POINTER :: test1ptr
END TYPE test

ABSTRACT INTERFACE
  SUBROUTINE test1(THIS)
    IMPORT
    IMPLICIT NONE
    CLASS(test),INTENT(IN) :: THIS
  END SUBROUTINE test1
END INTERFACE

PUBLIC :: temp

CONTAINS

  SUBROUTINE temp(THIS)
    IMPLICIT NONE
    CLASS(test),INTENT(IN) :: THIS
    WRITE (*,*) 'Hello world from the object!'
  END SUBROUTINE temp

END MODULE test_m

helloworld.F90
Code:
PROGRAM helloworld

USE test_m

TYPE(test) :: tester

tester%test1ptr => temp
CALL tester%test1prt()

END PROGRAM helloworld

If gfortran was the only compiler that existed I guess we would be OK, but getting tied down to a specific compiler is something to avoid I think...especially since we don't have control over the compilers on all of the machines we use. Now for the main point...is there any way we can do this properly with type-bound procedures? For example, in an ideal world we could do the following, but I think it's a long shot that something for this is legal:

abstracttype.F90
Code:
MODULE abstracttype_m

IMPLICIT NONE

TYPE,PUBLIC,ABSTRACT :: abstracttype
  CONTAINS
    PROCEDURE(iface),PUBLIC,DEFERRED :: testproc
END TYPE abstracttype

ABSTRACT INTERFACE
  SUBROUTINE iface(THIS)
    IMPORT
    CLASS(abstracttype),INTENT(IN) :: THIS
  END SUBROUTINE iface
END INTERFACE

END MODULE abstracttype_m

derived.F90
Code:
MODULE derivedtype_m

IMPLICIT NONE

TYPE,EXTENDS(abstracttype) :: derivedtype
  CONTAINS
   PROCEDURE,PUBLIC :: testproc => (WAIT TO DEFINE THIS UNTIL INITIALIZATION)
END TYPE derivedtype

END MODULE derivedtype_m

Does anybody know if the second option where we had a procedure pointer with passing is officially allowed in the Fortran standard? It seems like it would be a huge hinderance to not allow simple passing like was shown in the option. Maybe it's just a bug in the intel compiler...






 
Well, this is far beyond my expertise. Just one comment:

If gfortran was the only compiler that existed I guess we would be OK, but getting tied down to a specific compiler is something to avoid I think...especially since we don't have control over the compilers on all of the machines we use.

If you want to have your code between different compilers you will have to stick to the fortran standard. Especially gfrotran - at least in the older versions - was much advanced and incorporated features of a later standard than that it was named for. For instance g77 held some features of fortran 95 and it seems to be the same here: I could not find anything about an 'abstract interface' in my old Compaq f90/f95 compiler.

But why would you want to do this? gfortran comes free of charge as far as I know, so there seems to be no issue on having it implemented whereever you work.

And, if you do not mind my saying, if you do not have control of the compilers you are to use in your project, well, I would rethink my position if I were in your shoes.


Norbert


The optimist believes we live in the best of all possible worlds - the pessimist fears this might be true.
 
Abstract interface seems to be Fortran 2003 standard. Maybe it's implemented in gfortran, but not in the Intel Fortran version you have...
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top