- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Can anybody explain why the following code is not permitted?
subroutine Allocation1(Vec) class(*), allocatable, intent(out) :: Vec(:) select type(Vec) type is(real(8)) allocate(Vec(10)); Vec = 0.D0 type is(complex(8)) allocate(Vec(10)); Vec = (0.D0,0.D0) type is(integer) allocate(Vec(10)); Vec = 0 endselect endsubroutine Allocation1
Link Copied
- « Previous
-
- 1
- 2
- Next »
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Also, On the Fortran only side see:
INTERFACE GROUP_SUBS SUBROUTINE INTEGER_SUB (A, B) INTEGER, INTENT(INOUT) :: A, B END SUBROUTINE INTEGER_SUB SUBROUTINE REAL_SUB (A, B) REAL, INTENT(INOUT) :: A, B END SUBROUTINE REAL_SUB SUBROUTINE COMPLEX_SUB (A, B) COMPLEX, INTENT(INOUT) :: A, B END SUBROUTINE COMPLEX_SUB END INTERFACE ... INTEGER V1, V2 CALL GROUP_SUBS (V1, V2) ! calls INTEGER_SUB REAL V1, V2 CALL GROUP_SUBS (V1, V2) ! calls REAL_SUB ...
Now then, later, assume you add a type, say REAL(16), COMPLEX, user defined type
One would add the appropriate interface with type, and then add a specific handler (subroutine) to perform the process.
As stated earlier, one can use
Fortran INCLUDE for the body of the code sans SUBROUTINE...and variable type declarations. And you also would have to add the appropriate specific interface to the generic interface section.
FPP #include that can generate the SUBROUTINE...and variable type declarations as well as code.
Note, with appropriate #defines, the same source file can be used to generate the interface block as well as the instance of the subroutine.
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
FWIW
module foo interface Allocation subroutine Allocation_real_8(vec, n) real(8), allocatable, intent(out) :: vec(:) integer :: n end subroutine Allocation_real_8 subroutine Allocation_complex_8(vec, n) complex(8), allocatable, intent(out) :: vec(:) integer :: n end subroutine Allocation_complex_8 subroutine Allocation_integer(vec, n) integer, allocatable, intent(out) :: vec(:) integer :: n end subroutine Allocation_integer end interface Allocation contains subroutine Allocation_real_8(vec, n) real(8), allocatable, intent(out) :: vec(:) integer :: n allocate(vec(n)) vec = 0.0D0 end subroutine Allocation_real_8 subroutine Allocation_complex_8(vec, n) complex(8), allocatable, intent(out) :: vec(:) integer :: n allocate(vec(n)) vec = (0.0D0,0.0D0) end subroutine Allocation_complex_8 subroutine Allocation_integer(vec, n) integer, allocatable, intent(out) :: vec(:) integer :: n allocate(vec(n)) vec = 0 end subroutine Allocation_integer end module foo .... USE foo real(8), allocatable :: myVec(:) ... call Allocation(myVec, 123)
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
jimdempseyatthecove wrote:On the C++ side, a generic procedure relies on a template to generate the appropriate code for provided types ..
Jim,
Just curious as to how C++ came about in this thread.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
See #14 from IanH
>>You could write an interoperable C function that takes a descriptor for a Fortran pointer,...
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
jimdempseyatthecove wrote:See #14 from IanH
>>You could write an interoperable C function that takes a descriptor for a Fortran pointer,...
Jim Dempsey
Jim,
isn't that still C and not C++? Doesn't the text blurb you point out from Quote #14 refer to enhanced interoperability with C introduced starting with Fortran 2018: https://software.intel.com/en-us/fortran-compiler-developer-guide-and-reference-interoperating-with-arguments-using-c-descriptors. Sure C++ with 'extern C' facility toward a companion C processor can be expected to interoperate with Fortran provided a *conforming* Fortran processor and Fortran standard constructs are in play with the very same companion C processor. But there is no other connection or analogy to draw with anything generally in C++ and Fortran including with C++ templates, language design toward OO, is there?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Fortran calling C++ using extern "C" interface but compiled with C++ using templates. Templates in C++ can expand extern "C" code too.
It appears to me at least that the OP wants some language characteristics in Fortran as they have in C++ (or other oop language). In a particular "auto" typing seems to be desired. To me, while these efforts to have type agnostic programming are a benefit to maintainability and re-useability of code, I think that they are counter-productive for attaining performance. Complex simulation problems require performance. Keep in mind that to be truly type agnostic, the runtime system would either have to be an interpreter or include JIT capability. It may be that at some point in compiler development the JIT route can potentially be as efficient as explicit typing (after overhead is amortized).
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
jimdempseyatthecove wrote:..
It appears to me at least that the OP wants some language characteristics in Fortran as they have in C++ (or other oop language) .. I think that they are counter-productive for attaining performance. ..
Jim,
It's not clear what is wanted by OP. A couple of points to consider:
- Note the original post is different from Quote #8. Considering what the Fortran standard offers in terms of ALLOCATE statement, especially with SOURCE= and MOLD= options, and also with allocation on assignment, the code such as in original post toward a generic that allocates arrays of intrinsic types is superfluous.
- When a library method in C such as MPI_WIN_ALLOCATE_SHARED is what is really 'alloc'ing the array and if it's done once or a few times during program/library 'initialization' stage, performance may not be an issue but convenience can be important. And what may be relevant is only that an object in Fortran with a POINTER attribute get associated with the C pointer to the allocated data. In this case the code in the original post and any OO type of generic pursuits are again irrelevant. OP may then simply go with C_F_POINTER route as shown in Quote #19, a simpler option where the Fortran object (fptr) details are grabbed via host association. Or if host association is not to be employed and the Fortran object (fptr) is to made available to a separate subprogram via the argument (parameter) list, then OP can try the more involved C descriptor approach using Fortran 2018 features. Either way, an attempt toward templated/generic interfaces, like in the original post, appears unnecessary.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
>>isn't that still C and not C++?
The interoperability of Fortran and C deal only with the function interface, and not with the capability of the compiler. extern "C" foo(.... only affects the calling convention (and as importantly if the caller/callee encodes exception handling). The body of the function, as well as the function entry can use any of the C++ features including being generated via template.
The point I was trying to make type agnostic programming (at least that is my take of it), and IanH suggested a potential possibility was to use interoperability with C to aid in that process. Presumably through use of templates. I was only pointing out that if you add types on the Fortran side, that you will also have to address this on the "C" side. At this point in time, it is about a similar amount of work use generic interface and copy&paste code blocks. (or use FPP or CPP or Python BlockIt to give you ersatz templates).
RE: your 2.
The OP's code in #1 is an array descriptor (of unknown class), and that that array descriptor is to be returned with the intended allocation. (Setting aside Steve's observation of intent(out) deallocating the output arg, and thus de-classifying it). While a pointer could have been the actual argument, it also can be an actual array descriptor. In this case, the allocation function cannot grab a blob of data from some allocator, and manufacture a pointer into the output argument. It would have to construct a workable array descriptor, however the OP must be aware that that returned array descriptor is unsuitable for use with a Fortran DEALLOCATE.
Jim Dempsey
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page
- « Previous
-
- 1
- 2
- Next »