OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [deferred_type_param_2.f90] - Blame information for rev 720

Go to most recent revision | Details | Compare with Previous | View Log

Line No. Rev Author Line
1 694 jeremybenn
! { dg-do compile }
2
! { dg-options "-std=f2008" }
3
!
4
! PR fortran/45170
5
!
6
! Character deferred type parameter
7
!
8
 
9
subroutine one(x, y) ! { dg-error "Entity .y. at .1. has a deferred type parameter" }
10
  implicit none
11
  character(len=:), pointer :: x
12
  character(len=:) :: y
13
  character(len=:), allocatable, target :: str2
14
  character(len=:), target :: str ! { dg-error "deferred type parameter" }
15
end subroutine one
16
 
17
subroutine two()
18
  implicit none
19
  character(len=:), allocatable, target :: str1(:)
20
  character(len=5), save, target :: str2
21
  character(len=:), pointer :: pstr => str2
22
  character(len=:), pointer :: pstr2(:)
23
end subroutine two
24
 
25
subroutine three()
26
!  implicit none  ! Disabled because of PR 46152
27
  character(len=:), allocatable, target :: str1(:)
28
  character(len=5), save, target :: str2
29
  character(len=:), pointer :: pstr
30
  character(len=:), pointer :: pstr2(:)
31
 
32
  pstr => str2
33
  pstr2 => str1
34
  str1 = ["abc"]
35
  pstr2 => str1
36
 
37
  allocate (character(len=77) :: str1(1))
38
  allocate (pstr, source=str2)
39
  allocate (pstr, mold=str2)
40
  allocate (pstr) ! { dg-error "requires either a type-spec or SOURCE tag" }
41
  allocate (character(len=:) :: str1(1)) ! { dg-error "cannot contain a deferred type parameter" }
42
 
43
  str1 = [ character(len=2) :: "abc" ]
44
  str1 = [ character(len=:) :: "abc" ] ! { dg-error "cannot contain a deferred type parameter" }
45
end subroutine three
46
 
47
subroutine four()
48
  implicit none
49
  character(len=:), allocatable, target :: str
50
  character(len=:), pointer :: pstr
51
  pstr => str
52
  str = "abc"
53
  if(len(pstr) /= len(str) .or. len(str)/= 3) call abort()
54
  str = "abcd"
55
  if(len(pstr) /= len(str) .or. len(str)/= 4) call abort()
56
end subroutine four
57
 
58
subroutine five()
59
character(len=4) :: str*(:)
60
allocatable :: str
61
end subroutine five
62
 

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.