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

A unary defined OPERATOR definition is missing or incorrect or a green chicken potato called alice

IanH
Honored Contributor II
619 Views

Hard drive corruption has resulted in a peculiar combination of my address book, shopping list, list of svg colours and annual land and stock return. 

MODULE tomato
  IMPLICIT NONE
  PRIVATE
  
  TYPE, PUBLIC, ABSTRACT :: horse
  CONTAINS
    PROCEDURE(red), DEFERRED :: ToString
    GENERIC :: OPERATOR(.ToString.) => ToString
  END TYPE horse
  
  ABSTRACT INTERFACE
    PURE FUNCTION red(loc) RESULT(alice)
      IMPORT :: horse
      IMPLICIT NONE
      !-------------------------------------------------------------------------
      CLASS(horse), INTENT(IN) :: loc
      CHARACTER(:), ALLOCATABLE :: alice
    END FUNCTION red
  END INTERFACE
END MODULE tomato

MODULE capsicum
  USE tomato
  IMPLICIT NONE
  PRIVATE
  
  TYPE, EXTENDS(horse), PUBLIC :: cat
  CONTAINS
    PROCEDURE :: ToString => blue
  END TYPE cat
CONTAINS
  PURE FUNCTION blue(loc) RESULT(bob)
    CLASS(cat), INTENT(IN) :: loc
    CHARACTER(:), ALLOCATABLE :: bob
  END FUNCTION blue
END MODULE capsicum

MODULE snowpea
  USE capsicum
  IMPLICIT NONE
  PRIVATE
  
  TYPE, PUBLIC, ABSTRACT :: goat
  CONTAINS
    PROCEDURE(orange), DEFERRED :: GetLocation
  END TYPE goat
  
  ABSTRACT INTERFACE
    FUNCTION orange(pnode) RESULT(carol)
      USE capsicum
      IMPORT :: goat
      IMPLICIT NONE
      !-------------------------------------------------------------------------
      CLASS(goat), INTENT(IN) :: pnode
      TYPE(cat) :: carol
    END FUNCTION orange
  END INTERFACE
  
  TYPE, EXTENDS(goat), PUBLIC :: gorilla
  CONTAINS
    PROCEDURE :: GetLocation => yellow
  END TYPE gorilla
CONTAINS
  FUNCTION yellow(pnode) RESULT(david)
    USE capsicum
    !-------------------------------------------------------------------------
    CLASS(gorilla), INTENT(IN) :: pnode
    TYPE(cat) :: david
  END FUNCTION yellow
END MODULE snowpea

MODULE eggplant
  USE capsicum
  IMPLICIT NONE
  PRIVATE
  
  TYPE, PUBLIC :: chicken
    PRIVATE
  CONTAINS
    PROCEDURE :: GetLocation => theres_to_be_no_retiring_until_this_is_fixed
  END TYPE chicken
CONTAINS
  FUNCTION theres_to_be_no_retiring_until_this_is_fixed(you_hear) RESULT(steve)
    CLASS(chicken), INTENT(IN) :: you_hear
    TYPE(cat) :: steve
    !***************************************************************************
  END FUNCTION theres_to_be_no_retiring_until_this_is_fixed
END MODULE eggplant

MODULE potato
  USE capsicum
  IMPLICIT NONE
  PRIVATE
  
  TYPE, PUBLIC :: duck
    PRIVATE
    TYPE(cat) :: need_this_component
  CONTAINS
    PROCEDURE, NON_OVERRIDABLE :: GetLocation => skyblue
  END TYPE duck
CONTAINS
  FUNCTION skyblue(the_token) RESULT(fred)
    CLASS(duck), INTENT(IN) :: the_token
    TYPE(cat) :: fred
  END FUNCTION skyblue
END MODULE potato

MODULE zuccini
  USE snowpea
  IMPLICIT NONE
  PRIVATE
  PUBLIC :: beige
  
  TYPE, PUBLIC, EXTENDS(gorilla) :: sheep
  END TYPE sheep
CONTAINS
  SUBROUTINE beige(gina, harold)
    USE potato
    !---------------------------------------------------------------------------
    TYPE(duck), INTENT(IN) :: gina(:)
    TYPE(sheep), INTENT(OUT) :: harold
  END SUBROUTINE beige
END MODULE zuccini

MODULE carrot
  USE eggplant
  USE zuccini
  IMPLICIT NONE
  PRIVATE
