File: modproc01.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 (149 lines) | stat: -rw-r--r-- 9,118 bytes parent folder | download | duplicates (4)
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
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
!RUN: %flang_fc1 -fdebug-dump-symbols %s | FileCheck %s
module m
  type pdt1(k1,l1)
    integer, kind :: k1
    integer, len :: l1
    type(pdt2(k1,l1)), allocatable :: a1
  end type pdt1
  type pdt2(k2,l2)
    integer, kind :: k2
    integer, len :: l2
    integer(k2) :: j2
    type(pdt1(k2,l2)) :: a2(k2)
  end type pdt2
  interface
    module function mf(n,str,x1) result(res)
      integer, intent(in) :: n
      character(n), intent(in) :: str
      type(pdt1(1,n)), intent(in) :: x1
      type(pdt2(2,n)) :: res
    end function
    module subroutine ms(f)
      procedure(mf) :: f
    end subroutine
  end interface
end module
!CHECK:    mf, MODULE, PUBLIC (Function): Subprogram isInterface result:TYPE(pdt2(k2=2_4,l2=n)) res (INTEGER(4) n,CHARACTER(n,1) str,TYPE(pdt1(k1=1_4,l1=n)) x1)
!CHECK:    pdt1, PUBLIC: DerivedType components: a1
!CHECK:    pdt2, PUBLIC: DerivedType components: j2,a2
!CHECK:    sm: Module (m)
!CHECK:    DerivedType scope: pdt1
!CHECK:      a1, ALLOCATABLE: ObjectEntity type: TYPE(pdt2(int(k1,kind=4),int(l1,kind=4)))
!CHECK:      k1: TypeParam type:INTEGER(4) Kind
!CHECK:      l1: TypeParam type:INTEGER(4) Len
!CHECK:    DerivedType scope: pdt2
!CHECK:      a2: ObjectEntity type: TYPE(pdt1(k1=int(k2,kind=4),l1=int(l2,kind=4))) shape: 1_8:k2
!CHECK:      j2: ObjectEntity type: INTEGER(int(int(k2,kind=4),kind=8))
!CHECK:      k2: TypeParam type:INTEGER(4) Kind
!CHECK:      l2: TypeParam type:INTEGER(4) Len
!CHECK:    Subprogram scope: mf size=112 alignment=8
!CHECK:      mf (Function): HostAssoc
!CHECK:      n, INTENT(IN) size=4 offset=0: ObjectEntity dummy type: INTEGER(4)
!CHECK:      res size=40 offset=72: ObjectEntity funcResult type: TYPE(pdt2(k2=2_4,l2=n))
!CHECK:      str, INTENT(IN) size=24 offset=8: ObjectEntity dummy type: CHARACTER(n,1)
!CHECK:      x1, INTENT(IN) size=40 offset=32: ObjectEntity dummy type: TYPE(pdt1(k1=1_4,l1=n))
!CHECK:      DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=1_4,l1=n)
!CHECK:        a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=1_4,l2=int(l1,kind=4)))
!CHECK:        k1: TypeParam type:INTEGER(4) Kind init:1_4
!CHECK:        l1: TypeParam type:INTEGER(4) Len init:n
!CHECK:        DerivedType scope: size=72 alignment=8 instantiation of pdt2(k2=1_4,l2=int(l1,kind=4))
!CHECK:          a2 size=64 offset=8: ObjectEntity type: TYPE(pdt1(k1=1_4,l1=int(l2,kind=4))) shape: 1_8:1_8
!CHECK:          j2 size=1 offset=0: ObjectEntity type: INTEGER(1)
!CHECK:          k2: TypeParam type:INTEGER(4) Kind init:1_4
!CHECK:          l2: TypeParam type:INTEGER(4) Len init:int(l1,kind=4)
!CHECK:          DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=1_4,l1=int(l2,kind=4))
!CHECK:            a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=1_4,l2=int(l1,kind=4)))
!CHECK:            k1: TypeParam type:INTEGER(4) Kind init:1_4
!CHECK:            l1: TypeParam type:INTEGER(4) Len init:int(l2,kind=4)
!CHECK:      DerivedType scope: size=72 alignment=8 instantiation of pdt2(k2=2_4,l2=n)
!CHECK:        a2 size=64 offset=8: ObjectEntity type: TYPE(pdt1(k1=2_4,l1=int(l2,kind=4))) shape: 1_8:2_8
!CHECK:        j2 size=2 offset=0: ObjectEntity type: INTEGER(2)
!CHECK:        k2: TypeParam type:INTEGER(4) Kind init:2_4
!CHECK:        l2: TypeParam type:INTEGER(4) Len init:n
!CHECK:        DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=2_4,l1=int(l2,kind=4))
!CHECK:          a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=2_4,l2=int(l1,kind=4)))
!CHECK:          k1: TypeParam type:INTEGER(4) Kind init:2_4
!CHECK:          l1: TypeParam type:INTEGER(4) Len init:int(l2,kind=4)
!CHECK:          DerivedType scope: size=72 alignment=8 instantiation of pdt2(k2=2_4,l2=int(l1,kind=4))
!CHECK:            a2 size=64 offset=8: ObjectEntity type: TYPE(pdt1(k1=2_4,l1=int(l2,kind=4))) shape: 1_8:2_8
!CHECK:            j2 size=2 offset=0: ObjectEntity type: INTEGER(2)
!CHECK:            k2: TypeParam type:INTEGER(4) Kind init:2_4
!CHECK:            l2: TypeParam type:INTEGER(4) Len init:int(l1,kind=4)

