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

Allocatable character problem

Göttinger__Michael
3,030 Views

Hi,

We have found a serious problem with allocateable character in Intel® Parallel Studio XE 2018 Update 3 Composer Edition for Fortran Windows.

 

It seems that a move from types in an array causes gigantic memory leaks. It does not work either if a custom finalize stuff is added to the type and frees all memory from allocated characters.

 

When you run the small code, you will see that in the second loop where the data is moved the memory problem occurs. You will see that the small stuff needs about 500MB on the heap!!

 

          TEST1: block 
            type :: TestData
              character(len=20)               :: UID = ' '      ! Name of global variable
              character(:) , allocatable      :: strVal         ! Value of variable dynamic string
             !character(len=80)               :: strVal         ! Value of variable constant string
              integer(2)                      :: Container = 0
            end type TestData

            type(TestData), pointer :: pData(:)
            type(TestData)          :: item
            integer                 :: i, n, nItems, nAdd
            character(len=20)       :: strNum

            nItems = 10000
            nAdd = 2000

            allocate( pData(nItems+nAdd) )

            do n=1,nItems
              write(strNum,FMT='(I8)') n
              item % UID = '#V'//adjustl(strNum)
              item % strVal = 'xyz'
              pData(n) = item
            end do

            continue

            do n=1,nAdd-1
              write(strNum,FMT='(I8)') n
              item % UID = '#A'//adjustl(strNum)
              item % strVal = 'Hallo'
              pData(n+1:nItems+n+1) = pData(n:nItems+n)
            end do

          end block TEST1

Just for information, the same code compiled with Intel® Parallel Studio XE 2016 works fine.

 

BTW: problem is was already submitted to intel support too, but maybe someone here has the same problem and a possible solution for it…

0 Kudos
1 Solution
FortranFan
Honored Contributor II
2,997 Views

@Gottlinger, Michael:

I concur with yours and others' assessments in this thread (e.g., with Quote #14) there has been a regression with Intel Fortran compiler 18.0 version compared to, say, version corresponding to Intel Parallel Studio 2016.  Hopefully you will feedback comments from this thread at your support incident at the Intel OSC and Intel support team will then work with Intel developers to address your problem,

In the meantime, I will suggest a workaround for you which is to go with defined assignment for your data structure(s) (derived type); as one's 'classes' get bigger and more and more complicated in terms of the data they encapsulate, such defined assignment may be an option to consider in your actual code(s), especially as they can provide control in terms of shallow copy vs deep copy, etc.

! -----------------------------------------------------------------------------
!
!  PROGRAM: TestFTN
!
!  PURPOSE:  Show a serious heap error problem in Intel Fortran Composer 2018.
!            Note, this stuff works fine in older versions.
!
!  AUTHOR:   Michael Göttlinger
!

! -----------------------------------------------------------------------------
module WinStuff
   use ISO_C_BINDING
   implicit none

contains

   !DEC$ IF DEFINED(_WIN32)
   ! Get heap memory of process
   function ChkMemory()
      use IFWINTY
      use KERNEL32
      use PSAPI
      implicit none

      integer         :: ChkMemory
      integer(DWORD)  :: processID
      integer(HANDLE) :: hProc
      integer(DWORD)  :: dwRet
      type(T_PROCESS_MEMORY_COUNTERS) :: pmc

      ChkMemory = 0

      processID = GetCurrentProcessId()
      hProc = OpenProcess (ior(PROCESS_QUERY_INFORMATION, PROCESS_VM_READ), FALSE, processID)
      if( hProc /= null ) then
         dwRet = GetProcessMemoryInfo( hProc, pmc, sizeof(pmc) )
         if( dwRet /= 0 ) then
            !write (*, '(2X,A,1X,I0)') &
               !  "PageFaultCount:", pmc%PageFaultCount, &
               !  "PeakWorkingSetSize:", pmc%PeakWorkingSetSize, &
               !  "WorkingSetSize:", pmc%WorkingSetSize, &
               !  "QuotaPeakPagedPoolUsage:", pmc%QuotaPeakPagedPoolUsage, &
               !  "QuotaPeakNonPagedPoolUsage:", pmc%QuotaPeakNonPagedPoolUsage, &
               !  "QuotaNonPagedPoolUsage:", pmc%QuotaNonPagedPoolUsage, &
               !  "PagefileUsage:", pmc%PagefileUsage, &
               !  "PeakPagefileUsage:", pmc%PeakPagefileUsage
            ChkMemory = pmc%WorkingSetSize / 1024
         end if
         dwRet = CloseHandle( hProc )
      end if
   end function ChkMemory
   !DEC$ ELSE
   ! Get heap memory of process
   function ChkMemory()
      implicit none
      integer :: ChkMemory
      ChkMemory = 0
   end function ChkMemory
   !DEC$ ENDIF
