- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hello,
I am not sure if the follwoing approach is allowed by fortran standards. I read the language reference but I could not understand the rules. Can you help me with the following code snippet. If it is not allowed can you suggest me an alternative approach. I have constructed this exmple based on the structure of a another code i am working on.
thanks
Reddy
I am not sure if the follwoing approach is allowed by fortran standards. I read the language reference but I could not understand the rules. Can you help me with the following code snippet. If it is not allowed can you suggest me an alternative approach. I have constructed this exmple based on the structure of a another code i am working on.
thanks
Reddy
[fortran]module genIfaceTest_m
implicit none
! The idea here is that Printer needs a PrinRoutine
! which can take Real or complex argument.
! The user of the printer will be aware whether
! the printer will be used for printing a real or a complex
! and accordingly call
! printer%printRoutine(C) or printer%printRoutine
! The user must provide a prinRoutine to intiate the printer
type Printer_t
real :: R
complex :: C
procedure(genPrint), pointer, nopass :: printRoutine => null()
contains
procedure :: init => init_printer
end type Printer_t
interface genPrint
subroutine PrintReal
real :: R
end subroutine PrintReal
subroutine PrintComplex(C)
complex :: C
end subroutine PrintComplex
end interface genPrint
contains
subroutine init_printer(this,printRoutine)
class(Printer_t), intent(inout) :: this
procedure(genPrint) :: printRoutine
this%printRoutine => printRoutine
end subroutine init_printer
end module genIfaceTest_m
!-----------------------------------
!ifort -V
!Intel Fortran Intel 64 Compiler XE for applications running on Intel 64, Ver
!sion 12.1.0.233 Build 20110811
!Copyright (C) 1985-2011 Intel Corporation. All rights reserved.
!FOR NON-COMMERCIAL USE ONLY
! Compile command
! ifort filename.F90
! Error Message::
!gendummyProc.F90(23): error #8182: The name is neither an abstract interface nor
! a procedure with an explicit interface. [GENPRINT]
! procedure(genPrint) :: printRoutine
[/fortran] Link Copied
4 Replies
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The interface that you nominate for a pointer or deferred binding must be for a particular procedure or abstract interface - not a generic interface as in your example.
Some alternatives are available (such as using type extension to provide specific procedures for deferred bindings in Printer_t or perhaps another separate type) - but what's best depends on what you are trying to do. Perhaps provide a little more description - "who" is providing the procedures and "who" is calling them?
Some alternatives are available (such as using type extension to provide specific procedures for deferred bindings in Printer_t or perhaps another separate type) - but what's best depends on what you are trying to do. Perhaps provide a little more description - "who" is providing the procedures and "who" is calling them?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Let me see if i can explain the problem. Otherwise i will try to construct a better example.
I need to use a derivied type which can handle both complex and real data variables. The underlying structure of the derived type is same except that in one instance i will compute a function which will use real data and another instance of the derived type will do the calculation using complex data. In printer code,
i will create two instances.
type(Printer_t) :: rPrinter
type(Printer_t) :: cPrinter
To intitate the printers, i will do this
call rPrinter%init(rPrinterRoutine)
call cPrinter%init(cPrinterRoutine)
where rPrinterRoutine and cPrinterRoutine are sepecific subroutine which the user provides.
the actual problem that i am working on is the following. I am constructing a derived type which will be used for assembling a matrix in the finite element method. The user must provide a subrotuine for evaluating the element matrix which can be complex data or real data. One option i can think of is to make the data complex by default and use it for real or complex element matrix. Or i create seperate bindings for complex and real subrotuines and make the init generic instead. What i am doing right now is keep the init procedure specific and let the binding be generic but as you tell this seem to be a problem.
I need to use a derivied type which can handle both complex and real data variables. The underlying structure of the derived type is same except that in one instance i will compute a function which will use real data and another instance of the derived type will do the calculation using complex data. In printer code,
i will create two instances.
type(Printer_t) :: rPrinter
type(Printer_t) :: cPrinter
To intitate the printers, i will do this
call rPrinter%init(rPrinterRoutine)
call cPrinter%init(cPrinterRoutine)
where rPrinterRoutine and cPrinterRoutine are sepecific subroutine which the user provides.
the actual problem that i am working on is the following. I am constructing a derived type which will be used for assembling a matrix in the finite element method. The user must provide a subrotuine for evaluating the element matrix which can be complex data or real data. One option i can think of is to make the data complex by default and use it for real or complex element matrix. Or i create seperate bindings for complex and real subrotuines and make the init generic instead. What i am doing right now is keep the init procedure specific and let the binding be generic but as you tell this seem to be a problem.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The correct syntax for generic type-bound procedures is:
[fortran] type :: t1
real:: r
complex:: c
contains
procedure :: init_r
procedure :: init_c
generic :: init => init_r, init_c
end type
[/fortran] Where the procedures init_r and init_c already exist. If you want the user to strictly provide the init_r and init_c procedures, then:[fortran]module mod1
type, abstract :: t1
real :: r
complex :: c
contains
procedure(i_real_proc), deferred :: init_r
procedure(i_complex_proc), deferred :: init_c
generic :: init => init_r, init_c
end type
abstract interface
subroutine i_real_proc(this, r)
import
class(t1), intent(INOUT) :: this
real, intent(IN) :: r
end subroutine
subroutine i_complex_proc(this, r)
import
class(t1), intent(INOUT) :: this
complex, intent(IN) :: r
end subroutine
end interface
end module
[/fortran] Since both subroutines have been deferred, this option requires the user to provide them when extending the abstract type, even if he only intends to use one of them ---you could provide some dummy subroutines (e.g., dummy_init_r and dummy_init_c) that do nothing but match the abstract interfaces, so that the user has an easy way to provide the one he intends not to use:[fortran]module usermod
use mod1
type, extends(t1) :: usert
contains
procedure :: init_r => user_init_r
procedure :: init_c => dummy_init_c
end type
contains
subroutine user_init_r(this, r)
...
end usermod
[/fortran]You could even declare t1 non-abstract from the beginning and just provide the two dummy ones, but then the user might not bother to override them and then complain that your code doesn't work :) .One interesting option is to work with the data types you want and let the user handle the details he wants, for example:
[fortran]module mod2
use iso_fortran_env
implicit none
private
type, abstract, public :: t1
class(*), allocatable :: d(:)
contains
procedure(i_printer_proc), deferred :: printer
procedure :: mycode
end type
abstract interface
subroutine i_printer_proc(this)
import
class(t1), intent(IN) :: this
end subroutine
end interface
contains
subroutine mycode(this, input)
class(t1), intent(INOUT) :: this
class(*), intent(IN) :: input
class(*), allocatable :: copy(:)
!check if type is supported
select type (input)
type is (real)
type is (complex)
class default
write (ERROR_UNIT, '(/ A)') 'Unsupported type'
return
end select
allocate (this%d(9), SOURCE = input)
!do something
select type (e => this%d)
type is (real)
e = e ** 2
type is (complex)
e = CONJG(e)
end select
!print
call this%printer()
end subroutine
end module mod2
module mod3
use mod2
implicit none
type, extends(t1), public :: usert
contains
procedure :: printer => user_printer
end type
contains
subroutine user_printer(this)
class(usert), intent(IN) :: this
real, allocatable :: r(:)
complex, allocatable :: c(:)
select type(e => this%d)
type is (real)
allocate (r(SIZE(e)))
r = e
write (*, '(/ "real:" / (3F4.1))') r
type is (complex)
allocate (c(SIZE(e)))
c = e
write (*, '(/ "complex:" / (3(:"(", F4.1, ",", F4.1, ")")))') c
end select
end subroutine
end module mod3
use mod3
implicit none
type(usert) :: a
complex :: aux = CMPLX(3., -2)
call a%mycode(1)
call a%mycode(2.)
call a%mycode(aux)
end[/fortran] In this case, you provide mod2, which must handle any of the supported data types, and ignore the unsupported ones. The user can do something similar ---i.e., it's up to the user to have a printer for a certain data type.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks John for the interesting alternatives. When i started coding for the project, intel did not support source= allocation for unlimited polymorphic objects so i had to keep the data types specific. But now intel compiler does suppport this featrue. I will try to mkae use of your suggestions.
Reddy
Reddy
Reply
Topic Options
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page