view gcc/testsuite/gfortran.dg/storage_size_4.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 84e7813d76e9
line wrap: on
line source

! { dg-do compile }
! { dg-options "-fdump-tree-original" }
!
! PR fortran/57553
!
! Ensure that there is no ICE and that compile-time simplication works.
!
  use iso_fortran_env
  implicit none
  integer, parameter :: ESize = storage_size('a')
  integer, parameter :: ESize2 = storage_size('aa')
  if ( ESize/CHARACTER_STORAGE_SIZE /= 1) call abort()
  if ( ESize2/CHARACTER_STORAGE_SIZE /= 2) call abort()
end

subroutine S ( A )
  character(len=*), intent(in) :: A
  integer :: ESize = 4
  esize = ( storage_size(a) + 7 ) / 8
end

! { dg-final { scan-tree-dump-not "abort" "original" } }