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

"Passing" allocatable arrays of different sizes to module

jirina
New Contributor I
443 Views

I have several modules, each of them containing an allocatable array of a generally different size:

       module Temperature
       real*4, allocatable, dimension(:,:,:) :: T
       end module Temperature
       
       module Pressure
       real*4, allocatable, dimension(:,:,:) :: p
       end module Pressure

I have another module that I would like to process allocatable arrays from the modules above, so I have

       module ScalarOperations
       
       real*4, allocatable, dimension(:,:,:) :: scalar
       
       contains
       
       subroutine InitializeScalar ( )
       scalar = 0.0
       return
       end subroutine InitializeScalar
       
       end module ScalarOperations

I would like to do this:

       module Temperature
       
       real*4, allocatable, dimension(:,:,:) :: T
       
       contains
       
       subroutine AllocateAndInitializeTemperature ( )
       use ScalarOperations
       allocate ( T(10,20,30) )
       scalar = T
       call InitializeScalar ( )
       end subroutine AllocateAndInitializeTemperature
       
       end module Temperature

The source code line "scalar = T" is probably wrong and my question is what I should/can do to assign allocatable fields "T" and "p" to the allocatable array "scalar".

        

 

0 Kudos
7 Replies
Arjen_Markus
Honored Contributor I
443 Views

Why not simply pass the array to the iniitialisation routine:

       module ScalarOperations
       
       contains
       
       subroutine InitializeScalar ( scalar )
       real*4, allocatable, dimension(:,:,:) :: scalar

       scalar = 0.0
       return
       end subroutine InitializeScalar
       
       end module ScalarOperations

It is a lot clearer than using module variables - your intended solution would require pointer variables instead of allocatables.

(Side note: real*4 is not standard Fortran - better use real(kind=...), like real(kind=kind(1,0)) or the like)

 

0 Kudos
jirina
New Contributor I
443 Views

The main reason I wanted "scalar" to be a module variable is that there will be more subroutines in the module "ScalarOperations" working with the array "scalar". One option is thus pass the array to all subroutines working with it, another option is then pointer variables. I prefer the first option.

Thank you for your valuable answer and comments!

0 Kudos
FortranFan
Honored Contributor II
443 Views

jirina wrote:

The main reason I wanted "scalar" to be a module variable is that there will be more subroutines in the module "ScalarOperations" working with the array "scalar". One option is thus pass the array to all subroutines working with it, another option is then pointer variables. I prefer the first option ..

Your original post and subsequent comment suggests you're interested in knowing the details with the semantics of MODULEs and module entities in Fortran (but if you think that's not the case, then you may want to reconsider what you know given instructions such as 'scalar = T' followed 'call AssignandIniitalizeScalar' in your code snippet which are questionable relative to any presumed intent).  Toward this, the book Modern Fortran Explained is a better starting point to get a clean overview and your time will be better spent going through that book rather than reacting to tidbits on any peer forum such as this one: https://play.google.com/store/books/details/Modern_Fortran_Explained_Incorporating_Fortran_201?id=sB1rDwAAQBAJ&hl=en_US

 

0 Kudos
jimdempseyatthecove
Honored Contributor III
443 Views

Assuming from your description that given an arbitrary array (known external to the ScalarOperations) that you desire to have a series of procedures within ScalarOperations that operate on the same array: ProcedureFoo, ProcedureFi, ProcedureFo, ProcedureFum. Then consider using a contained procedure:

module Temperature
    real*4, allocatable :: T(:,:,:)
end module Temperature
    
module Pressure
    real*4, allocatable :: P(:,:,:)
end module Pressure
    
module ScalarOperations
! variables
    contains
    ! module procedures
    subroutine doScalarOperations(scalar)
        real*4 :: scalar(:,:,:)
        call ProcedureFee()
        call ProcedureFi()
        call ProcedureFo()
        call ProcedureFum
    contains
    ! subroutine contained procedures
        subroutine ProcedureFee
            scalar = scalar + 1.0
        end subroutine ProcedureFee
    
        subroutine ProcedureFi
            scalar = scalar * 2.0
        end subroutine ProcedureFi
    
        subroutine ProcedureFo
            scalar = scalar / 3.0
        end subroutine ProcedureFo
    
        subroutine ProcedureFum
            scalar = sqrt(scalar)
        end subroutine ProcedureFum
    
    end subroutine doScalarOperations
