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

The IMPLICIT NONE issue drags on

Andrew_Smith
Valued Contributor I
7,581 Views

It is good practice to use IMPLICIT NONE but it is hard to enforce because one has to pepper code with IMPLICIT NONE and when you miss one, there is nothing to tell you unless you use a non-standard compiler directive.

The standard should make life easier for us by making good things the default when it does not break old code. Module procedures is new so the standard could have been better in this area.

This code raises no errors. You can add IMPLICIT NONE to all the module procedure interfaces but it can be an onerous task.

We dont need an IMPORT statement in the module procedure interface because this special type of interface picks up the scope of the module. Since the parent module has IMPLICIT NONE, the module interfaces should see this.

Is this a correct interpretation of the standard and if not why was the standard lacking in this area?

module A

   implicit none
   
   interface
      module subroutine foo(X)
      end
   end interface

end module

 

45 Replies
JVanB
Valued Contributor II
2,225 Views

/assume:[no]protect_constants doesn't apply to character constants. You have to compile with /assume:writeable_strings for some standard-conforming codes to run correctly.

module constants
   implicit none
   character, parameter :: hello*(*) = 'Hello, world!'//achar(0)
end module constants

module funcs
   implicit none
   contains
      subroutine trashme(string,length)
         integer length
         character string(length)
         call trashme2(string(:length:2))
         write(*,'(*(g0))') string(:length)
      end subroutine trashme
      subroutine trashme2(array)
         character array(:)
         call trashme3(array)
      end subroutine trashme2
end module funcs

subroutine trashme3(array)
   implicit none
   character array(*)
end subroutine trashme3

program test
   use constants
   use funcs
   implicit none
   call trashme(hello, index(hello,achar(0))-1)
end program test

 

0 Kudos
Steve_Lionel
Honored Contributor III
2,225 Views

RO, that is pure evil - my congratulations. The issue here is that when trashme2 calls trashme3, it has to pass a contiguous copy because the argument passed to trashme2 is not contiguous. The compiler doesn't know what trashme3 does, so it has to copy the elements of the temp back to the dummy - which is not definable since it is a constant.

I am going to run this by the committee and see what they think. I believe a new restriction is in order, but am not sure how it should be worded.

0 Kudos
Steve_Lionel
Honored Contributor III
2,225 Views

After moire studying of the standard, I believe that RO's program is in fact not standard-compliant. The relevant text (from F2015 draft section 15.5.2.4, Argument Association > Ordinary Dummy Variables) is:

The length type parameter values of a present actual argument shall agree with the corresponding ones of the dummy argument that are not assumed, except for the case of the character length parameter of an actual argument of type character with default kind or C character kind (18.2.2) associated with a dummy argument that is not assumed-shape or assumed-rank.

In this case, the dummy argument of trashme2 is assumed-shape, therefore the length parameters must match - they do not. Unfortunately this is not something the compiler can check since it doesn't know how long the substring is. If the substring was only a single character, so that the lengths match, it would be contiguous and no copy needed.

0 Kudos
JVanB
Valued Contributor II
2,225 Views

Thanks for looking at the issue Steve, but this time I am at variance with your analysis. Would it have been clearer if I had declared dummy argument string in subroutine trashme as

CHARACTER(LEN=1,KIND=KIND('A')), DIMENSION(length) :: string

And then dummy argument array in subroutine trashme2 as

CHARACTER(LEN=1,KIND=KIND('A')), DIMENSION(:) :: array

Since my reading of the standard is that the Fortran processor implicitly fills in the blanks in this fashion.

Thus string(:length:2) is an array section, not a substring. Check LEN(string(:length:2)), KIND(string(:length:2)), and SHAPE(string(:length:2)) to confirm. ifort prints out 1, 1, and 7 for these quantities.

 

0 Kudos
Steve_Lionel
Honored Contributor III
2,225 Views

My apologies, RO, I should have known better than to doubt you. You're correct that I misread the code. The character type is really not relevant - I think you could get into the same trouble with an integer array constant and passing it the way you have. Let me ponder this some more.

0 Kudos
Steve_Lionel
Honored Contributor III
2,225 Views

I ran this by the committee and the concensus seems to be that RO's example is legal. Most compilers behave as ifort does here, but not all.

The suggested solution for compiler developers is that when a character constant is passed to a routine with no explicit interface or one where the dummy argument is known to be an array with INTENT either omitted or not IN, pass a writable copy of the constant. Kevin, please pass this on to the developers.

0 Kudos
JVanB
Valued Contributor II
2,225 Views

Cool. But should "when a character constant is passed" be changed to something like "when a character constant or character dummy argument with INTENT(IN) is passed"? Otherwise one could insert a trashme1 subroutine with a character(*), intent(in) dummy that was called by program test and called subroutine trashme and cause the crash the same way.

 

