view gcc/testsuite/gfortran.dg/pr44882.f90 @ 127:4c56639505ff

fix function.c and add CbC-example Makefile
author mir3636
date Wed, 11 Apr 2018 18:46:58 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do compile }
! { dg-options "-O3 -ffast-math -funroll-loops -w" }

      SUBROUTINE TRUDGE(KDIR)
! There is a type mismatch here for TRUPAR which caused an ICE
      COMMON /TRUPAR/ DR(10),V(10,10)
      DO 110 I=1,NDIR
  110 DR(I)=V(I,JDIR)
      END
      SUBROUTINE TRUSRC(LEAVE)
      IMPLICIT DOUBLE PRECISION (A-H,O-Z)
      COMMON /TRUPAR/ DX(10),V(10,10)
      END