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

Allocating using CLASS(*) as MOLD

holysword
Novice
717 Views

Hello there!

Is there any smart and elegant way to allocate a variable to have the same dimensions as polymorphic class?

Example:

SUBROUTINE Allocate_Thing(icls,ocls)
  CLASS(*), DIMENSION(:,:), INTENT(IN) :: icls
  INTEGER,  DIMENSION(:,:), POINTER    :: ocls
  
  ALLOCATE(ocls, MOLD=icls)
  (...)
END SUBROUTINE

The above snippet doesn't work, obviously, because MOLD does not take polymorphic classes as argument. In this particular case I could use ALLOCATE(ocls(SIZE(icls,1), SIZE(icls,2))), but I would like to have a generic expression, if there is any trick to do so. The reason is that I'm using preprocessor tricks to get this done for many ranks.

Also, when is it planned for Intel Fortran to support assumed rank polymorphic classes?

Thanks in advance!

0 Kudos
9 Replies
Steven_L_Intel1
Employee
717 Views

The restriction is actually, "C638 (R626) Each allocate-object shall be type compatible (4.3.1.3) with source-expr ." Following the link, we read, "A nonpolymorphic entity is type compatible only with entities of the same declared type." Since ocls is nonpolymorphic, it is not type compatible with CLASS(*) which has no declared type.

I can tell you only that polymorphic assumed-rank dummy arguments aren't supported in the upcoming 17.0. It might get added in the next major release after that.

0 Kudos
holysword
Novice
717 Views

Steve Lionel (Intel) wrote:

The restriction is actually, "C638 (R626) Each allocate-object shall be type compatible (4.3.1.3) with source-expr ." Following the link, we read, "A nonpolymorphic entity is type compatible only with entities of the same declared type." Since ocls is nonpolymorphic, it is not type compatible with CLASS(*) which has no declared type.

I can tell you only that polymorphic assumed-rank dummy arguments aren't supported in the upcoming 17.0. It might get added in the next major release after that.

Thank you for your reply.

Do you know of any workaround for the above problem? ALLOCATE(ocls(SHAPE(icls))) also doesn't work because the argument in ocls() needs to be a scalar. I cannot think of any elegant solution in this situation.

0 Kudos
Steven_L_Intel1
Employee
717 Views

The only method I can think of is the one you rejected earlier. I note that UBOUND would also work but SIZE is better because it's more obvious that you want the extent. UBOUND would give you the same value in this usage.

0 Kudos
FortranFan
Honored Contributor II
717 Views

holysword wrote:

.. Also, when is it planned for Intel Fortran to support assumed rank polymorphic classes? ..

Say you had access to a compiler supporting assumed rank dummy arguments that are polymorphic, a feature from pending revision to the Fortran standard: how would it help with what you are trying to achieve?  Would not the constraint on assumed rank dummy argument, as proposed in the draft standard, restrict what you can do with the object you want to be allocated (ocls)?

13 C539 An assumed-rank variable name shall not appear in a designator or expression except as an actual
14 argument that corresponds to a dummy argument that is assumed-rank, the argument of the function
15 C LOC from the intrinsic module ISO C BINDING (15.2.3.6), or the first dummy argument of an intrinsic
16 inquiry function.

 

0 Kudos
FortranFan
Honored Contributor II
717 Views

Steve Lionel (Intel) wrote:

The only method I can think of is the one you rejected earlier. ..

Steve,

In the context of generic programming as alluded to by OP, it would appear an option for someone interested in implementing such a facility for themselves can be, say, a MOLD_ALLOC procedure ala MOVE_ALLOC intrinsic.  Then with the facilities offered by the draft of the upcoming standard revision (2015?), the following code would be standard-conforming I presume:

module m

   implicit none

   private

   !.. This is supported by the draft standard for Fortran 201X (2015?)
   generic, public :: mold_alloc => mold_alloc_rank0_int, mold_alloc_rank0_real,                    &
                                    mold_alloc_rank1_int, mold_alloc_rank1_real,                    &
                                    mold_alloc_rank2_int, mold_alloc_rank2_real
   !.. Elided are additional overloads up to the maximum rank allowed in the standard