end module WinStuff

module m

   ! Small type with automatically allocatable character
   type :: TestData
      character(len=20)               :: UID = ' '      ! Name of global variable
      character(:) , allocatable      :: strVal         ! Value of variable dynamic string
      !character(len=80)               :: strVal         ! Value of variable constant string
      integer(2)                      :: Container = 0
   contains
      private
      procedure, pass(this) :: assign_t
      generic, public :: assignment(=) => assign_t
   end type TestData

contains

   elemental subroutine assign_t( this, rhs )

      ! Argument list
      class(TestData), intent(inout) :: this
      type(TestData), intent(in)     :: rhs

      this%UID = rhs%UID
      if ( allocated(rhs%strVal) ) this%strVal = rhs%strVal
      this%Container = rhs%Container

   end subroutine assign_t

end module

! -----------------------------------------------------------------------------
program TestFTN

   use, intrinsic :: iso_fortran_env, only : compiler_version
   use m, only : TestData
   use WinStuff, only : ChkMemory
   
   implicit none

   ! Variables
   !type(TestData), allocatable :: pData(:)
   type(TestData), pointer     :: pData(:) => null()
   type(TestData)              :: item
   integer                     :: i, n, nItems, nAdd
   character(len=20)           :: strNum

   print *, "Compiler Version: ", compiler_version()
   
   nItems = 10000
   nAdd = 2000

   99 format(A,', heap ',I0,' KB')

   ! Before alloc
   write(*, 99) 'Before alloc', ChkMemory()

   allocate( pData(nItems+nAdd) )

   ! After alloc
   write(*, 99) 'After alloc', ChkMemory()

   ! Assign data to the vector
   do n=1,nItems
      write(strNum,fmt='(I0)') n
      item % UID = '#V'//trim(strNum)
      item % strVal = 'xyz'//trim(strNum)
      pData(n) = item
   end do

   ! After assignment
   write(*, 99) 'Data assignment done', ChkMemory()

   ! Move of data in the vector, should simulate data shift in when sorted
   do n=1,nAdd-1
      write(strNum,fmt='(I0)') n
      item % UID = '#A'//trim(strNum)
      item % strVal = 'abc'//trim(strNum)
      ! Here the heap memory leak occurs, nothing helps to fix it: loop, dealloc, ...
      pData(n+1:nItems+n+1) = pData(n:nItems+n)
      !do i=n+nItems, n, -1
      !  if( allocated(pData(i+1) % strVal) ) deallocate( pData(i+1) % strVal )
      !  pData(i+1) = pData(i)
      !end do
      !if( allocated(pData(n) % strVal) ) deallocate( pData(n) % strVal )
      pData(n) = item
   end do

   ! After move
   write(*, 99) 'Data move done', ChkMemory()

   deallocate( pData )

   write(*, 99) 'Deallocate done', ChkMemory()

end program TestFTN

Upon execution,

 Compiler Version:
 Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on IA-32,

  Version 18.0.3.210 Build 20180410
Before alloc, heap 3156 KB
After alloc, heap 3732 KB
Data assignment done, heap 4164 KB
Data move done, heap 4264 KB
Deallocate done, heap 3440 KB

 

Separately, take a look at this thread and note Fortran language standard has limitations when it comes to move semantics and therefore, if you need to 'move' large amounts of data within or across arrays such as with your statements

    pData(n+1:nItems+n+1) = pData(n:nItems+n) 

you need to consider the consequences in terms of memory requirements and ponder over  (code design) options to overcome issues:

https://software.intel.com/en-us/forums/intel-visual-fortran-compiler-for-windows/topic/701985

View solution in original post