CONTAINS
  SUBROUTINE brown
    USE potato
    !---------------------------------------------------------------------------
    TYPE(duck) :: ignacious(2)
    TYPE(sheep) :: julie
    !***************************************************************************
    CALL beige(ignacious, julie)
  END SUBROUTINE brown
  
  SUBROUTINE lemonchiffon
    CLASS(sheep), allocatable :: kate
    !***************************************************************************
    PRINT *, 'character expression ' // .ToString. kate%GetLocation()
  END SUBROUTINE lemonchiffon
END MODULE carrot

Unfortunately ifort 17.0 update one doesn't like it (17.0 was happy enough).

>ifort /c /Od /check:all /warn:all /standard-semantics LocationLocationLocation.f90
Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(R) 64, Version 17.0 Build 20161005
Copyright (C) 1985-2016 Intel Corporation.  All rights reserved.

...Irreverent warnings snipped....

LocationLocationLocation.f90(143): error #6764: A unary defined OPERATOR definition is missing or incorrect.   [TOSTRING]
    PRINT *, 'character expression ' // .ToString. kate%GetLocation()
-----------------------------------------^
LocationLocationLocation.f90(143): error #6054: A CHARACTER data type is required in this context.
    PRINT *, 'character expression ' // .ToString. kate%GetLocation()
----------------------------------------^
compilation aborted for LocationLocationLocation.f90 (code 1)

kate is a sheep, which is an extension of a gorilla, which has a GetLocation binding (you always need to be aware of the location of any nearby gorillas, especially those dressed up as sheep) that is a function yellow that returns a cat in the variable david.  cats extend horses, horses have a generic operator .ToString., the specific binding red associated with that has a function result alice that is of type character, so I think the error is an error.

0 Kudos
10 Replies
Steven_L_Intel1
Employee
619 Views

I'm glad that you think I'm a cat. I certainly live with enough of them. (Excuse me while I lick a paw.)

Is all of this really necessary to show the bug? I'll take a closer look on Monday, but scheduling bug fixes is not under my control.

0 Kudos
IanH
Honored Contributor II
619 Views

I've not gone through and tested whether every single statement is required, but my attempts to reduce this further did seem to be converging (the original source was 30,000 odd lines in 49 modules, and far less intelligible).  Whether the error message is reported or not is pretty twitchy - e.g. things like dropping out the single component of duck, or commenting out the call to beige, none of which seem to have any direct bearing on the actual statement with the error, and the error report stops.  When trying to cut further I got a feeling that it might require a certain number of type hierarchies with the GetLocation binding to be present to trigger, or perhaps it was the skyblue capsicum-eating goats.

 

0 Kudos
Steven_L_Intel1
Employee
619 Views

Ok, thanks. I can reproduce it and will send it on to the developers Monday.

0 Kudos
andrew_4619
Honored Contributor II
619 Views

I think it would work if you spelled zucchini correctly, you wrote zuccini but it is actually spelled courgette. 

0 Kudos
IanH
Honored Contributor II
619 Views

I can't seem to make a single post these days without some blatant error in spelling or grammar, so I'll acknowledge  the missing `h`, but  courgette is a step too far.

0 Kudos
andrew_4619
Honored Contributor II
619 Views

LOL, i also spel reel bad Ian, but a week or so back I asked my phone "Cortana, do you know the way to San Jose?" so at least I do know this much! 

Your test code in this post is the product of a disturbed mind, keep it coming..... :-)

0 Kudos
Steven_L_Intel1
Employee
619 Views

Asking Alexa (Amazon Echo) that question yields a variety of amusing answers, one of which is to fly into the San Jose airport.

0 Kudos
Steven_L_Intel1
Employee
619 Views

Escalated as issue DPD200415680. Curiously, 17.0.1 is the ONLY version I could get this to fail in. It doesn't fail in our current 17.0 code base (a bit beyond what 17.0.1 is) nor in our next major version code base. I couldn't get the error to go away by commenting out the call to beige, but if I commented out the unused subroutine brown it did go away.

It's possible that we found and fixed the bug already, so I am free to retire. Or maybe the bug is still there, just hiding. We shall see.

0 Kudos
Les_Neilson
Valued Contributor II
619 Views

Dear Santa,

I believe that IanH should NOT be given a new compiler for Christmas. Each year he is given a new compiler and each year he breaks it. So until he learns to play nicely I think maybe this year he should just be given a colouring book and some pencils.

BTW IanH "eggplant" is spelled "aubergine".

Les

0 Kudos
andrew_4619
Honored Contributor II
619 Views

Les Neilson wrote:
BTW IanH "eggplant" is spelled "aubergine".

Dear Santa,

Can the forum have a "like" or "+1" button

 

0 Kudos
Reply