0 Kudos
Steve_Lionel
Honored Contributor III
2,225 Views

Yes, that sounds right.

0 Kudos
JVanB
Valued Contributor II
2,225 Views

Oh yeah, there's also the case where the actual argument is potentially READONLY and the dummy argument is intent(in) but also has the TARGET attribute, because any pointer (Fortran or C_PTR) to READONLY data can run you through the same wringer...

 

0 Kudos
Steve_Lionel
Honored Contributor III
2,225 Views

In that case it's the programmer's fault for storing to an INTENT(IN) argument. Really the issue here relates to the compiler needing to copy back possible changes. Any modification done by the programmer then violate other rules.

0 Kudos
JVanB
Valued Contributor II
2,225 Views

Here is roughly what I am talking about:

module constants
   use ISO_C_BINDING
   implicit none
   character(LEN=*,KIND=C_CHAR), parameter :: hello = 'Hello, world!'//achar(0)
end module constants

module funcs
   use ISO_C_BINDING
   implicit none
   contains
!      subroutine level1(string)
      subroutine level1(string,length)
         integer length
!         character(LEN=*,KIND=C_CHAR), intent(in) :: string
         character(LEN=length,KIND=C_CHAR), intent(in) :: string
         call level2(string)
      end subroutine level1

      subroutine level2(string)
         character(LEN=*,KIND=C_CHAR), intent(in), target :: string
         call level3(string,LEN(string))
      end subroutine level2

      subroutine level3(array,length)
         integer length
         character(KIND=C_CHAR), intent(in), target :: array(length)
         type(C_PTR) p
         p = C_LOC(array)
         call level4(p,length)
      end subroutine level3

      subroutine level4(p,length)
         type(C_PTR) p
         integer length
         character(KIND=C_CHAR), pointer :: array(:)
         call C_F_POINTER(p,array,[length])
         call trashme(array,length)
      end subroutine level4

      subroutine trashme(string,length)
         integer length
         character(KIND=C_CHAR) string(length)
         call trashme2(string(:length:2))
         write(*,'(*(a))') string(:length)
      end subroutine trashme

      subroutine trashme2(array)
         character(KIND=C_CHAR) array(:)
         call trashme3(array)
      end subroutine trashme2
end module funcs

subroutine trashme3(array)
   use ISO_C_BINDING
   implicit none
   character(KIND=C_CHAR) array(*)
end subroutine trashme3

program test
   use constants
   use funcs
   use ISO_C_BINDING
   implicit none
!   call level1(hello)
   call level1(hello,index(hello,achar(0))-1)
end program test

One thing I noticed in composing this example was that if the dummy argument in subroutine level1 is assumed length, it finds itself in writeable memory, but if its LEN is given as another dummy argument it will be in READONLY memory unless /assume:writeable_strings is in effect. But on to the discussion:

In subroutine level1, the Fortran processor knows that, because ifort can pass actual arguments in READONLY memory to intent(in) character scalars, it's possible the dummy argument string is in REAONLY memory. What happens if it passes string directly to subroutine level2 rather than a copy in writeable memory?

In that case, subroutine level2 can't make a copy to pass to subroutine level3 because any pointers that get associated with dummy argument array in subroutine level3 will remain associated in level2, and in its caller. While in subroutine level2 the Fortran processor has no memory of whether any pointers were associated with dummy argument string higher up in the call chain. Thus subroutine level3 will get a READONLY dummy argument array.

In subroutine level3, we now point a C_PTR at that READONLY memory and pass it along to subroutine level4.

Now in subroutine level4 we get a Fortran pointer to that READONLY memory and pass it along to known fatal subroutine trashme. How could the Fortran processor save itself at this point? Passing the target of pointer array directly to subroutine trashme causes a GPF, but copy-in/copy-out causes the same GPF directly. Thus I claim that we were on the hook with no escape when we invoked subroutine level2 without making a copy of the potentially READONLY memory that was going to get associated with an intent(in), target character scalar dummy argument.

I point out that at no time was the READONLY memory used in a variable definition context.

 

0 Kudos
Jim_A_
Beginner
2,225 Views

Is here a setting in "Property Pages" or somewhere else in the Intel FORTRAN within Microsoft Visual Studio that disables the "EXPLICIT NONE" statement?

0 Kudos
Steve_Lionel
Honored Contributor III
2,225 Views

There is no "EXPLICIT NONE" statement. Do you mean IMPLICIT NONE? No, there is no option to cause that to be ignored. Why would you want that?

0 Kudos
John_Campbell
New Contributor II
2,225 Views

I have long wondered why INTENT was introduced into the language. It could be:

1) as with IMPLICIT NONE, for the compiler to check the use of a variable in the routine, that it complies with the INTENT and give warning/error reports if it does not.

2) act on the INTENT selection to make sure the interface can be managed/optimised to make use of the explicit INTENT selection.