0 Kudos
25 Replies
Göttinger__Michael
2,663 Views

For better diagnostics, I've added a small FTN project which shows the problem too. When you run the console application, you will see that there is a huge heap allocation problem. I've added some print lines which show how much memory is allocated for the small program on my PC. When you run it you will see the following output:

 

 Before alloc, heap 3640 KB

 After alloc, heap 4332 KB

 Data assignment done, heap 4692 KB

 Data move done, heap 477364 KB!!!

 Deallocate done, heap 476800 KB!!!

0 Kudos
Göttinger__Michael
2,663 Views

In additon I've added 2 screenshots from debugging session and process memory info. Looks not fine at all...

0 Kudos
jimdempseyatthecove
Honored Contributor III
2,663 Views

Maybe IanH or Steve can answer this better.

  type(TestData), pointer :: pData(:)

Is an unallocated array of pointers to TestData objects

  allocate( pData(nItems+nAdd) )

Allocates, but does not initialize, the array of pointers to TestData objects

  pData(n) = item

Copies an item of TestData to (into) a TestData object pointed to by an uninitialized pointer. Note, the prior statement is not the same as (auto) reallocate left hand side for unallocated allocatable object.

Perhaps one means of fixing the code would be to use:

   type(TestData), allocatable :: pData(:)

The earlier compilers used to have a problem with the above syntax, I haven't tried using an allocatable array of allocatable objects lately.

Jim Dempsey

0 Kudos
Göttinger__Michael
2,663 Views

Thanks for your feedback Jim, but this is not the problem. When you change pDatato allocatable the behavior does not change at all.

I'm quite sure there is a problem is the management of data assignment with allocatable stuff in the compiler, because the problem comes from this line:

  ! Move of data in the vector, should simulate data shift in when sorted
  do n=1,nAdd-1
    write(strNum,FMT='(I8)') n
    item % UID = '#A'//adjustl(strNum)
    item % strVal = 'Hallo'
    pData(n+1:nItems+n+1) = pData(n:nItems+n) ! Here the heap memory leak occurs!!
  end do

As I mentioned, I've also tried to add a final code to the type and manually free the memory there. Does not work either. 

0 Kudos
jimdempseyatthecove
Honored Contributor III
2,663 Views

The behavior = on pointer(s) is different than = on (non-pointer) array element(s).

Arrays, with reallocate lhs in effect, may use, allocate, or reallocate the entity on the lhs.

whereas

pointers, require the lhs to point to a valid object (else undefined behavior occurs), the lhs is treated as a reference into which the rhs is copied into. IOW the = on pointer(s) does not copy the pointer, rather it copies the contents of the object referenced.

The => operator constructs a pointer to the rhs (if rhs is a pointer it needs to be defined for defined behavior).

The syntax of your last statement will attempt to

copy into the objects as referenced by pointers contained within pData(n+1:nItems+n+1),
the contents of the objects referenced by pointers contained within pData(n:nItems+n)

IOW, if the pointers referenced on both sides, are not initialized or not associated, then undefined behavior occurs.

If you desire to copy the pointers, then you will have to do it with an explicit loop using => and being careful about aliases and/or nullifications.

! Move of data in the vector, should simulate data shift in when sorted
  do n=1,nAdd-1
    write(strNum,FMT='(I8)') n
    item % UID = '#A'//adjustl(strNum)
    item % strVal = 'Hallo'
    do j=nItems+n-1,1,-1
      pData(j+1) => pData(j) ! requires pData(j) to exist
      nullify(pData(1))
      allocate(pData(1))
      pData(1) = item
    end do
  end do

The above is descriptive but non-optimal.

Jim Dempsey

0 Kudos
Göttinger__Michael
2,663 Views

Jim, sorry I cannot follow your approach here at all.

There is single allocated pData array. It is based on a type. The type initialization is controlled by the compiler. Therefore, it should not be a problem. The data in the type is also correctly initialized as you can see in the debugger. In the type there as a dynamic allocateable character strVal. This one must be controlled by the compiler (init, allocate, deallocate):  

  type :: TestData
    character(len=20)               :: UID = ' '      ! Name of global variable
    character(:) , allocatable      :: strVal         ! Value of variable dynamic string
    integer(2)                      :: Container = 0
  end type TestData

