File: generic01.f90

package info (click to toggle)
swiftlang 6.0.3-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 2,519,992 kB
  • sloc: cpp: 9,107,863; ansic: 2,040,022; asm: 1,135,751; python: 296,500; objc: 82,456; f90: 60,502; lisp: 34,951; pascal: 19,946; sh: 18,133; perl: 7,482; ml: 4,937; javascript: 4,117; makefile: 3,840; awk: 3,535; xml: 914; fortran: 619; cs: 573; ruby: 573
file content (108 lines) | stat: -rw-r--r-- 2,410 bytes parent folder | download | duplicates (14)
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
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
! RUN: %flang_fc1 -fdebug-unparse %s 2>&1 | FileCheck %s
! Tests rules of 15.5.5.2 for generics and explicit intrinsics
! competing at various scoping levels.
module m1
  private
  public abs
  interface abs
    module procedure :: abs_int_redef, abs_noargs
  end interface
contains
  integer function abs_int_redef(j)
    integer, intent(in) :: j
    abs_int_redef = j
  end function
  integer function abs_noargs()
    abs_noargs = 0
  end function
end module

module m2
  private
  public abs
  interface abs
    module procedure abs_real_redef
  end interface
contains
  real function abs_real_redef(x)
    real, intent(in) :: x
    abs_real_redef = x
  end function
end module

module m3
  use m1, only: abs
  implicit none
contains
  subroutine test1
    use m2, only: abs
    !CHECK: abs_int_redef(
    print *, abs(1)
    !CHECK: abs_real_redef(
    print *, abs(1.)
    !CHECK: 1.41421353816986083984375_4
    print *, abs((1,1))
    !CHECK: abs_noargs(
    print *, abs()
  end subroutine
  subroutine test2
    intrinsic abs ! override some of module's use of m1
    block
      use m2, only: abs
      !CHECK: 1_4
      print *, abs(1)
      !CHECK: abs_real_redef(
      print *, abs(1.)
      !CHECK: 1.41421353816986083984375_4
      print *, abs((1,1))
      !CHECK: abs_noargs(
      print *, abs()
    end block
  end subroutine
  subroutine test3
    interface abs
      module procedure abs_complex_redef ! extend module's use of m1
    end interface
    !CHECK: abs_int_redef(
    print *, abs(1)
    !CHECK: 1._4
    print *, abs(1.)
    !CHECK: abs_complex_redef(
    print *, abs((1,1))
    !CHECK: abs_noargs(
    print *, abs()
    block
      intrinsic abs ! override the extension
      !CHECK: 1.41421353816986083984375_4
      print *, abs((1,1))
    end block
  end subroutine
  real function abs_complex_redef(z)
    complex, intent(in) :: z
    abs_complex_redef = z
  end function
  subroutine test4
    !CHECK: abs(
    print *, abs(1)
   contains
    integer function abs(n) ! override module's use of m1
      integer, intent(in) :: n
      abs = n
    end function
  end subroutine
end module

module m4
 contains
  integer function abs(n)
    integer, intent(in) :: n
    abs = n
  end function
  subroutine test5
    interface abs
      module procedure abs ! same name, host-associated
    end interface
    !CHECK: abs(
    print *, abs(1)
  end subroutine
end module