contains

   subroutine mold_alloc_rank0_int( ptr, mold )

      type(integer), intent(inout), pointer :: ptr
      class(*), intent(in), optional        :: mold

      include 'a.f90'

      return

   end subroutine mold_alloc_rank0_int

   subroutine mold_alloc_rank0_real( ptr, mold )

      type(real), intent(inout), pointer :: ptr
      class(*), intent(in), optional     :: mold

      include 'a.f90'

      return

   end subroutine mold_alloc_rank0_real

   subroutine mold_alloc_rank1_int( ptr, mold )

      type(integer), intent(inout), pointer :: ptr(:)
      class(*), intent(in)                  :: mold(:)

      include 'b.f90'

      return

   end subroutine mold_alloc_rank1_int

   subroutine mold_alloc_rank1_real( ptr, mold )

      type(real), intent(inout), pointer :: ptr(:)
      class(*), intent(in), optional     :: mold(:)

      include 'b.f90'

      return

   end subroutine mold_alloc_rank1_real

   subroutine mold_alloc_rank2_int( ptr, mold )

      type(integer), intent(inout), pointer :: ptr(:,:)
      class(*), intent(in)                  :: mold(:,:)

      include 'c.f90'

      return

   end subroutine mold_alloc_rank2_int

   subroutine mold_alloc_rank2_real( ptr, mold )

      type(real), intent(inout), pointer :: ptr(:,:)
      class(*), intent(in)               :: mold(:,:)

      include 'c.f90'

      return

   end subroutine mold_alloc_rank2_real

end module m
      !.. include a.f90
      allocate( ptr )
      if ( present(mold) ) then        
      end if
      !.. include b.f90
      allocate( ptr(size(mold)) )
      !.. include c.f90
      allocate( ptr(size(mold,dim=1), size(mold,dim=2)) )

 

So you can see it is somewhat limiting to actual practitioners with the need for include files and duplicate code for the types they wish to support.  What do you think, from an Intel Fortran compiler foundation point-of-view, would be a reasonable enhancements to the standard that will help coders to overcome such limitations?  Do you think parameterized modules or some other ways to provide generic type facility possible in the next standard following the one in the works now?  Consider the following pseudo code, is this something viable for implementation in ifort, say if it were to be on the table for proposed changes to the standard?

module m

   implicit none

   private

   !.. This is supported by the draft standard for Fortran 201X (2015?)
   generic, public :: mold_alloc => mold_alloc_anyrank

   !.. This is currently not supported
   generic, type :: T => integer, real  !.. And any additional types desired by coder per a strict set to rules and constraints

contains

   subroutine mold_alloc_anyrank( ptr, mold )

      type(T), intent(inout), pointer :: ptr(..)
      class(*), intent(in), optional  :: mold(..)

      !.. This is currently not supported
      allocate( ptr, shape=shape(mold) )

      return

   end subroutine mold_alloc_anyrank

end module m

 

0 Kudos
Steven_L_Intel1
Employee
717 Views

FortranFan, I had assumed that the question about assumed-rank polymorphic arguments was unrelated to the question about ALLOCATE.

For your "generic" question, note that the current F2015 draft includes a SELECT RANK construct similar in concept to SELECT TYPE, which makes at least your first example a bit simpler.  The committee knows there is interest in generic programming, but the notion of rank not known at compile-time is very foreign to Fortran at this time. The allocate is really the least interesting part of this; I think the committee would have a hard time accepting such a sweeping change as to introduce "dynamic rank", but that's just my opinion.

0 Kudos
FortranFan
Honored Contributor II
717 Views

Thanks, Steve, for your explanation.

My downloaded copy of the draft 2015 standard was outdated enough that it didn't mention SELECT RANK.  I have downloaded what I think is the latest draft and yes, I see it now; one way it can help is to condense multiple include files in my snippet above into a single one.

I can relate to your comment about standards committee having issues with 'dynamic rank.  But I'm personally not advocating it; I just brought it up as a possible use case given the original post.  But what I'm most interested in is the generic types kind of facility where everything would be 'known at compile time', just that some sort of preprocessor or multiple pass aspects may come into play for an implementation to get at the full picture.

0 Kudos
Steven_L_Intel1
Employee
717 Views

Assumed-rank polymorphic might actually make it into the 17.0 product.

0 Kudos
Steven_L_Intel1
Employee
717 Views

It looks as if assumed-rank polymorphic will be in the 17.0 product release.

0 Kudos
Reply