- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hello,
Again, my environment:
$ ifort --version ifort (IFORT) 16.0.1 20151021 Copyright (C) 1985-2015 Intel Corporation. All rights reserved. $ uname -a Linux tfe03 2.6.32-431.29.2.el6.x86_64 #1 SMP Sun Jul 27 15:55:46 EDT 2014 x86_64 x86_64 x86_64 GNU/Linux
I believe the linux is a flavour of Red Hat (RHEL6 I think).
I discovered what I think may be a minor compiler bug due to my overuse of PRIVATE statements in object definitions. Note the use of the PRIVATE statement in the CONTAINS section of the iVar_type object definition below:
MODULE my_define
IMPLICIT NONE
PRIVATE
PUBLIC :: my_type
! Contained object definition
TYPE, PRIVATE :: iVar_type
INTEGER :: i = 0
CONTAINS
PRIVATE ! *** This is the statement in question ***
PROCEDURE :: iVar_Equal
PROCEDURE :: iVar_NotEqual
PROCEDURE :: iVar_Compare
GENERIC :: OPERATOR(==) => iVar_Equal
GENERIC :: OPERATOR(/=) => iVar_NotEqual
GENERIC :: OPERATOR(.Compare.) => iVar_Compare
END TYPE iVar_type
! The main object definition
TYPE :: my_type
INTEGER :: j = 0
! Contained object
TYPE(iVar_type) :: iVar
CONTAINS
PRIVATE
PROCEDURE :: Equal
PROCEDURE :: NotEqual
PROCEDURE :: Compare_
GENERIC, PUBLIC :: OPERATOR(==) => Equal
GENERIC, PUBLIC :: OPERATOR(/=) => NotEqual
GENERIC, PUBLIC :: OPERATOR(.Compare.) => Compare_
END TYPE my_type
CONTAINS
ELEMENTAL FUNCTION Equal( x, y ) RESULT( is_equal )
CLASS(my_type), INTENT(IN) :: x, y
LOGICAL :: is_equal
is_equal = (x%j == y%j) .AND. (x%iVar == y%iVar)
END FUNCTION Equal
ELEMENTAL FUNCTION iVar_Equal( x, y ) RESULT( is_equal )
CLASS(iVar_type), INTENT(IN) :: x, y
LOGICAL :: is_equal
is_equal = (x%i == y%i)
END FUNCTION iVar_Equal
ELEMENTAL FUNCTION NotEqual( x, y ) RESULT( not_equal )
CLASS(my_type), INTENT(IN) :: x, y
LOGICAL :: not_equal
not_equal = .NOT. (x == y)
END FUNCTION NotEqual
ELEMENTAL FUNCTION iVar_NotEqual( x, y ) RESULT( not_equal )
CLASS(iVar_type), INTENT(IN) :: x, y
LOGICAL :: not_equal
not_equal = .NOT. (x == y)
END FUNCTION iVar_NotEqual
FUNCTION Compare_( x, y ) RESULT( is_equal )
CLASS(my_type), INTENT(IN) :: x, y
LOGICAL :: is_equal
is_equal = .TRUE.
IF ( x%j /= y%j ) THEN
print *, 'J component of my objects are different'
is_equal = .FALSE.
END IF
IF ( x%iVar /= y%iVar ) THEN
print *, 'iVar component of my objects are different'
is_equal = .FALSE.
END IF
END FUNCTION Compare_
FUNCTION iVar_Compare( x, y ) RESULT( is_equal )
CLASS(iVar_type), INTENT(IN) :: x, y
LOGICAL :: is_equal
is_equal = .TRUE.
IF ( x%i /= y%i ) THEN
print *, 'I component of iVar objects are different'
is_equal = .FALSE.
END IF
END FUNCTION iVar_Compare
END MODULE my_define
! =======================
! Test program for module
! =======================
PROGRAM Test_my
USE my_define, ONLY: my_type
IMPLICIT NONE
LOGICAL :: is_equal
TYPE(my_type) :: my, my_copy
my%j = 1
my_copy = my
IF ( my /= my_copy ) THEN
is_equal = my .Compare. my_copy
print *, 'objects are not equal'
ELSE
print *, 'objects are equal'
END IF
END PROGRAM Test_my
When I compile the above I get:
$ ifort two_types.f90
two_types.f90(39): error #6355: This binary operation is invalid for this data type. [IVAR]
is_equal = (x%j == y%j) .AND. (x%iVar == y%iVar)
-------------------------------------^
two_types.f90(39): error #6355: This binary operation is invalid for this data type. [IVAR]
is_equal = (x%j == y%j) .AND. (x%iVar == y%iVar)
-----------------------------------------------^
two_types.f90(58): error #6355: This binary operation is invalid for this data type.
not_equal = .NOT. (x == y)
-----------------------^
two_types.f90(58): error #6355: This binary operation is invalid for this data type.
not_equal = .NOT. (x == y)
----------------------------^
two_types.f90(70): error #6355: This binary operation is invalid for this data type. [IVAR]
IF ( x%iVar /= y%iVar ) THEN
-----------^
two_types.f90(70): error #6355: This binary operation is invalid for this data type. [IVAR]
IF ( x%iVar /= y%iVar ) THEN
---------------------^
compilation aborted for two_types.f90 (code 1)
When I comment out the PRIVATE statement in question the test code compiles and runs fine:
$ diff two_types.f90 two_types_commented.f90
--- two_types.f90 2016-01-25 13:19:42.382898000 +0000
+++ two_types_commented.f90 2016-01-25 13:19:31.705164000 +0000
@@ -7,7 +7,7 @@
TYPE, PRIVATE :: iVar_type
INTEGER :: i = 0
CONTAINS
- PRIVATE ! *** This is the statement in question ***
+! PRIVATE ! *** This is the statement in question ***
PROCEDURE :: iVar_Equal
PROCEDURE :: iVar_NotEqual
PROCEDURE :: iVar_Compare
$ ifort two_types_commented.f90
$ ./a.out
objects are equal
So, while I have a solution to the problem in my production code, should the ifort compiler toss an error due to this extra PRIVATE statement?
Note that the test case compiles and runs using gofrtran 4.9.x
Thanks for any info.
cheers,
paulv
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
What happens with
is_equal = (x%j == y%j) .AND. ((x%iVar) == (y%iVar)) ! add ()'s
There was another thread on idz forum relating to a constructor issue where the additional ()'s resolved the problem.
I cannot recall if the additional ()'s were not required by the specification. The use of the additional ()'s may (stressed) work as a work-around, but will also add some additional overhead in creating temporaries.
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I've tripped over cases where fpp requires parentheses not normally required in Fortran, so I won't rule out possible strange effects of parentheses. Reminder : ifort doesn't necessarily follow standard unless protect_parents or standard-semantics is set. I don't agree with Jim about parentheses necessarily creating a temporary.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
jimdempseyatthecove wrote:
What happens with
is_equal = (x%j == y%j) .AND. ((x%iVar) == (y%iVar)) ! add ()'s
There was another thread on idz forum relating to a constructor issue where the additional ()'s resolved the problem.
I cannot recall if the additional ()'s were not required by the specification. The use of the additional ()'s may (stressed) work as a work-around, but will also add some additional overhead in creating temporaries.
Hi Jim,
Thanks for the info but, nope, no difference:
tfe03:/home/Paul.Vandelst/scratch/intel-bug : ifort two_types.f90
two_types.f90(39): error #6355: This binary operation is invalid for this data type. [IVAR]
is_equal = (x%j == y%j) .AND. ((x%iVar) == (y%iVar))
--------------------------------------^
two_types.f90(39): error #6355: This binary operation is invalid for this data type. [IVAR]
is_equal = (x%j == y%j) .AND. ((x%iVar) == (y%iVar))
--------------------------------------------------^
I need to check but I would be very surprised if the standard required the extra parentheses. That, to me at least, would suggest the structure separator, %, has a lower precedence than the operator. Which doesn't make sense...or does it? I'm having a hard time wrapping my head around how that would work? (Not enough coffee this morning....after being trapped inside most of the weekend due to snow)
cheers,
paulv
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks for the report - we'll check it out.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Paul, thanks for this one - seems very odd that accessibility changes would affect uses in the same module! Escalated as issue DPD200381114.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Steve Lionel (Intel) wrote:
Paul, thanks for this one - seems very odd that accessibility changes would affect uses in the same module! Escalated as issue DPD200381114.
And thanks again.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I expect the fix for this to appear in Parallel Studio XE 2016 Update 3.
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page