submodule(m) sm
 contains
  module procedure mf
    print *, len(str), x1%k1, x1%l1, res%k2, res%l2
    allocate(res%a2(1)%a1)
    res%a2(1)%a1%j2 = 2
  end procedure
  module procedure ms
!    type(pdt2(2.3)) x
!    x = f(3, "abc", pdt1(1,3)())
  end procedure
end submodule
!CHECK:    Module scope: sm size=0 alignment=1
!CHECK:      mf, MODULE, PUBLIC (Function): Subprogram result:TYPE(pdt2(k2=2_4,l2=n)) res (INTEGER(4) n,CHARACTER(n,1) str,TYPE(pdt1(k1=1_4,l1=n)) x1) moduleInterface: mf, MODULE, PUBLIC (Function): Subprogram isInterface result:TYPE(pdt2(k2=2_4,l2=n)) res (INTEGER(4) n,CHARACTER(n,1) str,TYPE(pdt1(k1=1_4,l1=n)) x1)
!CHECK:      Subprogram scope: mf size=112 alignment=8
!CHECK:        len, INTRINSIC, PURE (Function): ProcEntity
!CHECK:        n, INTENT(IN) size=4 offset=0: ObjectEntity dummy type: INTEGER(4)
!CHECK:        res size=40 offset=72: ObjectEntity funcResult type: TYPE(pdt2(k2=2_4,l2=n))
!CHECK:        str, INTENT(IN) size=24 offset=8: ObjectEntity dummy type: CHARACTER(n,1)
!CHECK:        x1, INTENT(IN) size=40 offset=32: ObjectEntity dummy type: TYPE(pdt1(k1=1_4,l1=n))
!CHECK:        DerivedType scope: size=72 alignment=8 instantiation of pdt2(k2=2_4,l2=n)
!CHECK:          a2 size=64 offset=8: ObjectEntity type: TYPE(pdt1(k1=2_4,l1=int(l2,kind=4))) shape: 1_8:2_8
!CHECK:          j2 size=2 offset=0: ObjectEntity type: INTEGER(2)
!CHECK:          k2: TypeParam type:INTEGER(4) Kind init:2_4
!CHECK:          l2: TypeParam type:INTEGER(4) Len init:n
!CHECK:          DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=2_4,l1=int(l2,kind=4))
!CHECK:            a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=2_4,l2=int(l1,kind=4)))
!CHECK:            k1: TypeParam type:INTEGER(4) Kind init:2_4
!CHECK:            l1: TypeParam type:INTEGER(4) Len init:int(l2,kind=4)
!CHECK:            DerivedType scope: size=72 alignment=8 instantiation of pdt2(k2=2_4,l2=int(l1,kind=4))
!CHECK:              a2 size=64 offset=8: ObjectEntity type: TYPE(pdt1(k1=2_4,l1=int(l2,kind=4))) shape: 1_8:2_8
!CHECK:              j2 size=2 offset=0: ObjectEntity type: INTEGER(2)
!CHECK:              k2: TypeParam type:INTEGER(4) Kind init:2_4
!CHECK:              l2: TypeParam type:INTEGER(4) Len init:int(l1,kind=4)
!CHECK:        DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=1_4,l1=n)
!CHECK:          a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=1_4,l2=int(l1,kind=4)))
!CHECK:          k1: TypeParam type:INTEGER(4) Kind init:1_4
!CHECK:          l1: TypeParam type:INTEGER(4) Len init:n
!CHECK:          DerivedType scope: size=72 alignment=8 instantiation of pdt2(k2=1_4,l2=int(l1,kind=4))
!CHECK:            a2 size=64 offset=8: ObjectEntity type: TYPE(pdt1(k1=1_4,l1=int(l2,kind=4))) shape: 1_8:1_8
!CHECK:            j2 size=1 offset=0: ObjectEntity type: INTEGER(1)
!CHECK:            k2: TypeParam type:INTEGER(4) Kind init:1_4
!CHECK:            l2: TypeParam type:INTEGER(4) Len init:int(l1,kind=4)
!CHECK:            DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=1_4,l1=int(l2,kind=4))
!CHECK:              a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=1_4,l2=int(l1,kind=4)))
!CHECK:              k1: TypeParam type:INTEGER(4) Kind init:1_4
!CHECK:              l1: TypeParam type:INTEGER(4) Len init:int(l2,kind=4)

