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

Problem with CHARACTER(*) :: PICKLIST(:)

dboggs
New Contributor I
3,863 Views

I have a program that I am working on in two different places on my computer. The programs are nearly identical. Here is excerpt:

PROGRAM TEST_EDCELL

INTEGER, PARAMETER :: LENGTH = 5

CHARACTER(20) :: PICKLIST(LENGTH)

... define PICKLIST(1) through PICKLIST(5)...

CALL EDCELL (IROW, ICOL, ...PICKLIST...RETURNCODE)

END PROGRAM

 

SUBROUTINE PICKLIST (IROW, ICOL, ...PICKLIST...RETURNCODE)

CHARACTER(*) :: PICKLIST(:)

...

PRINT *, PICKLIST

END SUBROUTINE

In the first location this program runs fine. In the second location it compiles and links without error, but gives a runtime error "Program execption-stack overflow" on the PRINT *, PICKLIST line. In the debugger watchlist, PICKLIST is identified as "Undefined pointer/array".

I cannot see any differences in the codes or the directory structure that could cause these differences. In both cases I am running 2011.10.325. I believe that all of the compiler and link switches are standard. Can you suggest where or how to look for the cause? 

0 Kudos
31 Replies
dboggs
New Contributor I
915 Views

Re: "If we are unable to provide the required interfaces, we should not link against the library...the compiler cannot give any warnings..."

Yes it can--just do it! There is a well defined set of criteria for when an interface is required, and if the compiler cannot tell if one was provided (i.e. the procedure is not a module or internal), then I think it should give a warning. In the example at hand, there is a subroutine with array argument A declared as A(:), and it caused trouble. On the other hand the declaration A(*) did not cause trouble. OK, the first method is more robust (safer), but only if the interface is provided. It would have saved a lot of trouble if the compiler had simply warned that an explicit array must be provided. Here is a case where the A(*) (assumed length) technique actually caused less trouble, only because the coder didn't realize that A(:) required an interface.

(To clarify: using A(*) the code consistently compiles and links OK, and runs OK as long as the programmer is careful that the subroutine code does not overwrite the bounds of A. Using A(:), without an interface, the program consistently compiles OK, but doesn't always link, and when it does link, it runs OK sometimes and fails other times, even when the code does not overwrite the bounds of A. So I feel that the assumed length A(*) method is more reliable than the assumed shape A(:) method, UNLESS THE COMPILER ISSUES A WARNING ABOUT NEEDING AN INTERFACE.)

0 Kudos
John_Campbell
New Contributor II
915 Views
I once tried a coding approach to provide the calling information for all routines in a project. I defined a single module with interface definitions for all routines. Unfortunately, when I compiled it with the compiler I was using at that time, it failed as I could not have an interface defined within the same subroutine. If this was accepted, this could be a very good outcome, as the compiler could then check the interface definition ( which is used throughout the project) against the actual routine definition. This would negate the main objection I have with the INTERFACE structure, which is the duplicate definition of the interface. It could be argued that the INTERFACE definition could be used in this way as the definition of the calling interface for the routine. Does anyone else see the benefit of what I am proposing ? . What can be done is to create a module of interface definitions for all external libraries I use. This is a good coding practice. Unfortunately with the present limitations, this must be done carefully, as the interface is not checked against the actual routine. . To answer part of Ian's question, the main functionality of argument list checking that I had wanted (and requested) was merely a check on the argument list count. This simple test could have removed many errors in coding, before IDE's were available. Numerous times, in the 80's I tried out a new workstation fortran compiler, where the compiler developer introduced checks on the type and kind of each argument. For those familiar with memory management prior to F90, this was never a welcome error test, which had to be disabled, often to the strong objections of the compiler developer. Salesmen can be helpful some times! What could be helpful is that for each argument, the kind, rank and size could be supplied automatically, to be used if required. Another special case is to identify arguments that are constants ( eg 1.0 ), that should be flagged as INTENT=IN. However there remains a requirement that all you are transferring is an address, to be used as the called routine requires. This option should never be excluded. This approach might not appeal to some compiler developers or computer scientists, but it would answer the needs of this fortran programmer, who actually graduated with a computer science major in 1973. There have been many good programming rules come and go since then. . John
0 Kudos
JVanB
Valued Contributor II
915 Views

mecej4 wrote:
(ii) If we wish to use a library as in (i) but do not have the module files, or the module files are not compatible with our Fortran compiler, we need to write INTERFACE blocks or modules containing interfaces by consulting the documentation of the library routines, and make these interfaces available in each caller.

If the module files are not compatible with your Fortran compiler, you are simply dead meat. That means that the Fortran procedures that require an explicit interface will not be compatible with your Fortran compiler, either.

Regarding another comment, permit me to remark that you can check an interface definition against the actual procedure if you provide code within the procedure to do it.

[fortran]module ifaces
   implicit none
   interface
      subroutine s(x)
         real x(:)
      end subroutine s
   end interface
end module ifaces

subroutine s(x)
   use ifaces
   use ifaces, only: chk => s
   implicit none
   real x(:)
   procedure(chk), pointer :: p

   if(.FALSE.) p => s
   x = 1
end subroutine s

program p
   use ifaces
   implicit none
   real x(5)

   call s(x)
   write(*,*) x
end program p
[/fortran]

Subroutine s here uses the module that provides an explicit interface for it. As is, the code compiles and runs. However if the interface body is changed to something incompatible, for e.g.,

[fortran]interface
      subroutine s(x)
         real x(:,:)
      end subroutine s
   end interface[/fortran]

Then the compiler (gfortran) errors out. The checking should not cost anything at runtime because dead code and unused local variable elimination should throw it out.

0 Kudos
IanH
Honored Contributor III
915 Views

Repeat Offender wrote:
Regarding another comment, permit me to remark that you can check an interface definition against the actual procedure if you provide code within the procedure to do it.

(Do you have a stray "use ifaces" in your subroutine?  Assuming so...)

I don't think (and I'm far from sure about it) this is legal code.  The procedure defined by the external subprogram named "s" has two explicit specific interfaces available inside the scope of s - one from the use associated interface block and one from the specification statements of the subprogram itself.  F2008 12.4.3.2p7 doesn't like that.  The fact that those two different interfaces for the same procedure have different local names is not relevant.  This would not be something the compiler would be required to diagnose. 