Exactly this stuff seems to fail here. It works well when only following change is applied to the type: 

  type :: TestData
    character(len=20)               :: UID = ' '      ! Name of global variable
    character(len=80)               :: strVal         ! Value of variable constant string
    integer(2)                      :: Container = 0
  end type TestData

How should it be possible to nullify an item which is not directly allocated. You can call nullify(pData) but not nullify( pdata(i) )

I've also tried the following stuff and as I already mentioned, it does not work either:

  ! Move of data in the vector, should simulate data shift in when sorted
  do n=1,nAdd-1
    write(strNum,FMT='(I8)') n
    item % UID = '#A'//adjustl(strNum)
    item % strVal = 'Hallo'
    !pData(n+1:nItems+n+1) = pData(n:nItems+n) ! Here the heap memory leak occurs!!
    do i=n+nItems, n, -1
      if( allocated(pData(i+1) % strVal) ) deallocate( pData(i+1) % strVal )
      pData(i+1) = pData(i)
    end do
    pData(n) = item
  end do

Yesterday I've got the feedback from Intel Customer Support that they can reproduce the problem too. They also cannot offer a solution yet. Very bad at all...

0 Kudos
jimdempseyatthecove
Honored Contributor III
2,663 Views

I wish to apologize about array of pointers, I was wrong about this. pData is a single pointer to an array of objects as you said.

Minor edits appears to work with V17.0.5.267

program AllocatableCharacterProblem
    implicit none
    type :: TestData
        character(len=20)               :: UID = ' '      ! Name of global variable
        character(:) , allocatable      :: strVal         ! Value of variable dynamic string
        !character(len=80)               :: strVal         ! Value of variable constant string
        integer(2)                      :: Container = 0
    end type TestData

    type(TestData), pointer :: pData(:)
    type(TestData)          :: item
    integer                 :: i, n, nItems, nAdd
    character(len=20)       :: strNum

    nItems = 100    ! reduce counts for quick test verification to console
    nAdd = 20

    allocate( pData(nItems+nAdd) )
  
    do n=1,nItems
        write(strNum,FMT='(I8)') n
        item % UID = '#V'//adjustl(strNum)
        item % strVal = 'xyz'//adjustl(strNum) ! add sequence number to disambiguate results
        pData(n) = item
    end do

    continue

    do n=1,nAdd ! original code had nAdd-1, which did not add the nAdd values
        write(strNum,FMT='(I8)') n
        item % UID = '#A'//adjustl(strNum)
        item % strVal = 'Hallo'//adjustl(strNum)
        pData(n+1:nItems+n+1) = pData(n:nItems+n)
        pData(n) = item ! add code to copy in new item
    end do

    do n=1,nItems+nAdd
        print *, pData(n)%UID, pData(n)%strVal
    end do
end program AllocatableCharacterProblem

and