program test
  use m
  type(pdt2(2,3)) x
  x = mf(3, "abc", pdt1(1,3)())
!  call ms(mf)
end program
!CHECK:  MainProgram scope: test size=88 alignment=8
!CHECK:    mf, MODULE (Function): Use from mf in m
!CHECK:    pdt1: Use from pdt1 in m
!CHECK:    pdt2: Use from pdt2 in m
!CHECK:    x size=88 offset=0: ObjectEntity type: TYPE(pdt2(k2=2_4,l2=3_4))
!CHECK:    DerivedType scope: size=88 alignment=8 instantiation of pdt2(k2=2_4,l2=3_4)
!CHECK:      a2 size=80 offset=8: ObjectEntity type: TYPE(pdt1(k1=2_4,l1=3_4)) shape: 1_8:2_8
!CHECK:      j2 size=2 offset=0: ObjectEntity type: INTEGER(2)
!CHECK:      k2: TypeParam type:INTEGER(4) Kind init:2_4
!CHECK:      l2: TypeParam type:INTEGER(4) Len init:3_4
!CHECK:      DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=2_4,l1=3_4)
!CHECK:        a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=2_4,l2=3_4))
!CHECK:        k1: TypeParam type:INTEGER(4) Kind init:2_4
!CHECK:        l1: TypeParam type:INTEGER(4) Len init:3_4
!CHECK:    DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=1_4,l1=3_4)
!CHECK:      a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=1_4,l2=3_4))
!CHECK:      k1: TypeParam type:INTEGER(4) Kind init:1_4
!CHECK:      l1: TypeParam type:INTEGER(4) Len init:3_4
!CHECK:      DerivedType scope: size=1 alignment=1 instantiation of pdt2(k2=1_4,l2=3_4)
!CHECK:        a2: ObjectEntity type: TYPE(pdt1(k1=1_4,l1=3_4)) shape: 1_8:1_8
!CHECK:        j2 size=1 offset=0: ObjectEntity type: INTEGER(1)
!CHECK:        k2: TypeParam type:INTEGER(4) Kind init:1_4
!CHECK:        l2: TypeParam type:INTEGER(4) Len init:3_4