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

dynamic character array of deferred length in subroutine

Alexey_M_
Beginner
1,364 Views

I have found that that dynamic character array of deferred length in subroutine could not be allocated.

Here is the sample code. One array is declared in the main program (var name is array_main) and is being passed to subroutine. In subroutine this array is being declared as array_sub1. Also subroutine contains another array - array_sub2.

And here is the problem. First array (array_sub1) has no problems with allocation in the subroutine. The allocation of array_sub2 is not seen in debugger ("Undefined pointer/array") when program is being run the next after allocation statements. At the same time there are no error signs such as non zero error stat.

Where is the problem? How to allocate array of this kind in subroutine?

Intel Visual Fortran Composer XE 2013 + Microsoft Visual Studio 2012

 program TEST_PROG
    implicit none
    CHARACTER*(:), ALLOCATABLE :: array_main(:)
    INTERFACE
        SUBROUTINE TEST_SUB (array_sub1)
            IMPLICIT NONE
            INTEGER nword, wordlen, statv
            CHARACTER*(7) errv
            CHARACTER*(:), ALLOCATABLE :: array_sub1(:)
            CHARACTER*(:), ALLOCATABLE :: array_sub2(:)
        END SUBROUTINE
    END INTERFACE

    CALL TEST_SUB(array_main)
    end program TEST_PROG

    SUBROUTINE TEST_SUB (array_sub1)
    IMPLICIT NONE
    INTEGER nword, wordlen, statv
    CHARACTER*(7) errv
    CHARACTER*(:), ALLOCATABLE :: array_sub1(:)
    CHARACTER*(:), ALLOCATABLE :: array_sub2(:)

    nword = 3; wordlen = 4
    ALLOCATE (CHARACTER(wordlen)::array_sub2(nword), STAT=statv, ERRMSG=errv)
    WRITE (*,*) statv, errv
    ALLOCATE (CHARACTER(wordlen)::array_sub1(nword), STAT=statv, ERRMSG=errv)
    WRITE (*,*) statv, errv
    array_sub2(1) = 'abab'
    array_sub2(2) = 'cdcd'
    array_sub2(3) = 'efef'
    END SUBROUTINE

 

0 Kudos
11 Replies
Steven_L_Intel1
Employee
1,364 Views

It seems to me that this should work, but I confirm that it doesn't. Let me look at it a bit more.

0 Kudos
FortranFan
Honored Contributor III
1,364 Views

Steve Lionel (Intel) wrote:

It seems to me that this should work, but I confirm that it doesn't. Let me look at it a bit more.

Steve,

What exactly do you mean when you say "this should work, but I confirm that it doesn't"?  Are you referring to OP's statement "The allocation of array_sub2 is not seen in debugger ("Undefined pointer/array")" or something else?

I don't think there are any actual issues with assignment and allocation with the variable of character type here.  If I take the code by OP and add some assignments and introduce write statements, the output is as expected.  I think the problem is just in the debugger.

And if I'm not mistaken, the debugger problem is the same as the one in this thread: https://software.intel.com/en-us/forums/topic/535663.

Thanks,  

 

 

0 Kudos
Steven_L_Intel1
Employee
1,364 Views

I was looking at the assignments but now see that I was testing the wrong variable.

The program passes array_main to array_sub1, but then assigns to array_sub2 which is a local and gets deallocated on return. When I fix this, then the program executes correctly. Yes, the debugger does not properly display the values. I am using the current compiler version, I see Alexey is using a rather old one.

0 Kudos
FortranFan
Honored Contributor III
1,364 Views

Alexey,

If you run the following code, do you get the following output:

program TEST_PROG
   implicit none
   CHARACTER*(:), ALLOCATABLE :: array_main(:)
   INTERFACE
       SUBROUTINE TEST_SUB (array_sub1)
           IMPLICIT NONE
           INTEGER nword, wordlen, statv
           CHARACTER*(7) errv
           CHARACTER*(:), ALLOCATABLE :: array_sub1(:)
           CHARACTER*(:), ALLOCATABLE :: array_sub2(:)
       END SUBROUTINE
   END INTERFACE

   CALL TEST_SUB(array_main)
   write(*,*) " array_main = ", array_main

   end program TEST_PROG

   SUBROUTINE TEST_SUB (array_sub1)
   IMPLICIT NONE
   INTEGER nword, wordlen, statv
   CHARACTER*(7) errv
   CHARACTER*(:), ALLOCATABLE :: array_sub1(:)
   CHARACTER*(:), ALLOCATABLE :: array_sub2(:)

   nword = 3; wordlen = 4
   ALLOCATE (CHARACTER(wordlen)::array_sub2(nword), STAT=statv, ERRMSG=errv)
   WRITE (*,*) statv, errv
   ALLOCATE (CHARACTER(wordlen)::array_sub1(nword), STAT=statv, ERRMSG=errv)
   WRITE (*,*) statv, errv
   array_sub2(1) = 'abab'
   array_sub2(2) = 'cdcd'
   array_sub2(3) = 'efef'
   write(*,*) " array_sub2 = ", array_sub2
   array_sub1 = array_sub2
   END SUBROUTINE
 0
 0
  array_sub2 = ababcdcdefef
  array_main = ababcdcdefef
Press any key to continue . . .

 

0 Kudos
FortranFan
Honored Contributor III
1,364 Views

Steve Lionel (Intel) wrote:

I was looking at the assignments but now see that I was testing the wrong variable.

The program passes array_main to array_sub1, but then assigns to array_sub2 which is a local and gets deallocated on return. When I fix this, then the program executes correctly. Yes, the debugger does not properly display the values. I am using the current compiler version, I see Alexey is using a rather old one.

Steve,

So do you think it is just a problem in the debugger?  And by the way, do you think it is possible to get some priority and urgency to get the debugger problem fixed?  It hurts productivity in not being able to work with such variables in the debugger.

Thanks,

0 Kudos
Steven_L_Intel1
Employee
1,364 Views

Yes, this is just a debugger issue. I will ask our debugger team if they can look at it again.

0 Kudos
shakeham
Beginner
1,364 Views

Steve Lionel (Intel) wrote:

Yes, this is just a debugger issue. I will ask our debugger team if they can look at it again.

 

On a related note, it seems whenever there are multiple layers in the structure with mixed objects and pointers, the debugger is not able to show the values. For example, VS will have trouble showing the values of run_input2%test%dat1 in following code. I've been screwed pretty badly by this and need to add local pointers and recompile to see values.

    ================================
          module testMod
          type test
              real*8,pointer,dimension(:):: dat1
              real*8,pointer,dimension(:,:):: dat2
          end type
          TYPE :: containsMixed
              type(test):: test
          END TYPE containsMixed
          TYPE(containsMixed) :: run_input2
          end module
    
          program main
          use testMod, Only: run_input2
          implicit none
          real*8, dimension(100),target::x
          real*8, dimension(:),pointer::p2=>null()
          x=100D0
          run_input2%test%dat1 =>  x  ! issue 1: we cannot examine run_input2%test%dat1 values in visual studio. 
         end

0 Kudos
Alexey_M_
Beginner
1,364 Views

FortranFan wrote:

If you run the following code, do you get the following output:

program TEST_PROG
   implicit none
.
.
.

   write(*,*) " array_sub2 = ", array_sub2
   array_sub1 = array_sub2
   END SUBROUTINE
 0
 0
  array_sub2 = ababcdcdefef
  array_main = ababcdcdefef
Press any key to continue . . .

Yes. The output is the same. May be my problem is just a debugger issue, as it is mentioned in the discussion.

0 Kudos
Alexey_M_
Beginner
1,364 Views

Steve Lionel (Intel) wrote:

I was looking at the assignments but now see that I was testing the wrong variable.

The program passes array_main to array_sub1, but then assigns to array_sub2 which is a local and gets deallocated on return. When I fix this, then the program executes correctly. Yes, the debugger does not properly display the values. I am using the current compiler version, I see Alexey is using a rather old one.

Yes. I use array_sub2 only in subprogram (in the real project; here I just extracted minimum of code to show the problem). That's why it is important to me to allocate it properly.

Steve, does your answer that it is the debugger problem mean that the code by itself is being compiled correctly and I can use it not taking in account the debuggers' behavior?

0 Kudos
Steven_L_Intel1
Employee
1,364 Views

Yes, the compiled code seems to be correct.

0 Kudos
Alexey_M_
Beginner
1,364 Views

Thank you, FortranFan and Steve!

0 Kudos
Reply