Mercurial > hg > CbC > CbC_gcc
diff gcc/testsuite/gfortran.dg/public_private_module_2.f90 @ 111:04ced10e8804
gcc 7
author | kono |
---|---|
date | Fri, 27 Oct 2017 22:46:09 +0900 |
parents | |
children |
line wrap: on
line diff
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/gcc/testsuite/gfortran.dg/public_private_module_2.f90 Fri Oct 27 22:46:09 2017 +0900 @@ -0,0 +1,74 @@ +! { dg-do compile } +! { dg-options "-O2" } +! { dg-require-visibility "" } +! +! 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 + +! The two xfails below have appeared with the introduction of submodules. 'iii' and +! 'mmm' now are TREE_PUBLIC but has DECL_VISIBILITY (decl) = VISIBILITY_HIDDEN set. + + ! { dg-final { scan-assembler "__mod_MOD_aa" } } + ! { dg-final { scan-assembler-not "iii" { xfail *-*-* } } } + ! { dg-final { scan-assembler "jj" } } + ! { dg-final { scan-assembler "lll" } } + ! { dg-final { scan-assembler-not "kk" } } + ! { dg-final { scan-assembler-not "mmmm" { xfail *-*-* } } } + ! { 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" } }