File: aliasing_dummy_1.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 (67 lines) | stat: -rw-r--r-- 1,915 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
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
! { dg-do run }
! { dg-options "-std=legacy" }
!
! This tests the fix for PR24276, which originated from the Loren P. Meissner example,
! Array_List.  The PR concerns dummy argument aliassing of components of arrays of derived
! types as arrays of the type of the component.  gfortran would compile and run this
! example but the stride used did not match the actual argument.  This test case exercises
! a procedure call (to foo2, below) that is identical to Array_List's.
!
! Contributed by Paul Thomas  <pault@gcc.gnu.org>

program test_lex
  type :: dtype
    integer :: n
    character*5 :: word
  end type dtype

  type :: list
    type(dtype), dimension(4) :: list
    integer :: l = 4
  end type list
 
  type(list) :: table
  type(dtype) :: elist(2,2)

  table%list = (/dtype (1 , "one  "), dtype (2 , "two  "), dtype (3 , "three"), dtype (4 , "four ")/)

! Test 1D with assumed shape (original bug) and assumed size.
  call bar (table, 2, 4)
  if (any (table%list%word.ne.(/"one  ","i=  2","three","i=  4"/))) STOP 1

  elist = reshape (table%list, (/2,2/))

! Check 2D is OK with assumed shape and assumed size.
  call foo3 (elist%word, 1)
  call foo1 (elist%word, 3)
  if (any (elist%word.ne.reshape ((/"i=  1","i=  2","i=  3","i=  4"/), (/2,2/)))) STOP 2

contains

  subroutine bar (table, n, m)
    type(list) :: table
    integer n, m
    call foo1 (table%list(:table%l)%word, n)
    call foo2 (table%list(:table%l)%word, m)
  end subroutine bar

  subroutine foo1 (slist, i)
    character(*), dimension(*) :: slist
    integer i
    write (slist(i), '(2hi=,i3)') i
  end subroutine foo1

  subroutine foo2 (slist, i)
    character(5), dimension(:) :: slist
    integer i
    write (slist(i), '(2hi=,i3)') i
  end subroutine foo2

  subroutine foo3 (slist, i)
    character(5), dimension(:,:) :: slist
    integer i
    write (slist(1,1), '(2hi=,i3)') i
  end subroutine foo3

end program test_lex