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.

Namelist and length type parameters

IanH
Honored Contributor III
373 Views

When it comes to namelist, I certainly don't know what I am doing.  But at least the compiler is with me in being confused.

PROGRAM p20151006_namelist
  IMPLICIT NONE
  TYPE :: t(len)
    INTEGER, LEN :: len
    REAL :: array(len)
  END TYPE t
  TYPE(t(:)), ALLOCATABLE :: a
  NAMELIST /nml/ a
  INTEGER, PARAMETER :: unit = 10
  CHARACTER(*), PARAMETER :: len_fmt = "(I10)"
  CHARACTER(*), PARAMETER :: filename = '2015-10-06 namelist.txt'
  INTEGER :: l
  
  ALLOCATE(t(5) :: a)
  a%array = [(REAL(l), l = 1, a%len)]
  PRINT "(I10,*(F4.1,:,1X))", a%len, a
  
  OPEN(unit, FILE=filename, ACTION='WRITE', STATUS='REPLACE')
  WRITE (unit, len_fmt) a%len
  WRITE (unit, nml)
  CLOSE(unit)
  
  DEALLOCATE(a)
  
  OPEN(unit, FILE=filename, ACTION='READ', STATUS='OLD', POSITION='REWIND')
  READ(unit, len_fmt) l
  ALLOCATE(t(l) :: a)
  READ (unit, nml)
  CLOSE(unit)
  
  PRINT "(I10,*(F4.1,:,1X))", a%len, a
END PROGRAM p20151006_namelist

 

>ifort /check:all /warn:all /standard-semantics /stand:f08 "2015-10-06 namelist.f90"
Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(R) 64, Version 16.0 Build 20150815
Copyright (C) 1985-2015 Intel Corporation.  All rights reserved.

0_1855

U:\projects\FortranMisc\2015\2015-10-06 namelist.f90(20): catastrophic error: **Internal compiler error: internal abort*
* Please report this error along with the circumstances in which it occurred in a Software Problem Report.  Note: File and line given may not be explicit cause of this error.
compilation aborted for 2015-10-06 namelist.f90 (code 1)

 

This variant, where the value of the derived type parameter is set by specification, compiles, but I am suspicious of the namelist output (and the PRINT statement output to the console?) - there are entries for the length parameter, noting that length parameters are not components. Plus the array values in the namelist output are bonkers.
 

PROGRAM p20151006_namelist2
  IMPLICIT NONE
  TYPE :: t(len)
    INTEGER, LEN :: len
    REAL :: array(len)
  END TYPE t
  CALL execute
CONTAINS
  SUBROUTINE execute
    TYPE(t(:)), ALLOCATABLE :: a
    INTEGER, PARAMETER :: unit = 10
    CHARACTER(*), PARAMETER :: len_fmt = "(I10)"
    CHARACTER(*), PARAMETER :: filename = '2015-10-06 namelist2.txt'
    INTEGER :: l
    ALLOCATE(t(5) :: a)
    a%array = [(REAL(l), l = 1, a%len)]
    PRINT "(I10,*(F4.1,:,1X))", a%len, a
    
    OPEN(unit, FILE=filename, ACTION='WRITE', STATUS='REPLACE')
    WRITE (unit, len_fmt) a%len
    CALL write(unit, a%len, a)
    CLOSE(unit)
    
    DEALLOCATE(a)
    
!    OPEN(unit, FILE=filename, ACTION='READ', STATUS='OLD', POSITION='REWIND')
!    READ(unit, len_fmt) l
!    ALLOCATE(t(l) :: a)
!    CLOSE(unit)
    
!    PRINT "(I10,*(F4.1,:,1X))", a%len, a
  END SUBROUTINE execute
  
  SUBROUTINE read(unit, l, a)
    INTEGER, INTENT(IN) :: unit
    INTEGER, INTENT(IN) :: l
    TYPE(t(l)), INTENT(OUT) :: a
    NAMELIST /nml/ a
    READ (unit, nml)
  END SUBROUTINE read
  
  SUBROUTINE write(unit, l, a)
    INTEGER, INTENT(IN) :: unit
    INTEGER, INTENT(IN) :: l
    TYPE(t(l)), INTENT(IN) :: a
    NAMELIST /nml/ a
    WRITE (unit, nml)
  END SUBROUTINE write
END PROGRAM p20151006_namelist2

 

>ifort /check:all /warn:all /standard-semantics /stand:f08 "2015-10-06 namelist2.f90" && "2015-10-06 namelist2.exe" && type "2015-10-06 namelist2.txt"
Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(R) 64, Version 16.0 Build 20150815
Copyright (C) 1985-2015 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 10.00.40219.01
Copyright (C) Microsoft Corporation.  All rights reserved.

"-out:2015-10-06 namelist2.exe"
-subsystem:console
"2015-10-06 namelist2.obj"
         5 1.0  2.0  3.0  4.0  5.0
         5
 &NML
 A%LEN     = 5,
 A%ARRAY   = 2.9511794E-39  , 0.000000       , 5.6051939E-45  , 2*0.000000
 /

 

0 Kudos
1 Reply
Kevin_D_Intel
Employee
373 Views

Thank you IanH for reporting the issues.

Updated 11/19/2015: Submitted to Development

(Internal tracking id: DPD200378942 - internal error w/Namelist and length type parameters)
(Internal tracking id: DPD200378943 - incorrect results w/Namelist and length type parameters)

0 Kudos
Reply