Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
Announcements
FPGA community forums and blogs on community.intel.com are migrating to the new Altera Community and are read-only. For urgent support needs during this transition, please visit the FPGA Design Resources page or contact an Altera Authorized Distributor.

Overloaded structure constructors get distracted by abstract

IanH
Honored Contributor III
491 Views

I think this has been around for a little while, but the new version prompted me to flush it out.

MODULE MA
  IMPLICIT NONE
  PRIVATE
  PUBLIC :: t
  TYPE :: t
    INTEGER :: comp
  END TYPE t
  INTERFACE t
    MODULE PROCEDURE Make_t
  END INTERFACE t
CONTAINS
  FUNCTION Make_t(arg)
    REAL, INTENT(IN) :: arg
    TYPE(t) :: Make_t
    Make_t%comp = NINT(arg)
  END FUNCTION Make_t
END MODULE MA

PROGRAM PB
  USE MA
  IMPLICIT NONE
  ABSTRACT INTERFACE
    SUBROUTINE s
      USE MA      ! #A comment me out and all is well.
    END SUBROUTINE s
  END INTERFACE
CONTAINS
  SUBROUTINE internal_or_module
    ! USE MA      ! #B comment me in and all is well.
    TYPE(t) :: a
  END SUBROUTINE internal_or_module
END PROGRAM PB

 

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

DistractedByAbstract.f90(30): error #6463: This is not a derived type name.   
    TYPE(t) :: a
---------^
compilation aborted for DistractedByAbstract.f90 (code 1)

 

0 Kudos
1 Reply
IanH
Honored Contributor III
491 Views

A different variant, with no interface block, that perhaps looks a bit like the one recently reported on the linux forum.  If either line marked #A is commented out then the error messages go away.

MODULE CmdLine
  IMPLICIT NONE
  PRIVATE
  !-----------------------------------------------------------------------------
  PUBLIC :: CmdLineOption
  !-----------------------------------------------------------------------------
  TYPE :: CmdLineOption
    CHARACTER(:), ALLOCATABLE :: LongName
  END TYPE CmdLineOption
  
  INTERFACE CmdLineOption
    MODULE PROCEDURE CmdLineOption_all
  END INTERFACE CmdLineOption
CONTAINS
  PURE FUNCTION CmdLineOption_all(long_name) RESULT(clo)
    CHARACTER(*), INTENT(IN), OPTIONAL :: long_name
    ! Function result
    TYPE(CmdLineOption) :: clo
    !***************************************************************************
    IF (PRESENT(long_name))     clo%LongName = long_name
  END FUNCTION CmdLineOption_all
END MODULE CmdLine

MODULE ContexterTestImplementation
  IMPLICIT NONE
  PRIVATE
  PUBLIC :: UsageMessage
CONTAINS
  SUBROUTINE UsageMessage(cmd_line_options)
    USE CmdLine
    !---------------------------------------------------------------------------
    TYPE(CmdLineOption), INTENT(IN) :: cmd_line_options(:)
    if (size(cmd_line_options) /= 0) continue  ! Just to get rid of warning.
  END SUBROUTINE UsageMessage
END MODULE ContexterTestImplementation

PROGRAM ContexterTest
  USE CmdLine
  USE ContexterTestImplementation                             ! #A
  IMPLICIT NONE
  !-----------------------------------------------------------------------------
  TYPE(CmdLineOption) :: cmd_line_options(1)
  !*****************************************************************************
  cmd_line_options(1) = CmdLineOption(LONG_NAME='help')
  CALL UsageMessage(cmd_line_options)                         ! #A
END PROGRAM ContexterTest

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

ContexterTest.f90(42): error #6463: This is not a derived type name.   [CMDLINEOPTION]
  TYPE(CmdLineOption) :: cmd_line_options(1)
-------^
ContexterTest.f90(44): error #6404: This name does not have a type, and must have an explicit type.   [CMD_LINE_OPTIONS]
  cmd_line_options(1) = CmdLineOption(LONG_NAME='help')
--^
ContexterTest.f90(44): error #8213: A keyword in the structure constructor is not the name of a type component.   [LONG_NAME]
  cmd_line_options(1) = CmdLineOption(LONG_NAME='help')
--------------------------------------^
compilation aborted for ContexterTest.f90 (code 1)

So apparently its not a derived type name, but it is a structure constructor.  Cake, have, eat too.

Edit to note that a workaround appears to be to rename the type (and then use that new name) in the use statement of the main program.

0 Kudos
Reply