Compiling with Intel(R) Visual Fortran Compiler 17.0.5.267 [Intel(R) 64]...
...
 #A1                 Hallo1
 #A2                 Hallo2
 #A3                 Hallo3
 #A4                 Hallo4
 #A5                 Hallo5
 #A6                 Hallo6
 #A7                 Hallo7
 #A8                 Hallo8
 #A9                 Hallo9
 #A10                Hallo10
 #A11                Hallo11
 #A12                Hallo12
 #A13                Hallo13
 #A14                Hallo14
 #A15                Hallo15
 #A16                Hallo16
 #A17                Hallo17
 #A18                Hallo18
 #A19                Hallo19
 #A20                Hallo20
 #V1                 xyz1
 #V2                 xyz2
 #V3                 xyz3
 #V4                 xyz4
 #V5                 xyz5
 #V6                 xyz6
 #V7                 xyz7
 #V8                 xyz8
 #V9                 xyz9
 #V10                xyz10
 #V11                xyz11
 #V12                xyz12
 #V13                xyz13
 #V14                xyz14
 #V15                xyz15
 #V16                xyz16
 #V17                xyz17
 #V18                xyz18
 #V19                xyz19
 #V20                xyz20
 #V21                xyz21
 #V22                xyz22
 #V23                xyz23
 #V24                xyz24
 #V25                xyz25
 #V26                xyz26
 #V27                xyz27
 #V28                xyz28
 #V29                xyz29
 #V30                xyz30
 #V31                xyz31
 #V32                xyz32
 #V33                xyz33
 #V34                xyz34
 #V35                xyz35
 #V36                xyz36
 #V37                xyz37
 #V38                xyz38
 #V39                xyz39
 #V40                xyz40
 #V41                xyz41
 #V42                xyz42
 #V43                xyz43
 #V44                xyz44
 #V45                xyz45
 #V46                xyz46
 #V47                xyz47
 #V48                xyz48
 #V49                xyz49
 #V50                xyz50
 #V51                xyz51
 #V52                xyz52
 #V53                xyz53
 #V54                xyz54
 #V55                xyz55
 #V56                xyz56
 #V57                xyz57
 #V58                xyz58
 #V59                xyz59
 #V60                xyz60
 #V61                xyz61
 #V62                xyz62
 #V63                xyz63
 #V64                xyz64
 #V65                xyz65
 #V66                xyz66
 #V67                xyz67
 #V68                xyz68
 #V69                xyz69
 #V70                xyz70
 #V71                xyz71
 #V72                xyz72
 #V73                xyz73
 #V74                xyz74
 #V75                xyz75
 #V76                xyz76
 #V77                xyz77
 #V78                xyz78
 #V79                xyz79
 #V80                xyz80
 #V81                xyz81
 #V82                xyz82
 #V83                xyz83
 #V84                xyz84
 #V85                xyz85
 #V86                xyz86
 #V87                xyz87
 #V88                xyz88
 #V89                xyz89
 #V90                xyz90
 #V91                xyz91
 #V92                xyz92
 #V93                xyz93
 #V94                xyz94
 #V95                xyz95
 #V96                xyz96
 #V97                xyz97
 #V98                xyz98
 #V99                xyz99
 #V100               xyz100
Press any key to continue . . .

Jim Dempsey

0 Kudos
Göttinger__Michael
2,663 Views

Jim, just for clarification, it was never a question of not working stuff. The code was intended as a sample to outline the memory leak in Fortran Composer 2018.

I've reported that it works perfect in old version 2016, but in Intel® Parallel Studio XE 2018 Update 3 Composer Edition for Fortran Windows it created a huge memory leak. Keep this stuff in mind:

 Before alloc, heap 3640 KB
 After alloc, heap 4332 KB
 Data assignment done, heap 4692 KB
 Data move done, heap 477364 KB!!!
 Deallocate done, heap 476800 KB!!!

Yesterday I've got a strange feedback from Intel Support which I want to share here in the forum for all users too.

(1)  Regarding deallocation, according to the compiler developers, the physical deallocation of memory does not actually occur until the end of the program.

That answer is truly incredible. It's is a memory leak which occurs as soon as you assign data to an allocateabe character. No one who understands how memory management works (and certainly not a compiler developer) can claim that this is correct behavior!

No idea how to proceed here further...

0 Kudos
Lorri_M_Intel
Employee
2,663 Views

One comment, one suggestion.

My comment is that the "allocate" at line 17 in your original program does not get deallocated until the end of the program.  It's possible that that is what my colleague was reacting to.

My suggestion is to reply to your support contact, acknowledge that you understand that this allocation is not released, but that your concern goes beyond that one allocation, and could they kindly look at it again.

                             --Lorri

 

 

0 Kudos
Göttinger__Michael
2,663 Views

Thanks Lorri,

This is not the problem. Even when deallocate is done, it needs 500MB of data. And deallocate is not applicable here at all. The scenarios is to work with a dynamic filled sorted data vector. There the data is moved to keep it on order. Then it is of course not possible to deallocate it, because you want to work with it.

I think you can look at it as you like, the summary is in my opinion the following: implementation of allocatable character in Intel Fortran 2018 is complete garbage.

BTW: in the full FTN project (see ZIP), which I've added, the deallocate stuff present too.

0 Kudos
jimdempseyatthecove
Honored Contributor III
2,663 Views

>>That answer is truly incredible. It's is a memory leak which occurs as soon as you assign data to an allocateabe character. No one who understands how memory management works (and certainly not a compiler developer) can claim that this is correct behavior!