end module ScalarOperations
    
program ProgScalarOperations
    use Temperature
    use Pressure
    use ScalarOperations
    implicit none

    allocate(T(10,20,30))
    allocate(P(10,20,30))

    call doScalarOperations(T)
    call doScalarOperations(P)
end program ProgScalarOperations

Jim Dempsey

0 Kudos
jimdempseyatthecove
Honored Contributor III
443 Views

It should be noted that while it looks like you are saving the overhead of copying the (reference to the) array descriptor in the source code, the contained procedure call is doing this for you behind the scenes (for the used dummies from the outer scope).

This is a style matter.

Jim Dempsey

0 Kudos
jirina
New Contributor I
443 Views

FortranFan wrote:

Your original post and subsequent comment suggests you're interested in knowing the details with the semantics of MODULEs and module entities in Fortran (but if you think that's not the case, then you may want to reconsider what you know given instructions such as 'scalar = T' followed 'call AssignandIniitalizeScalar' in your code snippet which are questionable relative to any presumed intent).  Toward this, the book Modern Fortran Explained is a better starting point to get a clean overview and your time will be better spent going through that book rather than reacting to tidbits on any peer forum such as this one: https://play.google.com/store/books/details/Modern_Fortran_Explained_Inc...

Thank you for recommending reading the book. I have it, I will read it and I will hopefully learn how to do what I need.

0 Kudos
FortranFan
Honored Contributor II
443 Views

jirina wrote:

Quote:

FortranFan wrote:

 

.. the book Modern Fortran Explained is a better starting point to get a clean overview and your time will be better spent going through that book rather than reacting to tidbits on any peer forum such as this one: https://play.google.com/store/books/details/Modern_Fortran_Explained_Inc...

 

 

Thank you for recommending reading the book. I have it, I will read it and I will hopefully learn how to do what I need.

That's really great.  Once you've gone over it, you may want to review closely the sections on ELEMENTAL procedures, SELECT RANK facility, etc.  Or better yet, you may want to look at your coding needs and consider whether you want to start with type safety (always IMPLICIT NONE), defined KINDs (see this, no *4 usage: https://software.intel.com/en-us/blogs/2017/03/27/doctor-fortran-in-it-takes-all-kinds), explicitly declared INTENTs in subprograms, and move on object-oriented code design even - a simple illustration of the code in your original post will be whether you meant like so, something you can try out with your Intel Fortran compiler:

module kinds_m
   implicit none
   integer, parameter :: R4 = selected_real_kind( p=6 )
   integer, parameter :: R8 = selected_real_kind( p=12 )
end module

module scalar_m
   use kinds_m, only : R4
   implicit none
   type :: scalar_t
      real(kind=R4), allocatable :: vals(:,:,:)
   contains
      procedure, pass(this) :: Init => InitializeScalar
      ! Other methods to operate on scalars
   end type scalar_t
contains
   subroutine InitializeScalar( this, val )
      ! Argument list
      class(scalar_t), intent(inout) :: this
      real(R4), intent(in), optional :: val
      if ( present(val) ) then
         this%vals = val
      else
         this%vals = 0.0_r4
      end if
      return
   end subroutine InitializeScalar
end module scalar_m

module Temperature_m
   use kinds_m, only : R4
   use scalar_m, only : scalar_t
   implicit none
   type(scalar_t) :: T
contains
   subroutine AllocateAndInitializeTemperature ( )
      allocate ( T%vals(10,20,30) )
      call T%Init( )
   end subroutine AllocateAndInitializeTemperature
end module Temperature_m

module Pressure_m
   use kinds_m, only : R4
   use scalar_m, only : scalar_t
   implicit none
   type(scalar_t) :: P
contains
   subroutine AllocateAndInitializePressure( )
      allocate ( P%vals(10,20,30) )
      call P%Init( val=1.0_r4 )
   end subroutine AllocateAndInitializePressure
end module Pressure_m

program test
   use Temperature_m, only : T, AllocateAndInitializeTemperature
   use Pressure_m, only : P, AllocateAndInitializePressure
   implicit none
   call AllocateAndInitializeTemperature()
   print *, T%vals(1,1,1)
   call AllocateAndInitializePressure()
   print *, P%vals(1,2,3)
   stop
end program

 

0 Kudos
Reply