view gcc/testsuite/gfortran.dg/pr62135.f90 @ 118:fd00160c1b76

ifdef TARGET_64BIT
author mir3636
date Tue, 27 Feb 2018 15:01:35 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do compile }
! { dg-options -Wsurprising }

   PROGRAM PR62135
      IMPLICIT NONE
      CHARACTER*1 :: choice
      choice = 'x'
      SELECT CASE (choice)
         ! This triggered an ICE: an unreachable case clause
         ! as the last of a list.
         CASE ('2':'7','9':'0') ! { dg-warning "can never be matched" }
            WRITE(*,*) "barf"
         CASE DEFAULT
            CONTINUE
      END SELECT
   END PROGRAM PR62135