That may not entirely be a true on your part. Let me explain (assumption on my part). When the OpenMP tasking statements were implemented in IVF, the IVF development team wanted fast task dispatching, which in turn require fast memory allocation/deallocation. To implement this, the development team borrowed the TBB parallel allocator. This allocator, provides for each thread to allocate from the common heap, a slab of memory, and if necessary additional slabs of memory. The allocation/deallocaton scheme aggregates similar sized chunks of the slab into separate pools. Thus permitting thread independent (for the most part) memory pools. The slabs are not returned until the process ends (or there may be an API to disband a pool).

This activity blurs "how memory management works".

Detecting a memory leak is a bit more complicated than testing the condition of the main heap.

Note, the above does not preclude a memory leak.

Jim Dempsey

0 Kudos
Göttinger__Michael
2,663 Views

Maybe it's not a memory leak but if you can not control that stuff the allocateabe characters become useless. Keep in mind the sample which I've shown. We have a vector with only 10000 items. There are data strings with only some few bytes in it. When you move it (only 2000 times for additional inserts), the program size changes from 4MB to 470MB:

 Before alloc, heap 3640 KB
 After alloc, heap 4332 KB
 Data assignment done, heap 4692 KB
 Data move done, heap 477364 KB!!!

Now keep in mind that we have multiple of these data vectors. Then we need an incredible amount of memory because of optimization from intel compiler developers?! And the best thing here is that it worked fine in version 2016.

I'm happy if you can tell me that I'm doing some stuff wrong and that it must be implemented/used in a different way. But even the Intel Support was not able to provide here a useful approach to handle it.

 

 

0 Kudos
CTOptimizer
Beginner
2,663 Views

This certainly seems like a bug to me.  I am able to reproduce the heap growth with v18u3 (Windows) and it doesn't happen with v17u5.

Even if pData(:) is changed to an allocatable, the problem persists.