Why the rules are this way I don't know, but them's the rules.

(ifort 13.0.1 gives an error for this example that I don't expect or understand, but as (I think) the program is non-conforming it could well be argued it is a valid response.)

0 Kudos
JVanB
Valued Contributor II
915 Views

The first "use ifaces" was there because normally one of your library procedures needs the explicit interfaces of the others. The second was there so that the name "s" referred only to the subroutine being defined, not the interface.

It may be possible that by ordering the words in the paragraph cited in some anagram as is your wont one might come up with a meaning that allows one to arrive at the conclusion that my code is nonconforming. No matter:

[fortran]module ifaces
   implicit none
   abstract interface
      subroutine s_abstract(x)
         real x(:)
      end subroutine s_abstract
   end interface
   procedure(s_abstract) s
end module ifaces

subroutine s(x)
   use ifaces
   use ifaces, only: chk => s
   implicit none
   real x(:)
   procedure(s_abstract), pointer :: p

   if(.FALSE.) p => s
   x = 1
end subroutine s

program p
   use ifaces
   implicit none
   real x(5)

   call s(x)
   write(*,*) x
end program p[/fortran]

0 Kudos
IanH
Honored Contributor III
915 Views

Anagrams are fun! 

The reason that I queried the first use statement is that it makes the ONLY: option on the second use redundant, plus wouldn't the "s" name clash inside the sub be nonconforming?  Change those use's to a single "use iface, only: s_abstract" and then I think I have to conceed to your point.

0 Kudos
JVanB
Valued Contributor II
915 Views

No, the rules for the USE statement bear a paradoxicality worthy of C. The "use ifaces, only: chk => s" hides the name "s" from ifaces so the only "s" is the name of the subroutine being defined. Unfortunately hiding the name "s" doesn't actually hide the interface for "s" so I may have to change to
[fortran]module ifaces
   implicit none
   abstract interface
      subroutine s_abstract(x)
         real x(:)
      end subroutine s_abstract
   end interface
   procedure(s_abstract) s
end module ifaces

subroutine s(x)
   use ifaces, only: s_abstract
   implicit none
   real x(:)
   procedure(s_abstract), pointer :: p

   if(.FALSE.) p => s
   x = 1
end subroutine s

program p
   use ifaces
   implicit none
   real x(5)

   call s(x)
   write(*,*) x
end program p[/fortran]
as you said to make you happy. Is ifort similary joyful?

0 Kudos
IanH
Honored Contributor III
915 Views

ifort isn't happy.  It gives the same error message that I didn't "expect or understand" before.

[plain]>ifort /check:all /warn:all /standard-semantics "2013-01-14 intf.f90"
Intel(R) Visual Fortran Compiler XE for applications running on IA-32, Version 13.0.1.119 Build 20121008
Copyright (C) 1985-2012 Intel Corporation.  All rights reserved.

2013-01-14 intf.f90(15): error #8191: The procedure target must be a procedure or a procedure pointer.  
   if(.FALSE.) p => s
--------------------^
compilation aborted for 2013-01-14 intf.f90 (code 1)[/plain]

Looking at F2008 C729 it could possibly be justified.  In terms of having a procedure name as a proc target...

"A procedure name shall be the name of ... an external procedure that is accessed by use or host association and is referenced in the scoping unit as a procedure or that has the EXTERNAL attribute..."

I don't know what the precedence of the last (bolded) "or" is supposed to be relative to the bolded "and".  Is "an external procedure ... that has the external attribute" valid in its own right, or must it be also accessed via host or use association.  I suspect the latter.

0 Kudos
JVanB
Valued Contributor II
915 Views

Since and is logical product and or is logical sum, and has precedence just like in Fortran, so my last example is conforming, unless you really prefer anagrams.
An example of how use, only: hides names from simple use:
[fortran]module m1
   implicit none
   contains
      subroutine s
         write(*,'(a)') 'The host associated subroutine was called.'
      end subroutine s
end module m1

module m2
   implicit none
   contains
      subroutine s
         write(*,'(a)') 'The use associated subroutine was called.'
      end subroutine s
end module m2

module m3
   use m1, only: s => s
   implicit none
   contains
      subroutine t
         use m2
         use m2, only: chk => s
         call s
      end subroutine t
end module m3

program p
   use m3
   implicit none
   call t
end program p[/fortran]

gfortran and I vote for calling the host associated subroutine. g95 and ftn95 vote for the use associated subroutine. How do you and ifort vote?

0 Kudos
IanH
Honored Contributor III
915 Views

Ifort agrees with you, after remarking about the ONLY.  Reading F2008 I can now see why.  There you go!

Not quite sure that I agree that the rules of "and" and "or" in the English language follow that of Fortran precedence, but this is not the first occasion that I'd have preferred the language to use parentheses for clarity...

0 Kudos
JVanB
Valued Contributor II
915 Views

I think I have decoded the meaning of C279. Section 5.3.9 says
[fortran]subroutine s(x)
   implicit none
   character(*) x
   write(*,'(a)') 'Subroutine s was called '//x//'.'
end subroutine s

subroutine t(s)
   implicit none
   call s('from t')
end subroutine t

program p
   implicit none
   procedure(), pointer :: pp

   call s('legally')
   pp => s ! Illegal, see 5.3.9 p2
   call pp('illegally')
   call t(s) ! Also illegal, see 5.3.9 p2
end program p[/fortran]
is illegal, but C279 allows
[fortran]subroutine s(x)
   implicit none
   character(*) x
   write(*,'(a)') 'Subroutine s was called '//x//'.'
end subroutine s

subroutine u(x)
   implicit none
   character(*) x
   write(*,'(a)') 'Subroutine u was called '//x//'.'
end subroutine u

program p
   implicit none
   external u

   call s('once')
   call t
   contains
      subroutine t
         procedure(), pointer :: pp
         pp => s ! Legal, see C729
         call pp('again')
         pp => u ! Legal, see C729
         call pp('from t')
      end subroutine t
end program p[/fortran]
However, both gfortran and g95 like the first example, and while g95 compiles the second example, it causes an ICE in gfortran.
If the main program of the first example is changed to
[fortran]subroutine s(x)
   implicit none
   character(*) x
   write(*,'(a)') 'Subroutine s was called '//x//'.'
end subroutine s

subroutine t(s)
   implicit none
   call s('from t')
end subroutine t

program p
   implicit none
   procedure(), pointer :: pp

   pp => s ! Illegal, see 5.3.9 p2
   call pp('illegally')
   call t(s) ! Also illegal, see 5.3.9 p2
   call s('legally')
end program p[/fortran]
then g95 still likes it, but gfortran gets some kind of wierd error at link time. Any comments?

0 Kudos
Reply