-1

I have defined a new type called KhonShamOrbitals as it appears below

type KhonShamOrbitals

    integer :: NumUpOrbitals
    integer :: NumDownOrbitals
    real(dp), allocatable,dimension(:,:) :: PhiUp, PhiDown
    real(dp),allocatable,dimension(:) :: EigenEnergiesUp,EigenEnergiesDown

    real(dp),allocatable, dimension(:) :: DensityUp,DensityDown
end type KhonShamOrbitals

Then I initalize it somewhere like this

type(KhonShamOrbitals) :: orbitals
orbitals%NumUpOrbitals = 1
    orbitals%NumDownOrbitals = 1

    allocate(orbitals%PhiUp(orbitals%NumUpOrbitals,100))
    allocate(orbitals%PhiDown(orbitals%NumDownOrbitals,100))
    allocate(orbitals%EigenEnergiesUp(orbitals%NumUpOrbitals))
    allocate(orbitals%EigenEnergiesDown(orbitals%NumDownOrbitals))
    allocate(orbitals%DensityUp(100))
    allocate(orbitals%DensityDown(100))

Just after that I call a subroutine

call ComputeDensity(1, 100, orbitals%PhiUp, orbitals%DensityUp)

And then the definition of the subroutine

subroutine ComputeDensity(NumOrbitals, NumPoints, orbitals, Density)
    integer,intent(in) :: NumOrbitals,NumPoints
    real(dp), intent(in) :: orbitals(NumOrbitals,NumPoints)
    real(dp) :: Density(NumPoints)
    real(dp) :: aux(NumPoints)
    integer i
    Density = 0
    do i  = 1, NumOrbitals
        aux  = orbitals(i,:)
        Density = Density + aux**2
    enddo
end subroutine ComputeDensity

The problem is that I am getting this error

Fortran runtime error: Allocatable actual argument 'orbitals' is not allocated when running the program.

It is compiled with gfortran 6.0.0 on MacOS X 10.10. Any ideas of why this is happening?

IanH
  • 21,026
  • 2
  • 37
  • 59
