aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/ichar_1.f90
blob: 362cd2f453bdb702ed590d1ce57d3226bd081a45 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
! { dg-do compile }
! { dg-options "-std=legacy" }
!
! PR20879
! Check that we reject expressions longer than one character for the
! ICHAR and IACHAR intrinsics.

! Assumed length variables are special because the frontend doesn't have
! an expression for their length
subroutine test (c)
  character(len=*) :: c
  integer i
  i = ichar(c)
  i = ichar(c(2:))
  i = ichar(c(:1))
end subroutine

program ichar_1
   type derivedtype
      character(len=4) :: addr
   end type derivedtype

   type derivedtype1
      character(len=1) :: addr
   end type derivedtype1

   integer i
   integer, parameter :: j = 2
   character(len=8) :: c = 'abcd'
   character(len=1) :: g1(2)
   character(len=1) :: g2(2,2)
   character*1, parameter :: s1 = 'e'
   character*2, parameter :: s2 = 'ef'
   type(derivedtype) :: dt
   type(derivedtype1) :: dt1

   if (ichar(c(3:3)) /= 97) call abort
   if (ichar(c(:1)) /= 97) call abort
   if (ichar(c(j:j)) /= 98) call abort
   if (ichar(s1) /= 101) call abort
   if (ichar('f') /= 102) call abort
   g1(1) = 'a'
   if (ichar(g1(1)) /= 97) call abort
   if (ichar(g1(1)(:)) /= 97) call abort
   g2(1,1) = 'a'
   if (ichar(g2(1,1)) /= 97) call abort

   i = ichar(c)      ! { dg-error "must be of length one" "" }
   i = ichar(c(:))   ! { dg-error "must be of length one" "" }
   i = ichar(s2)     ! { dg-error "must be of length one" "" }
   i = ichar(c(1:2)) ! { dg-error "must be of length one" "" }
   i = ichar(c(1:))  ! { dg-error "must be of length one" "" }
   i = ichar('abc')  ! { dg-error "must be of length one" "" }

   ! ichar and iachar use the same checking routines. DO a couple of tests to
   ! make sure it's not totally broken.

   if (ichar(c(3:3)) /= 97) call abort
   i = ichar(c)      ! { dg-error "must be of length one" "" }
   
   i = ichar(dt%addr(1:1))
   i = ichar(dt%addr) ! { dg-error "must be of length one" "" }
   i = ichar(dt%addr(1:2)) ! { dg-error "must be of length one" "" }
   i = ichar(dt%addr(1:)) ! { dg-error "must be of length one" "" }
   
   i = ichar(dt1%addr(1:1))
   i = ichar(dt1%addr)


   call test(g1(1))
end program ichar_1