aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/public_private_module_2.f90
blob: aa6b9fc726896c4eeb909321f8f5ab0f4bb81d58 (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
! { dg-do compile }
! { dg-options "-O2" }
!
! PR fortran/52751 (top, "module mod")
! PR fortran/40973 (bottom, "module m"
!
! Ensure that (only) those module variables and procedures which are PRIVATE
! and have no C-binding label are optimized away.
!
      module mod
        integer :: aa
        integer, private :: iii
        integer, private, bind(C) :: jj             ! { dg-warning "PRIVATE but has been given the binding label" }
        integer, private, bind(C,name='lll') :: kk  ! { dg-warning "PRIVATE but has been given the binding label" }
        integer, private, bind(C,name='') :: mmmm
        integer, bind(C) :: nnn
        integer, bind(C,name='oo') :: pp
        integer, bind(C,name='') :: qq
      end module mod

      ! { dg-final { scan-assembler "__mod_MOD_aa" } }
      ! { dg-final { scan-assembler-not "iii" } }
      ! { dg-final { scan-assembler "jj" } }
      ! { dg-final { scan-assembler "lll" } }
      ! { dg-final { scan-assembler-not "kk" } }
      ! { dg-final { scan-assembler-not "mmmm" } }
      ! { dg-final { scan-assembler "nnn" } }
      ! { dg-final { scan-assembler "oo" } }
      ! { dg-final { scan-assembler "__mod_MOD_qq" } }

MODULE M
  PRIVATE :: two, three, four, six
  PUBLIC :: one, seven, eight, ten
CONTAINS
  SUBROUTINE one(a)
    integer :: a
    a = two()
  END SUBROUTINE one
  integer FUNCTION two()
     two = 42
  END FUNCTION two
  integer FUNCTION three() bind(C) ! { dg-warning "PRIVATE but has been given the binding label" }
     three = 43
  END FUNCTION three
  integer FUNCTION four() bind(C, name='five') ! { dg-warning "PRIVATE but has been given the binding label" }
     four = 44
  END FUNCTION four
  integer FUNCTION six() bind(C, name='')
     six = 46
  END FUNCTION six
  integer FUNCTION seven() bind(C)
     seven = 46
  END FUNCTION seven
  integer FUNCTION eight() bind(C, name='nine')
     eight = 48
  END FUNCTION eight
  integer FUNCTION ten() bind(C, name='')
     ten = 48
  END FUNCTION ten
END MODULE

! { dg-final { scan-assembler "__m_MOD_one" } }
! { dg-final { scan-assembler-not "two" } }
! { dg-final { scan-assembler "three" } }
! { dg-final { scan-assembler-not "four" } }
! { dg-final { scan-assembler "five" } }
! { dg-final { scan-assembler-not "six" } }
! { dg-final { scan-assembler "seven" } }
! { dg-final { scan-assembler "nine" } }
! { dg-final { scan-assembler "__m_MOD_ten" } }