I suspect the intermediate temporary objects that are being used for the loop copying are not being released/deallocated correctly.  I guess there could be some other (new) magic related to the v18 memory manager that is causing the heap growth (that's not my area), but this one sounds like a duck.

Definitely follow Lorri's guidance and ask them to take a second look at what you are demonstrating in your (very nice) reproducer.

0 Kudos
Göttinger__Michael
2,663 Views

I've created an enhanced sample where the process heap memory is dumped automatically. This should simplify a little bit to check the memory demand. For this the Windows API function GetProcessMemoryInfo() is used to query the WorkingSetSize of the current process.

Current output on my computer with Windows 10 1803 and Intel® Parallel Studio XE 2018 Update 3 Composer Edition for Fortran Windows:

Before alloc, heap 3808 KB
After alloc, heap 4392 KB
Data assignment done, heap 4784 KB
Data move done, heap 632236 KB
Deallocate done, heap 631672 KB
0 Kudos
FortranFan
Honored Contributor II
2,998 Views

@Gottlinger, Michael:

I concur with yours and others' assessments in this thread (e.g., with Quote #14) there has been a regression with Intel Fortran compiler 18.0 version compared to, say, version corresponding to Intel Parallel Studio 2016.  Hopefully you will feedback comments from this thread at your support incident at the Intel OSC and Intel support team will then work with Intel developers to address your problem,

In the meantime, I will suggest a workaround for you which is to go with defined assignment for your data structure(s) (derived type); as one's 'classes' get bigger and more and more complicated in terms of the data they encapsulate, such defined assignment may be an option to consider in your actual code(s), especially as they can provide control in terms of shallow copy vs deep copy, etc.

! -----------------------------------------------------------------------------
!
!  PROGRAM: TestFTN
!
!  PURPOSE:  Show a serious heap error problem in Intel Fortran Composer 2018.
!            Note, this stuff works fine in older versions.
!
!  AUTHOR:   Michael Göttlinger
!

! -----------------------------------------------------------------------------
module WinStuff
   use ISO_C_BINDING
   implicit none

contains

   !DEC$ IF DEFINED(_WIN32)
   ! Get heap memory of process
   function ChkMemory()
      use IFWINTY
      use KERNEL32
      use PSAPI
      implicit none

      integer         :: ChkMemory
      integer(DWORD)  :: processID
      integer(HANDLE) :: hProc
      integer(DWORD)  :: dwRet
      type(T_PROCESS_MEMORY_COUNTERS) :: pmc

      ChkMemory = 0

      processID = GetCurrentProcessId()
      hProc = OpenProcess (ior(PROCESS_QUERY_INFORMATION, PROCESS_VM_READ), FALSE, processID)
      if( hProc /= null ) then
         dwRet = GetProcessMemoryInfo( hProc, pmc, sizeof(pmc) )
         if( dwRet /= 0 ) then
            !write (*, '(2X,A,1X,I0)') &
               !  "PageFaultCount:", pmc%PageFaultCount, &
               !  "PeakWorkingSetSize:", pmc%PeakWorkingSetSize, &
               !  "WorkingSetSize:", pmc%WorkingSetSize, &
               !  "QuotaPeakPagedPoolUsage:", pmc%QuotaPeakPagedPoolUsage, &
               !  "QuotaPeakNonPagedPoolUsage:", pmc%QuotaPeakNonPagedPoolUsage, &
               !  "QuotaNonPagedPoolUsage:", pmc%QuotaNonPagedPoolUsage, &
               !  "PagefileUsage:", pmc%PagefileUsage, &
               !  "PeakPagefileUsage:", pmc%PeakPagefileUsage
            ChkMemory = pmc%WorkingSetSize / 1024
         end if
         dwRet = CloseHandle( hProc )
      end if
   end function ChkMemory
   !DEC$ ELSE
   ! Get heap memory of process
   function ChkMemory()
      implicit none
      integer :: ChkMemory
      ChkMemory = 0
   end function ChkMemory
   !DEC$ ENDIF
end module WinStuff

module m

   ! Small type with automatically allocatable character
   type :: TestData
      character(len=20)               :: UID = ' '      ! Name of global variable
      character(:) , allocatable      :: strVal         ! Value of variable dynamic string
      !character(len=80)               :: strVal         ! Value of variable constant string
      integer(2)                      :: Container = 0
   contains
      private
      procedure, pass(this) :: assign_t
      generic, public :: assignment(=) => assign_t
   end type TestData

contains

   elemental subroutine assign_t( this, rhs )

      ! Argument list
      class(TestData), intent(inout) :: this
      type(TestData), intent(in)     :: rhs

      this%UID = rhs%UID
      if ( allocated(rhs%strVal) ) this%strVal = rhs%strVal
      this%Container = rhs%Container

   end subroutine assign_t

end module

! -----------------------------------------------------------------------------
program TestFTN

   use, intrinsic :: iso_fortran_env, only : compiler_version
   use m, only : TestData
   use WinStuff, only : ChkMemory
   
   implicit none

   ! Variables
   !type(TestData), allocatable :: pData(:)
   type(TestData), pointer     :: pData(:) => null()
   type(TestData)              :: item
   integer                     :: i, n, nItems, nAdd
   character(len=20)           :: strNum

   print *, "Compiler Version: ", compiler_version()
   
   nItems = 10000
   nAdd = 2000

   99 format(A,', heap ',I0,' KB')

   ! Before alloc
   write(*, 99) 'Before alloc', ChkMemory()

   allocate( pData(nItems+nAdd) )

   ! After alloc
   write(*, 99) 'After alloc', ChkMemory()

   ! Assign data to the vector
   do n=1,nItems
      write(strNum,fmt='(I0)') n
      item % UID = '#V'//trim(strNum)
      item % strVal = 'xyz'//trim(strNum)
      pData(n) = item
   end do

   ! After assignment
   write(*, 99) 'Data assignment done', ChkMemory()

   ! Move of data in the vector, should simulate data shift in when sorted
   do n=1,nAdd-1
      write(strNum,fmt='(I0)') n
      item % UID = '#A'//trim(strNum)
      item % strVal = 'abc'//trim(strNum)
      ! Here the heap memory leak occurs, nothing helps to fix it: loop, dealloc, ...
      pData(n+1:nItems+n+1) = pData(n:nItems+n)
      !do i=n+nItems, n, -1
      !  if( allocated(pData(i+1) % strVal) ) deallocate( pData(i+1) % strVal )
      !  pData(i+1) = pData(i)
      !end do
      !if( allocated(pData(n) % strVal) ) deallocate( pData(n) % strVal )
      pData(n) = item
   end do

   ! After move
   write(*, 99) 'Data move done', ChkMemory()

   deallocate( pData )

   write(*, 99) 'Deallocate done', ChkMemory()

end program TestFTN

Upon execution,

 Compiler Version:
 Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on IA-32,

  Version 18.0.3.210 Build 20180410
Before alloc, heap 3156 KB
After alloc, heap 3732 KB
Data assignment done, heap 4164 KB
Data move done, heap 4264 KB
Deallocate done, heap 3440 KB

 

Separately, take a look at this thread and note Fortran language standard has limitations when it comes to move semantics and therefore, if you need to 'move' large amounts of data within or across arrays such as with your statements

    pData(n+1:nItems+n+1) = pData(n:nItems+n) 

you need to consider the consequences in terms of memory requirements and ponder over  (code design) options to overcome issues:

https://software.intel.com/en-us/forums/intel-visual-fortran-compiler-for-windows/topic/701985

0 Kudos
Göttinger__Michael
2,663 Views

@FortranFan

Thank you for your feedback. This was exactly what I was looking for. The assignment implementation works fine, when move is done using a do loop (as you mentioned):

  ! Move of data in the vector, should simulate data shift in when sorted
  do n=1,nAdd-1
    write(strNum,FMT='(I0)') n
    item % UID = '#A'//trim(strNum)
    item % strVal = 'abc'//trim(strNum)
    do i=n+nItems, n, -1
      pData(i+1) = pData(i)
    end do
    pData(n) = item
  end do

I tried it before with a final implementation, but this one did not solve the problem. And also freeing data in the do loop did not work either. But your approach with assignment works well. Thanks again!

BTW: I've informed Intel Support about feedback in this forum and what I can see on their response they are watching this discussion too.

0 Kudos
jimdempseyatthecove
Honored Contributor III
2,663 Views

FF, can you explain why in assign_t when rhs%strVal is not allocated, that you assure this%strVal is not allocated?

   elemental subroutine assign_t( this, rhs )

      ! Argument list
      class(TestData), intent(inout) :: this
      type(TestData), intent(in)     :: rhs

      this%UID = rhs%UID
      if ( allocated(rhs%strVal) ) then
          this%strVal = rhs%strVal
      else
          if(allocated(this%strVal)) deallocate(this%strVal))
      endif
      this%Container = rhs%Container

   end subroutine assign_t

