IBM Support

IV13925: INTERNAL COMPILER ERROR WITH -O3 AND -QREPORT

Subscribe

You can track all active APARs for this component.

 

APAR status

  • Closed as program error.

Error description

  • When compiling the following test case with -O3 and -qreport,
    the compiler ICEs in IPA.
    
    ===== COMPILE COMMAND:
    xlf95_r -O3 -qreport -c mo_mvstream_test.f90
    
    $cat mo_mvstream_test.f90
    MODULE mo_mvstream
    
    
    !---------------------------------------------------------------
    -----------
      !
      ! Module that allows to open an extra redoubled stream for
    some tracers
      ! or elements of any other stream (3d or 2d grid point fields)
      ! in order to calculate for example the mean values over a
    certain interval
      ! -----------------------------------------
      !
      ! Authors:
      !  J.S. Rast, MPI-Met, Hamburg, December 2003, original source
      !  P. Stier,  MPI-Met, Hamburg,          2004, modifications
      !  J.S. Rast, MPI-Met, Hamburg, June     2004, optimisation
    
    !---------------------------------------------------------------
    -----------
    
      IMPLICIT NONE
    
      PRIVATE
    
      PUBLIC                    :: mvstream_accumulate
    
      INTEGER, PARAMETER :: dp = SELECTED_REAL_KIND(12,307)
      INTEGER,PARAMETER :: maxstr   = 50    ! max number of output
    streams
      REAL(dp)           :: delta_time    = 2400.0_dp ! distance of
    adjacent times
    
      INTEGER, PARAMETER        :: nam_max=500
    
      LOGICAL                   :: lvarmean(nam_max, maxstr), &
                                   lvarsurf(nam_max, maxstr), &
                                   lstddev(nam_max, maxstr)
      CHARACTER(len=256)        :: m_stream_name(maxstr)
      INTEGER                   :: nmstream,nlist_elements(maxstr)
    
      TYPE vptr
         REAL(dp), POINTER      :: ptr3d(:,:,:)
         REAL(dp), POINTER      :: ptr3d_s(:,:,:)
         REAL(dp), POINTER      :: ptr2d(:,:)
         REAL(dp), POINTER      :: ptr2d_s(:,:)
      END TYPE vptr
    
      TYPE tptr
         REAL(dp), POINTER      :: ptt3d(:,:,:)
         REAL(dp), POINTER      :: ptt2d(:,:)
       END TYPE tptr
    
      TYPE(vptr)                :: varptr(nam_max, maxstr)
    
      TYPE(tptr)                :: tarptr(nam_max, maxstr)
    
    CONTAINS
    
      !>
      !! Accumulate values for all source streams besides tracer.
      !!
      subroutine mvstream_accumulate
        integer :: kstream, kvar
    
        do kstream = 1, nmstream; if (m_stream_name(kstream) /=
    'tracer') then
            ! Check elements from all non-tracer streams.
            do kvar = 1, nlist_elements(kstream); if (lvarmean(kvar,
    kstream)) then
                ! Only variables that are scheduled for averaging.
                if (lvarsurf(kvar,kstream)) then
                    ! For two-dimensional variables, add current
    value.
                    varptr(kvar,kstream)%ptr2d = &
                        varptr(kvar,kstream)%ptr2d + &
                        tarptr(kvar,kstream)%ptt2d * delta_time
                    if (lstddev(kvar,kstream)) then
                        ! Add square of current value to standard
    deviation.
                        varptr(kvar,kstream)%ptr2d_s = &
                            varptr(kvar,kstream)%ptr2d_s + &
                            tarptr(kvar,kstream)%ptt2d *
    tarptr(kvar,kstream)%ptt2d * &
                            delta_time
                    end if! lstddev
                else! lvarsurf
                    ! For three-dimensional variables, add current
    value.
                    varptr(kvar,kstream)%ptr3d = &
                        varptr(kvar,kstream)%ptr3d + &
                        tarptr(kvar,kstream)%ptt3d * delta_time
                    if (lstddev(kvar,kstream)) then
                        ! Add square of current value to standard
    deviation.
                        varptr(kvar,kstream)%ptr3d_s = &
                            varptr(kvar,kstream)%ptr3d_s + &
                            tarptr(kvar,kstream)%ptt3d *
    tarptr(kvar,kstream)%ptt3d * &
                            delta_time
                    end if! lstddev
                end if! else lvarsurf
            end if; end do! kvar|lvarmean
        end if; end do! kstream|m_stream_name /= 'tracer'
      end subroutine mvstream_accumulate
    
    END MODULE mo_mvstream
    $
    
    
    ===== ACTUAL OUTPUT:
    $xlf95_r -O3 -qreport -c mo_mvstream_test.f90
    ** mo_mvstream   === End of Compilation 1 ===
    Calling signal handler...
    1586-494 (U) INTERNAL COMPILER ERROR: Signal 11.
    /usr/bin/.orig/xlf95_r: 1501-230 (S) Internal compiler error;
    please contact your Service Representative. For more information
    visit:
    http://www.ibm.com/support/docview.wss?uid=swg21110810
    1501-511  Compilation failed for file mo_mvstream_test.f90.
    $
    
    
    
    ===== EXPECTED OUTPUT:
    Should compile cleanly
    

Local fix

  • n/a
    

Problem summary

  • USERS AFFECTED:
    Users of TPO with -O3 and above may be affected by this issue.
    
    PROBLEM DESCRIPTION:
    The compiler generates an internal compiler error with -O3 and
    -qreport in certain cases.
    

Problem conclusion

  • Huge expressions are causing the report generator to overflow a
    fixed size buffer.
    This causes things to be clobbered. The solution was to
    increase the size of these buffers.
    

Temporary fix

Comments

APAR Information

  • APAR number

    IV13925

  • Reported component name

    XL FORTRAN FOR

  • Reported component ID

    5724X1500

  • Reported release

    D10

  • Status

    CLOSED PER

  • PE

    NoPE

  • HIPER

    NoHIPER

  • Special Attention

    NoSpecatt

  • Submitted date

    2012-01-24

  • Closed date

    2012-03-28

  • Last modified date

    2012-03-28

  • APAR is sysrouted FROM one or more of the following:

  • APAR is sysrouted TO one or more of the following:

    LI76800

Fix information

  • Fixed component name

    XL FORTRAN FOR

  • Fixed component ID

    5724X1500

Applicable component levels

  • RD10 PSY U850834

       UP C

[{"Business Unit":{"code":"BU058","label":"IBM Infrastructure w\/TPS"},"Product":{"code":"SSGH4D","label":"XL Fortran for AIX"},"Component":"","ARM Category":[],"Platform":[{"code":"PF025","label":"Platform Independent"}],"Version":"13.1","Edition":"","Line of Business":{"code":"LOB57","label":"Power"}}]

Document Information

Modified date:
28 March 2012