3) when combined with an INTERFACE to optimise the calling of the routine to include or omit unnecessary interface management, such as the use of temporary or non-contiguous memory.

4) I have probably left others out !!

However the problem I have, as a programmer, is : Are these points above optional for the compiler to implement or can we assume the compiler must perform these functions ? I find the standard to be vague in what we can confidently assume the compiler will do, and so rarely use these features, only sometimes including them when I wish to provide better documentation for the routine calls, for later reference.

The devil is in the detail and many things in the standard that are "processor-dependent" reduce what we can confidently assume when coding. Most of the coding errors I have had when porting software is not recognising features which have a "processor-dependent" qualification.

0 Kudos
Steve_Lionel
Honored Contributor III
2,225 Views

IMPLICIT and INTENT are two entirely different things.

In F2008, IMPLICIT affects classic Fortran implicit typing only. IMPLICIT NONE was added to turn off this ill-advised feature. Fortran 2015 extends IMPLICIT NONE to allow disabling the implicit external nature of procedure references, requiring you to explicitly declare them external (with EXTERNAL or an explicit interface).

INTENT is a declaration by the programmer of what the called procedure wants to do with the dummy argument. It adds information that the compiler can use for optimization and error checking. (For example, you can't assign to an INTENT(IN) dummy, and a compiler could complain if you never define an INTENT(OUT) dummy. Also, a compiler could assume that an INTENT(IN) dummy doesn't change across a procedure call, possibly resulting in faster code.) There are a few "constraints" in the standard about INTENT that a compiler must follow (or have the ability to inform the user if they are violated.)

The standard has constraints a compiler must follow for INTENT. IMPLICIT controls which type (if any) an undeclared variable has, and the standard has rules about typing.

0 Kudos
andrew_4619
Honored Contributor III
2,225 Views

@john - I always now declare intent wherever possible simply as it makes the code clearer and gives the compiler more opportunity to shout at me when I mess up. A bit like seat belt  + air bag + crash helmet ......  

0 Kudos
FortranFan
Honored Contributor III
2,225 Views

andrew_4619 wrote:

@john - I always now declare intent wherever possible simply as it makes the code clearer and gives the compiler more opportunity to shout at me when I mess up. A bit like seat belt  + air bag + crash helmet ......  

Andrew,

What will be also nice is the compiler shouting at the programmer if instructed to do so of course, say with  /warn:intent which may be a subset of /warn:all or some such compilation flag, when the programmer fails to include the INTENT attribute!

Sure the language standard does not require the processor to detect and report such issues.

But I personally think it will nice if certain additional aspects that traditionally might have been the purview of external static analysis utilities can be made part of the compiler diagnostics now to add to the "seat belt + air bag + crash helmet" you seek while coding under the driving influence!  See below:

module m
   ! note missing IMPLICIT NONE 

   save :: x ! /warn:declarations as part of /warn:all can give diagnostics for missing
             ! type declaration for x
   
   interface
      subroutine sub( y )
      ! note missing IMPLICIT NONE in this scope; both type and INTENT of dummy argument are "implicit"
      ! no diagnostics currently available for "implicit" INTENT whereas missing type for y is diagnosed
      ! it will be useful to have something like /warn:intent in such situations
      end subroutine
   end interface

end module

 

 

0 Kudos
Steve_Lionel
Honored Contributor III
2,225 Views

A problem here is that there is no INTENT specifier equivalent to omitting INTENT. It isn't the same as INTENT(INOUT), in that the latter requires that the actual argument be definable, whereas omitting intent does not. I plan to propose for F2020 something like INTENT(UNKNOWN) or (OMITTED) to rectify this. Without such a feature, you can't ask a compiler to mandate INTENT.

0 Kudos
jimdempseyatthecove
Honored Contributor III
2,225 Views

How about INTENT(NONE).

And consider INTENT(UNUSED)

For arguments that are required, for future purposed, but currently are not used in existing implementation.

Jim Dempsey

0 Kudos
Steve_Lionel
Honored Contributor III
2,191 Views

 NONE I think is inaccurate. The concept here is that the user has not specified an intent, not that there isn't one. But J3 will, I am sure, debate this issue and come to an agreement (if they agree to include this feature.) It isn't necessary to get all the details nailed down here.

0 Kudos
andrew_4619
Honored Contributor III
2,191 Views

Steve Lionel (Ret.) wrote:

 NONE I think is inaccurate. The concept here is that the user has not specified an intent, not that there isn't one. But J3 will, I am sure, debate this issue and come to an agreement (if they agree to include this feature.) It isn't necessary to get all the details nailed down here.

INTENT (UNKNOWN) would get my vote it think as a useful language addition, any then have an optional warning for no intent specified. I get this dilema with SDK interfaces where you pass and address but what actually happens to it is dependant upon the values of other args.  

 

0 Kudos
Reply