Jim Dempsey

0 Kudos
CTOptimizer
Beginner
2,663 Views

Jim raises an interesting question - I have a hunch as I think I ran into the same issue last year...

A "normal" assignment between two allocatables (of intrinsic type) appears to be invalid if the RHS is not allocated.  What I think FF is trying to do here is resolve this "defect" "asymmetry" in the Fortran standard in that, like a deep copy, if a RHS component is not allocated, then the LHS component should also be deallocated to match RHS.  This example below throws the following error:

Attempt to fetch from allocatable variable A when it is not allocated

    real, allocatable :: a(:), b(:)
    a = [1.0,2.0,3.0]
    b = a
    deallocate(a)
    b = a       ! Why doesn't this just deallocate b(:)?

Perhaps Steve can comment on why the last assignment above seems to be invalid Fortran, yet if 'a' or 'b' were allocatable components of a higher (derived) type, the deep copy would just match allocation status?

0 Kudos
Steve_Lionel
Honored Contributor III
2,663 Views

It's invalid because in that last assignment, "a" is in an expression, which requires a value, and that in turn requires that the value be defined. Yes, an exception for this case could be carved out, but it hasn't.

0 Kudos
FortranFan
Honored Contributor II
2,225 Views

jimdempseyatthecove wrote:

FF, can you explain why in assign_t when rhs%strVal is not allocated, that you assure this%strVal is not allocated? ..

Jim,

Please see Quote #19, answered nicely there.  Generally for defined assignment, it may help to match what the standard mentions for intrinsic assignment of derived types keeping also in mind one's needs with shallow vs deep copy:

NOTE 10.43
If an allocatable component of expr is unallocated, the corresponding component of the variable has an
allocation status of unallocated after execution of the assignment.

 

{Edit: change to Quote #19 in first sentence in this comment)

0 Kudos
Reply