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

Structure/Array constructor syntax complaints

IanH
Honored Contributor III
491 Views

I think I've been running around all week calling array constructors structure constructors and vice versa, but anyway... this is perhaps about both structure constructors and array constructors, so I'm on safe terminology territory.  One of them is involved!

MODULE m
  IMPLICIT NONE
  
  ! The parent of our Fortran type inheritance tree.
  TYPE, ABSTRACT :: Node
  END TYPE Node
  
  ! An element in an array of Nodes, where the elements can be 
  ! of different dynamic type.
  TYPE :: NodeElement
    CLASS(Node), ALLOCATABLE :: item
  END TYPE NodeElement
  
  ! An extension of Node that can hold other nodes.
  TYPE, EXTENDS(Node) :: ParentNode
    TYPE(NodeElement), ALLOCATABLE :: children(:)
  END TYPE ParentNode
  
  ! An extension of Node that can hold an integer.
  TYPE, EXTENDS(Node) :: IntegerNode
    INTEGER :: i
  END TYPE IntegerNode
  
  ! A node that can't.
  TYPE, EXTENDS(Node) :: EmptyNode
  END TYPE EmptyNode
END MODULE m

PROGRAM p
  USE m
  IMPLICIT NONE
  
  TYPE(EmptyNode) :: a              ! Scalar empty node.
  TYPE(IntegerNode) :: b            ! Scalar integer node.
  TYPE(NodeElement) :: c            ! Scalar node element.
  
  ! Array node element.
  TYPE(NodeElement), ALLOCATABLE :: d(:)
  
  TYPE(ParentNode) :: e             ! Scalar parent node.
  TYPE(ParentNode) :: f             ! Scalar parent node.
  
  a = EmptyNode()                   ! Ok.
  b = IntegerNode(I=1)              ! Ok.
  c = NodeElement(EmptyNode())      ! Ok.
  d = [ NodeElement(EmptyNode()) ]  ! Ok.
  e = ParentNode(d)                 ! Ok
  
  ! But this is not ok!  And I have checked the source oh so many times...
  f = ParentNode( [ NodeElement(EmptyNode()) ] )
  
  ! Get explicit about component names.  Still not ok!
  f = ParentNode( CHILDREN=[ NodeElement(ITEM=EmptyNode()) ] )
END PROGRAM p

I think I'm being good with the above (with a niggling thought that maybe something here is not F2003 but ok F2008), but ifort 15.0 doesn't like it.

>ifort /check:all /warn:all /standard-semantics /stand StructureConstructorSyntax.f90
Intel(R) Visual Fortran Compiler XE for applications running on IA-32, Version 15.0.0.108 Build 20140726
Copyright (C) 1985-2014 Intel Corporation.  All rights reserved.

StructureConstructorSyntax.f90(50): error #6593: The number of expressions in a structure constructor differs from the number of components of the derived type.   [PARENTNODE]
  f = ParentNode( [ NodeElement(EmptyNode()) ] )
------^
compilation aborted for StructureConstructorSyntax.f90 (code 1)

 

0 Kudos
1 Reply
FortranFan
Honored Contributor III
491 Views

This appears to be an Intel Fortran compiler bug with the use of array constructor syntax in derived type constructors.

gfortran 5.0 doesn't have the capability to do type conversions involving polymorphic components in derived type constructors, so the original code can't be tried out.  But gfortran accepts the following code just fine:

    ...

  ! A concrete incarnation of the parent.
  TYPE, EXTENDS(Node) :: ConcreteNode
  END TYPE ConcreteNode

  TYPE :: NodeElement
    TYPE(ConcreteNode), ALLOCATABLE :: item
  END TYPE NodeElement

    ...

  f = ParentNode( [ NodeElement(ConcreteNode()) ] )

    ...

 

0 Kudos
Reply