Miguel Carvajal
  • 1,785
  • 19
  • 23
  • From the code you'd assume that it were allocated. But maybe use the `stat` and maybe `errmsg` clauses of the `allocate` statements to check that all went well? – chw21 Nov 16 '16 at 03:28
  • Please include a complete example (see [mcve]): without knowing exactly what happens to the thing called "`orbitals%PhiUp`" (is it deallocated at some point, does it refer to a variable you don't think it does?) we can't provide a good answer. Something unexpected is happening, but without a full lump of code I'd just be guessing as to what. – francescalus Nov 16 '16 at 08:44
  • @francescalus I have included all the relevant pieaces of codes from the type definition, instantiation and function call. I dont know what else would you like me to send. The only thing that happend to the thing phiUp (`real(dp), allocatable,dimension(:,:) :: PhiUp`) is all shown in the question. – Miguel Carvajal Nov 16 '16 at 22:57
  • If your program has a bug somewhere else, it may corrupt the internal data structures that the compiler uses at runtime for the problem variable. We don't know if your program has a bug somewhere else, because we don't have the source to your program. Perhaps your program is correct, and the compiler has a bug, but we cannot test the compiler against your program, because we don't have the source to your program. So if you want effective help, we need the minimal but complete source. – IanH Nov 17 '16 at 00:55
  • @IanH the complete source is a full DFT code for atoms. I don't think it fits into a question – Miguel Carvajal Nov 17 '16 at 04:21
  • 1
    Hence "minimal" source - you need to start cutting the source back, to get the shortest program that is still compilable, runnable and that continues to demonstrate the problem. This is a basic step in isolating the cause of this sort of problem. Often while preparing a minimal example, you end up discovering what caused the problem along the way. – IanH Nov 17 '16 at 06:35

2 Answers2

1

The following builds just fine with GCC 6.2.

I made a few changes to your code.

First, your derived data type now has type-bound procedures to allocate and (implicitly) deallocate memory.

Second, explicit-shaped arrays were replaced with assumed-shape arrays to improve robustness. See: Fortran subroutine returning wrong values

Lastly, you can overload the name of your derived data type by way of an interface to get user-defined constructors.

The following code

module mymod

  use, intrinsic :: ISO_C_binding, only: &
       ip => C_INT, &
       dp => C_DOUBLE

  ! Explicit typing only
  implicit none

  ! Everything is private unless stated otherwise
  private
  public :: ip, dp, KhonShamOrbitals, ComputeDensity

  ! Declare derived data type
  type, public :: KhonShamOrbitals
    ! Type components
    integer(ip)           :: NumUpOrbitals
    integer(ip)           :: NumDownOrbitals
    real(dp), allocatable :: PhiUp(:,:), PhiDown(:,:)
    real(dp), allocatable :: EigenEnergiesUp(:)
    real(dp), allocatable :: EigenEnergiesDown(:)
    real(dp), allocatable :: DensityUp(:),DensityDown(:)
  contains
    ! Type-bound procedures
    procedure :: create
    procedure :: destroy
  end type  KhonShamOrbitals

  ! Set user-defined constructor
  interface  KhonShamOrbitals
     module procedure constructor
  end interface KhonShamOrbitals

contains

  subroutine destroy(self)
    ! Dummy arguments
    class(KhonShamOrbitals), intent(out) :: self

  end subroutine destroy

  subroutine create(self, n, m)
    ! Dummy arguments
    class(KhonShamOrbitals), intent(inout) :: self
    integer(ip),             intent(in)    :: n
    integer(ip),             intent(in)    :: m

    ! Ensure object is usable
    call self%destroy()

    ! Set constants
    self%NumUpOrbitals = n
    self%NumDownOrbitals = m

    ! Allocate memory
    allocate( self%PhiUp(self%NumUpOrbitals, m) )
    allocate( self%PhiDown(self%NumDownOrbitals, m) )
    allocate( self%EigenEnergiesUp(self%NumUpOrbitals) )
    allocate( self%EigenEnergiesDown(self%NumDownOrbitals) )
    allocate( self%DensityUp(m) )
    allocate( self%DensityDown(m) )

  end subroutine create

  function constructor(n, m) result(return_value)
    integer(ip), intent(in) :: n, m
    type(KhonShamOrbitals)  :: return_value

    call return_value%create(n,m)

  end function constructor

  subroutine ComputeDensity(orbitals, Density)
    ! Dummy arguments
    real(dp), intent(in) :: orbitals(:,:)
    real(dp), intent(out):: Density(:)
    ! Local variables
    integer :: i, NumOrbitals, NumPoints

    NumOrbitals = size(orbitals, dim=1)
    NumPoints = size(orbitals, dim=2)
    Density = 0

    block
      real(dp) :: aux(NumPoints)

      do i  = 1, NumOrbitals
         aux  = orbitals(i,:)
         Density = Density + aux**2
      end do

   end block

  end subroutine ComputeDensity

end module mymod

program main

  use, intrinsic :: ISO_Fortran_env, only: &
       stdout => OUTPUT_UNIT, &
       compiler_version, &
       compiler_options

  use mymod

  implicit none

  type(KhonShamOrbitals) :: foo

  ! Initialize with user-defined constructor
  foo = KhonShamOrbitals(1,100)

  associate( &
       a => foo%PhiUp, &
       b => foo%DensityUp )  
    call ComputeDensity(a, b)
  end associate

  write (stdout, '(/4a/)') &
       'This file was compiled using compiler version ', compiler_version(), &
       ' and compiler options ', compiler_options()

end program main

yields

gfortran -Wall -o main.exe mymod.f90 main.f90
./main.exe

This file was compiled using compiler version GCC version 6.2.0 20161027 and compiler options -mtune=generic -march=x86-64 -Wall
Community
  • 1
  • 1
jlokimlin
  • 593
  • 4
  • 9
0

Is the data allocated in a routine? Does in have intent(out) or intent(inout)?

You pass arrays with a given shape. Assumed shape could work and would save you the explicit passing of dimension.

real(dp), intent(in) :: orbitals(:,:)
NumOrbitals = size(orbitals, dim=1)
NumPoints = size(orbitals, dim=2)

chw21's suggestion to check the allocation status is the first thing to check anyway.

For more help, post the full output of the compilation with the -g -Wall -fcheck=all flags.

Pierre de Buyl
  • 7,074
  • 2
  • 16
  • 22
  • 1
    This appears more to be a comment than an answer. – francescalus Nov 16 '16 at 08:41
  • 1
    If an ALLOCATE statement fails in a manner that would result in a non-zero IOSTAT, but the statement does not have an IOSTAT= specifier, then the Fortran processor is required to terminate the program there and then. So, if the program hasn't been terminated in that fashion, then we already know that IOSTAT, if present, would have been reported as zero. – IanH Nov 16 '16 at 09:51
  • the orbitals you are talking about is the dummy argument of the subroutine `ComputeDensity` and the error is about the actual argument. – Miguel Carvajal Nov 16 '16 at 23:11
  • Have you tested the compilation with the flags I mention? – Pierre de Buyl Nov 17 '16 at 00:17
  • ALLOCATED and SHAPE could be useful on some debug lines. – Holmz Nov 22 '16 at 09:33