File: realloc_on_assign_28.f90

package info (click to toggle)
gcc-arm-none-eabi 15%3A12.2.rel1-1
  • links: PTS, VCS
  • area: main
  • in suites: bookworm
  • size: 959,712 kB
  • sloc: cpp: 3,275,382; ansic: 2,061,766; ada: 840,956; f90: 208,513; makefile: 76,132; asm: 73,433; xml: 50,448; exp: 34,146; sh: 32,436; objc: 15,637; fortran: 14,012; python: 11,991; pascal: 6,787; awk: 4,779; perl: 3,054; yacc: 338; ml: 285; lex: 201; haskell: 122
file content (40 lines) | stat: -rw-r--r-- 905 bytes parent folder | download | duplicates (3)
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
! { dg-do run }
!
! PR fortran/66102
!
! Contributed by Vladimir Fuka  <vladimir.fuka@gmail.com>
!
  type t
    integer,allocatable :: i
  end type

  type(t) :: e
  type(t), allocatable, dimension(:) :: a, b
  integer :: chksum = 0

  do i=1,3   ! Was 100 in original
    e%i = i
    chksum = chksum + i
    if (.not.allocated(a)) then
      a = [e]
      b = first_arg([e], [e])
    else
      call foo
    end if
  end do

  if (sum ([(a(i)%i, i=1,size(a))]) .ne. chksum) STOP 1
  if (any([(a(i)%i, i=1,size(a))] /= [(i, i=1,size(a))])) STOP 2
  if (size(a) /= size(b)) STOP 3
  if (any([(b(i)%i, i=1,size(b))] /= [(i, i=1,size(b))])) STOP 4
contains
  subroutine foo
    b = first_arg([b, e], [a, e])
    a = [a, e]
  end subroutine
  elemental function first_arg(arg1, arg2)
    type(t), intent(in) :: arg1, arg2
    type(t)             :: first_arg
    first_arg = arg1
  end function first_arg
end