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

Internal compiler error - character(:) pointer in function declaration

Ernst_A__Meese
Beginner
750 Views

The program below gives an internal compiler error for ifort (IFORT) 14.0.3 20140422 under Linux.  It is the character(:) in front of function getS that triggers the error.  Moving character(:) to the pointer statement four lines below makes everything work ok.

MODULE testModule

  TYPE :: FOO
     CHARACTER(LEN=:), ALLOCATABLE :: s 
   CONTAINS
     PROCEDURE, PASS(this) :: getS
     PROCEDURE, PASS(this) :: setS
  END TYPE FOO

CONTAINS
 
  PURE SUBROUTINE setS( this, s )
    !
    CLASS(foo),   INTENT(inout) :: this
    CHARACTER(*), INTENT(in)    :: s

    IF( .NOT. ALLOCATED( this % s ) ) THEN
       ALLOCATE( this % s, SOURCE=s )
    ELSE IF ( LEN(this % s) /= LEN(s) ) THEN
       DEALLOCATE( this % s )
       ALLOCATE( this % s, SOURCE=s )
    ELSE
       this % s = s
    END IF

  END SUBROUTINE setS

  CHARACTER(:) FUNCTION getS( this ) RESULT( p )
    !
    CLASS(foo), INTENT(in), TARGET :: this
    !
    POINTER :: p

    p => this % s

  END FUNCTION getS

END MODULE testModule


PROGRAM testProgram

  USE testModule

  TYPE(foo),    TARGET  :: someFoo
  CHARACTER(:), POINTER :: stringInType

  CALL someFoo%setS( "The quick brown fox jumps over the lazy dog." )
  stringInType => someFoo%getS()
  PRINT '(A)', stringInType

END PROGRAM testProgram

0 Kudos
1 Reply
Kevin_D_Intel
Employee
750 Views

Thank you for the convenient reproducer. I can reproduce this using the CXE 2013 SP1 Update 3 you noted and using our upcoming release (currently in Beta testing) later this year. I reported this to Development (see internal tracking id below) and will keep you posted on a fix.

(Internal tracking id: DPD200358523)

0 Kudos
Reply