lto: Remove random_seed from section name.
[official-gcc.git] / gcc / testsuite / gfortran.dg / module_write_1.f90
blob0613c92e161834316e2b8c85328e09e4184f4da9
1 ! { dg-do compile }
3 ! PR fortran/41869
5 ! Was ICEing while module write of symbol 'vs_str' in m_dom_dom
6 ! because of "len" being private in fox_m_fsys_format.
8 module fox_m_fsys_array_str
9 contains
10 pure function str_vs(vs) result(s)
11 character, dimension(:), intent(in) :: vs
12 character(len=size(vs)) :: s
13 s = transfer(vs, s)
14 end function str_vs
15 pure function vs_str(s) result(vs)
16 character(len=*), intent(in) :: s
17 character, dimension(len(s)) :: vs
18 vs = transfer(s, vs)
19 end function vs_str
20 end module fox_m_fsys_array_str
22 module fox_m_fsys_format
23 private
24 interface str
25 module procedure str_logical_array
26 end interface str
27 interface len
28 module procedure str_logical_array_len
29 end interface
30 public :: str
31 contains
32 pure function str_logical_array_len(la) result(n)
33 logical, dimension(:), intent(in) :: la
34 end function str_logical_array_len
35 pure function str_logical_array(la) result(s)
36 logical, dimension(:), intent(in) :: la
37 character(len=len(la)) :: s
38 end function str_logical_array
39 pure function checkFmt(fmt) result(good)
40 character(len=*), intent(in) :: fmt
41 logical :: good
42 good = len(fmt) > 0
43 end function checkFmt
44 end module fox_m_fsys_format
46 module m_dom_dom
47 use fox_m_fsys_array_str, only: str_vs, vs_str
48 end module m_dom_dom
50 module FoX_dom
51 use fox_m_fsys_format
52 use m_dom_dom
53 end module FoX_dom
55 use FoX_dom
56 implicit none
57 print *, vs_str("ABC")
58 end