xref: /llvm-project/flang/test/Semantics/assign03.f90 (revision d9af9cf436ad1b892ecf8b794b0052135cc4029c)
16c1ac141SIvan Zhechev! RUN: %python %S/test_errors.py %s %flang_fc1
264ab3302SCarolineConcatto! Pointer assignment constraints 10.2.2.2 (see also assign02.f90)
364ab3302SCarolineConcatto
4*d9af9cf4SPeter Klauslermodule m0
5*d9af9cf4SPeter Klausler  procedure(),pointer,save :: p
6*d9af9cf4SPeter Klauslerend
7*d9af9cf4SPeter Klausler
864ab3302SCarolineConcattomodule m
964ab3302SCarolineConcatto  interface
1064ab3302SCarolineConcatto    subroutine s(i)
1164ab3302SCarolineConcatto      integer i
1264ab3302SCarolineConcatto    end
1364ab3302SCarolineConcatto  end interface
1464ab3302SCarolineConcatto  type :: t
1564ab3302SCarolineConcatto    procedure(s), pointer, nopass :: p
1664ab3302SCarolineConcatto    real, pointer :: q
1764ab3302SCarolineConcatto  end type
1864ab3302SCarolineConcattocontains
1964ab3302SCarolineConcatto  ! C1027
2064ab3302SCarolineConcatto  subroutine s1
2164ab3302SCarolineConcatto    type(t), allocatable :: a(:)
2264ab3302SCarolineConcatto    type(t), allocatable :: b[:]
2364ab3302SCarolineConcatto    a(1)%p => s
24573fc618SPeter Klausler    !ERROR: The left-hand side of a pointer assignment is not definable
25573fc618SPeter Klausler    !BECAUSE: Procedure pointer 'p' may not be a coindexed object
2664ab3302SCarolineConcatto    b[1]%p => s
2764ab3302SCarolineConcatto  end
2864ab3302SCarolineConcatto  ! C1028
2964ab3302SCarolineConcatto  subroutine s2
3064ab3302SCarolineConcatto    type(t) :: a
3164ab3302SCarolineConcatto    a%p => s
3264ab3302SCarolineConcatto    !ERROR: In assignment to object pointer 'q', the target 's' is a procedure designator
3364ab3302SCarolineConcatto    a%q => s
3464ab3302SCarolineConcatto  end
3564ab3302SCarolineConcatto  ! C1029
3664ab3302SCarolineConcatto  subroutine s3
3764ab3302SCarolineConcatto    type(t) :: a
3864ab3302SCarolineConcatto    a%p => f()  ! OK: pointer-valued function
3964ab3302SCarolineConcatto    !ERROR: Subroutine pointer 'p' may not be associated with function designator 'f'
4064ab3302SCarolineConcatto    a%p => f
4164ab3302SCarolineConcatto  contains
4264ab3302SCarolineConcatto    function f()
4364ab3302SCarolineConcatto      procedure(s), pointer :: f
4464ab3302SCarolineConcatto      f => s
4564ab3302SCarolineConcatto    end
4664ab3302SCarolineConcatto  end
4764ab3302SCarolineConcatto
4864ab3302SCarolineConcatto  ! C1030 and 10.2.2.4 - procedure names as target of procedure pointer
4964ab3302SCarolineConcatto  subroutine s4(s_dummy)
501e1a011bSPeter Steinfeld    procedure(s) :: s_dummy
5164ab3302SCarolineConcatto    procedure(s), pointer :: p, q
5264ab3302SCarolineConcatto    procedure(), pointer :: r
5364ab3302SCarolineConcatto    integer :: i
5464ab3302SCarolineConcatto    external :: s_external
5564ab3302SCarolineConcatto    p => s_dummy
5664ab3302SCarolineConcatto    p => s_internal
5764ab3302SCarolineConcatto    p => s_module
5864ab3302SCarolineConcatto    q => p
5964ab3302SCarolineConcatto    r => s_external
6064ab3302SCarolineConcatto  contains
6164ab3302SCarolineConcatto    subroutine s_internal(i)
6264ab3302SCarolineConcatto      integer i
6364ab3302SCarolineConcatto    end
6464ab3302SCarolineConcatto  end
6564ab3302SCarolineConcatto  subroutine s_module(i)
6664ab3302SCarolineConcatto    integer i
6764ab3302SCarolineConcatto  end
6864ab3302SCarolineConcatto
6964ab3302SCarolineConcatto  ! 10.2.2.4(3)
7064ab3302SCarolineConcatto  subroutine s5
71384b4e0dSEmil Kieri    procedure(f_impure1), pointer :: p_impure
72384b4e0dSEmil Kieri    procedure(f_pure1), pointer :: p_pure
7364ab3302SCarolineConcatto    !ERROR: Procedure pointer 'p_elemental' may not be ELEMENTAL
74384b4e0dSEmil Kieri    procedure(f_elemental1), pointer :: p_elemental
75384b4e0dSEmil Kieri    procedure(s_impure1), pointer :: sp_impure
76384b4e0dSEmil Kieri    procedure(s_pure1), pointer :: sp_pure
77384b4e0dSEmil Kieri    !ERROR: Procedure pointer 'sp_elemental' may not be ELEMENTAL
78384b4e0dSEmil Kieri    procedure(s_elemental1), pointer :: sp_elemental
79384b4e0dSEmil Kieri
80384b4e0dSEmil Kieri    p_impure => f_impure1 ! OK, same characteristics
81384b4e0dSEmil Kieri    p_impure => f_pure1 ! OK, target may be pure when pointer is not
8295f4ca7fSPeter Klausler    !ERROR: Procedure pointer 'p_impure' associated with incompatible procedure designator 'f_elemental1': incompatible procedure attributes: Elemental
8395f4ca7fSPeter Klausler    p_impure => f_elemental1
8495f4ca7fSPeter Klausler    !ERROR: Procedure pointer 'p_impure' associated with incompatible procedure designator 'f_impureelemental1': incompatible procedure attributes: Elemental
85384b4e0dSEmil Kieri    p_impure => f_ImpureElemental1 ! OK, target may be elemental
86384b4e0dSEmil Kieri
87384b4e0dSEmil Kieri    sp_impure => s_impure1 ! OK, same characteristics
88384b4e0dSEmil Kieri    sp_impure => s_pure1 ! OK, target may be pure when pointer is not
8995f4ca7fSPeter Klausler    !ERROR: Procedure pointer 'sp_impure' associated with incompatible procedure designator 's_elemental1': incompatible procedure attributes: Elemental
9095f4ca7fSPeter Klausler    sp_impure => s_elemental1
91384b4e0dSEmil Kieri
92384b4e0dSEmil Kieri    !ERROR: PURE procedure pointer 'p_pure' may not be associated with non-PURE procedure designator 'f_impure1'
93384b4e0dSEmil Kieri    p_pure => f_impure1
94384b4e0dSEmil Kieri    p_pure => f_pure1 ! OK, same characteristics
9595f4ca7fSPeter Klausler    !ERROR: Procedure pointer 'p_pure' associated with incompatible procedure designator 'f_elemental1': incompatible procedure attributes: Elemental
9695f4ca7fSPeter Klausler    p_pure => f_elemental1
97384b4e0dSEmil Kieri    !ERROR: PURE procedure pointer 'p_pure' may not be associated with non-PURE procedure designator 'f_impureelemental1'
98384b4e0dSEmil Kieri    p_pure => f_impureElemental1
99384b4e0dSEmil Kieri
100384b4e0dSEmil Kieri    !ERROR: PURE procedure pointer 'sp_pure' may not be associated with non-PURE procedure designator 's_impure1'
101384b4e0dSEmil Kieri    sp_pure => s_impure1
102384b4e0dSEmil Kieri    sp_pure => s_pure1 ! OK, same characteristics
10395f4ca7fSPeter Klausler    !ERROR: Procedure pointer 'sp_pure' associated with incompatible procedure designator 's_elemental1': incompatible procedure attributes: Elemental
104384b4e0dSEmil Kieri    sp_pure => s_elemental1 ! OK, target may be elemental when pointer is not
105384b4e0dSEmil Kieri
10662d874f2SPeter Klausler    !ERROR: Procedure pointer 'p_impure' associated with incompatible procedure designator 'f_impure2': incompatible dummy argument #1: incompatible dummy data object intents
107384b4e0dSEmil Kieri    p_impure => f_impure2
108c6b9df0fSPeter Klausler    !ERROR: Function pointer 'p_pure' associated with incompatible function designator 'f_pure2': function results have distinct types: INTEGER(4) vs REAL(4)
109384b4e0dSEmil Kieri    p_pure => f_pure2
110c6b9df0fSPeter Klausler    !ERROR: Function pointer 'p_pure' associated with incompatible function designator 'ccos': function results have distinct types: INTEGER(4) vs COMPLEX(4)
111b22873b1SPeter Klausler    p_pure => ccos
11295f4ca7fSPeter Klausler    !ERROR: Procedure pointer 'p_impure' associated with incompatible procedure designator 'f_elemental2': incompatible procedure attributes: Elemental
113384b4e0dSEmil Kieri    p_impure => f_elemental2
114384b4e0dSEmil Kieri
115b09c8905SPeter Klausler    !ERROR: Procedure pointer 'sp_impure' associated with incompatible procedure designator 's_impure2': incompatible procedure attributes: BindC
116384b4e0dSEmil Kieri    sp_impure => s_impure2
11762d874f2SPeter Klausler    !ERROR: Procedure pointer 'sp_impure' associated with incompatible procedure designator 's_pure2': incompatible dummy argument #1: incompatible dummy data object intents
118384b4e0dSEmil Kieri    sp_impure => s_pure2
11995f4ca7fSPeter Klausler    !ERROR: Procedure pointer 'sp_pure' associated with incompatible procedure designator 's_elemental2': incompatible procedure attributes: Elemental
120384b4e0dSEmil Kieri    sp_pure => s_elemental2
121384b4e0dSEmil Kieri
122384b4e0dSEmil Kieri    !ERROR: Function pointer 'p_impure' may not be associated with subroutine designator 's_impure1'
123384b4e0dSEmil Kieri    p_impure => s_impure1
124384b4e0dSEmil Kieri
125384b4e0dSEmil Kieri    !ERROR: Subroutine pointer 'sp_impure' may not be associated with function designator 'f_impure1'
126384b4e0dSEmil Kieri    sp_impure => f_impure1
127384b4e0dSEmil Kieri
12864ab3302SCarolineConcatto  contains
129384b4e0dSEmil Kieri    integer function f_impure1(n)
130384b4e0dSEmil Kieri      real, intent(in) :: n
131384b4e0dSEmil Kieri      f_impure = n
13264ab3302SCarolineConcatto    end
133384b4e0dSEmil Kieri    pure integer function f_pure1(n)
134384b4e0dSEmil Kieri      real, intent(in) :: n
135384b4e0dSEmil Kieri      f_pure = n
13664ab3302SCarolineConcatto    end
137384b4e0dSEmil Kieri    elemental integer function f_elemental1(n)
138384b4e0dSEmil Kieri      real, intent(in) :: n
139384b4e0dSEmil Kieri      f_elemental = n
140384b4e0dSEmil Kieri    end
141384b4e0dSEmil Kieri    impure elemental integer function f_impureElemental1(n)
142384b4e0dSEmil Kieri      real, intent(in) :: n
143384b4e0dSEmil Kieri      f_impureElemental = n
144384b4e0dSEmil Kieri    end
145384b4e0dSEmil Kieri
146384b4e0dSEmil Kieri    integer function f_impure2(n)
147384b4e0dSEmil Kieri      real, intent(inout) :: n
148384b4e0dSEmil Kieri      f_impure = n
149384b4e0dSEmil Kieri    end
150384b4e0dSEmil Kieri    pure real function f_pure2(n)
151384b4e0dSEmil Kieri      real, intent(in) :: n
152384b4e0dSEmil Kieri      f_pure = n
153384b4e0dSEmil Kieri    end
154384b4e0dSEmil Kieri    elemental integer function f_elemental2(n)
15543a263f5Speter klausler      real, value :: n
15643a263f5Speter klausler      f_elemental = n
15764ab3302SCarolineConcatto    end
158384b4e0dSEmil Kieri
159384b4e0dSEmil Kieri    subroutine s_impure1(n)
160384b4e0dSEmil Kieri      integer, intent(inout) :: n
161384b4e0dSEmil Kieri      n = n + 1
162384b4e0dSEmil Kieri    end
163384b4e0dSEmil Kieri    pure subroutine s_pure1(n)
164384b4e0dSEmil Kieri      integer, intent(inout) :: n
165384b4e0dSEmil Kieri      n = n + 1
166384b4e0dSEmil Kieri    end
167384b4e0dSEmil Kieri    elemental subroutine s_elemental1(n)
168384b4e0dSEmil Kieri      integer, intent(inout) :: n
169384b4e0dSEmil Kieri      n = n + 1
170384b4e0dSEmil Kieri    end
171384b4e0dSEmil Kieri
172384b4e0dSEmil Kieri    subroutine s_impure2(n) bind(c)
173384b4e0dSEmil Kieri      integer, intent(inout) :: n
174384b4e0dSEmil Kieri      n = n + 1
175384b4e0dSEmil Kieri    end subroutine s_impure2
176384b4e0dSEmil Kieri    pure subroutine s_pure2(n)
177384b4e0dSEmil Kieri      integer, intent(out) :: n
178384b4e0dSEmil Kieri      n = 1
179384b4e0dSEmil Kieri    end subroutine s_pure2
180384b4e0dSEmil Kieri    elemental subroutine s_elemental2(m,n)
181384b4e0dSEmil Kieri      integer, intent(inout) :: m, n
182384b4e0dSEmil Kieri      n = m + n
183384b4e0dSEmil Kieri    end subroutine s_elemental2
18464ab3302SCarolineConcatto  end
18564ab3302SCarolineConcatto
18664ab3302SCarolineConcatto  ! 10.2.2.4(4)
18764ab3302SCarolineConcatto  subroutine s6
18864ab3302SCarolineConcatto    procedure(s), pointer :: p, q
18964ab3302SCarolineConcatto    procedure(), pointer :: r
19064ab3302SCarolineConcatto    external :: s_external
1911341b5a0SPeter Steinfeld    p => s_external ! OK for a pointer with an explicit interface to be associated with a procedure with an implicit interface
1924f119446SPeter Steinfeld    r => s_module ! OK for a pointer with implicit interface to be associated with a procedure with an explicit interface.  See 10.2.2.4 (3)
19364ab3302SCarolineConcatto  end
19464ab3302SCarolineConcatto
19564ab3302SCarolineConcatto  ! 10.2.2.4(5)
19664ab3302SCarolineConcatto  subroutine s7
19764ab3302SCarolineConcatto    procedure(real) :: f_external
19864ab3302SCarolineConcatto    external :: s_external
19964ab3302SCarolineConcatto    procedure(), pointer :: p_s
20064ab3302SCarolineConcatto    procedure(real), pointer :: p_f
20164ab3302SCarolineConcatto    p_f => f_external
20264ab3302SCarolineConcatto    p_s => s_external
20362d874f2SPeter Klausler    !Ok: p_s has no interface
20464ab3302SCarolineConcatto    p_s => f_external
20562d874f2SPeter Klausler    !Ok: s_external has no interface
20664ab3302SCarolineConcatto    p_f => s_external
20764ab3302SCarolineConcatto  end
20864ab3302SCarolineConcatto
20964ab3302SCarolineConcatto  ! C1017: bounds-spec
21064ab3302SCarolineConcatto  subroutine s8
21164ab3302SCarolineConcatto    real, target :: x(10, 10)
21264ab3302SCarolineConcatto    real, pointer :: p(:, :)
21364ab3302SCarolineConcatto    p(2:,3:) => x
21464ab3302SCarolineConcatto    !ERROR: Pointer 'p' has rank 2 but the number of bounds specified is 1
21564ab3302SCarolineConcatto    p(2:) => x
21664ab3302SCarolineConcatto  end
21764ab3302SCarolineConcatto
21864ab3302SCarolineConcatto  ! bounds-remapping
21964ab3302SCarolineConcatto  subroutine s9
22064ab3302SCarolineConcatto    real, target :: x(10, 10), y(100)
22164ab3302SCarolineConcatto    real, pointer :: p(:, :)
22264ab3302SCarolineConcatto    ! C1018
22364ab3302SCarolineConcatto    !ERROR: Pointer 'p' has rank 2 but the number of bounds specified is 1
22464ab3302SCarolineConcatto    p(1:100) => x
22564ab3302SCarolineConcatto    ! 10.2.2.3(9)
22664ab3302SCarolineConcatto    !ERROR: Pointer bounds remapping target must have rank 1 or be simply contiguous
22764ab3302SCarolineConcatto    p(1:5,1:5) => x(1:10,::2)
22864ab3302SCarolineConcatto    ! 10.2.2.3(9)
22964ab3302SCarolineConcatto    !ERROR: Pointer bounds require 25 elements but target has only 20
23064ab3302SCarolineConcatto    p(1:5,1:5) => x(:,1:2)
23164ab3302SCarolineConcatto    !OK - rhs has rank 1 and enough elements
23264ab3302SCarolineConcatto    p(1:5,1:5) => y(1:100:2)
2337763c014SPeter Klausler    !OK - same, but from function result
2347763c014SPeter Klausler    p(1:5,1:5) => f()
2357763c014SPeter Klausler   contains
2367763c014SPeter Klausler    function f()
2377763c014SPeter Klausler      real, pointer :: f(:)
2387763c014SPeter Klausler      f => y
2397763c014SPeter Klausler    end function
24064ab3302SCarolineConcatto  end
24164ab3302SCarolineConcatto
24264ab3302SCarolineConcatto  subroutine s10
24364ab3302SCarolineConcatto    integer, pointer :: p(:)
24464ab3302SCarolineConcatto    type :: t
24564ab3302SCarolineConcatto      integer :: a(4, 4)
24664ab3302SCarolineConcatto      integer :: b
24764ab3302SCarolineConcatto    end type
24864ab3302SCarolineConcatto    type(t), target :: x
24964ab3302SCarolineConcatto    type(t), target :: y(10,10)
25064ab3302SCarolineConcatto    integer :: v(10)
25164ab3302SCarolineConcatto    p(1:16) => x%a
25264ab3302SCarolineConcatto    p(1:8) => x%a(:,3:4)
25364ab3302SCarolineConcatto    p(1:1) => x%b  ! We treat scalars as simply contiguous
25464ab3302SCarolineConcatto    p(1:1) => x%a(1,1)
25564ab3302SCarolineConcatto    p(1:1) => y(1,1)%a(1,1)
25664ab3302SCarolineConcatto    p(1:1) => y(:,1)%a(1,1)  ! Rank 1 RHS
25764ab3302SCarolineConcatto    !ERROR: Pointer bounds remapping target must have rank 1 or be simply contiguous
25864ab3302SCarolineConcatto    p(1:4) => x%a(::2,::2)
25964ab3302SCarolineConcatto    !ERROR: Pointer bounds remapping target must have rank 1 or be simply contiguous
26064ab3302SCarolineConcatto    p(1:100) => y(:,:)%b
26164ab3302SCarolineConcatto    !ERROR: Pointer bounds remapping target must have rank 1 or be simply contiguous
26264ab3302SCarolineConcatto    p(1:100) => y(:,:)%a(1,1)
26364ab3302SCarolineConcatto    !ERROR: Pointer bounds remapping target must have rank 1 or be simply contiguous
26464ab3302SCarolineConcatto    !ERROR: An array section with a vector subscript may not be a pointer target
26564ab3302SCarolineConcatto    p(1:4) => x%a(:,v)
26664ab3302SCarolineConcatto  end
26764ab3302SCarolineConcatto
26864ab3302SCarolineConcatto  subroutine s11
26964ab3302SCarolineConcatto    complex, target :: x(10,10)
27064ab3302SCarolineConcatto    complex, pointer :: p(:)
27164ab3302SCarolineConcatto    real, pointer :: q(:)
27264ab3302SCarolineConcatto    p(1:100) => x(:,:)
27364ab3302SCarolineConcatto    q(1:10) => x(1,:)%im
27464ab3302SCarolineConcatto    !ERROR: Pointer bounds remapping target must have rank 1 or be simply contiguous
27564ab3302SCarolineConcatto    q(1:100) => x(:,:)%re
27664ab3302SCarolineConcatto  end
27764ab3302SCarolineConcatto
27864ab3302SCarolineConcatto  ! Check is_contiguous, which is usually the same as when pointer bounds
27994896994SPeter Klausler  ! remapping is used.
28064ab3302SCarolineConcatto  subroutine s12
28164ab3302SCarolineConcatto    integer, pointer :: p(:)
28294896994SPeter Klausler    integer, pointer, contiguous :: pc(:)
28364ab3302SCarolineConcatto    type :: t
28464ab3302SCarolineConcatto      integer :: a(4, 4)
28564ab3302SCarolineConcatto      integer :: b
28664ab3302SCarolineConcatto    end type
28764ab3302SCarolineConcatto    type(t), target :: x
28864ab3302SCarolineConcatto    type(t), target :: y(10,10)
28964ab3302SCarolineConcatto    integer :: v(10)
29094896994SPeter Klausler    logical(kind=merge(1,-1,is_contiguous(x%a(:,:)))) :: l1 ! known true
29194896994SPeter Klausler    logical(kind=merge(1,-1,is_contiguous(y(1,1)%a(1,1)))) :: l2 ! known true
29264ab3302SCarolineConcatto    !ERROR: Must be a constant value
29394896994SPeter Klausler    logical(kind=merge(-1,-2,is_contiguous(y(:,1)%a(1,1)))) :: l3 ! unknown
29464ab3302SCarolineConcatto    !ERROR: Must be a constant value
29594896994SPeter Klausler    logical(kind=merge(-1,-2,is_contiguous(y(:,1)%a(1,1)))) :: l4 ! unknown
29694896994SPeter Klausler    logical(kind=merge(-1,1,is_contiguous(x%a(:,v)))) :: l5 ! known false
29764ab3302SCarolineConcatto    !ERROR: Must be a constant value
29894896994SPeter Klausler    logical(kind=merge(-1,-2,is_contiguous(y(v,1)%a(1,1)))) :: l6 ! unknown
299394d6fcfSJean Perier    !ERROR: Must be a constant value
30094896994SPeter Klausler    logical(kind=merge(-1,-2,is_contiguous(p(:)))) :: l7 ! unknown
30194896994SPeter Klausler    logical(kind=merge(1,-1,is_contiguous(pc(:)))) :: l8 ! known true
30294896994SPeter Klausler    logical(kind=merge(-1,1,is_contiguous(pc(1:10:2)))) :: l9 ! known false
30394896994SPeter Klausler    logical(kind=merge(-1,1,is_contiguous(pc(10:1:-1)))) :: l10 ! known false
304cebf1348SPeter Klausler    logical(kind=merge(1,-1,is_contiguous(pc(1:10:1)))) :: l11 ! known true
305cebf1348SPeter Klausler    logical(kind=merge(-1,1,is_contiguous(pc(10:1:-1)))) :: l12 ! known false
306cebf1348SPeter Klausler    !ERROR: Must be a constant value
307cebf1348SPeter Klausler    logical(kind=merge(-1,1,is_contiguous(pc(::-1)))) :: l13 ! unknown (could be empty)
308cebf1348SPeter Klausler    logical(kind=merge(1,-1,is_contiguous(y(1,1)%a(::-1,1)))) :: l14 ! known true (empty)
309cebf1348SPeter Klausler    logical(kind=merge(1,-1,is_contiguous(y(1,1)%a(1,::-1)))) :: l15 ! known true (empty)
31064ab3302SCarolineConcatto  end
311e0ca7b44SSteve Scalpone  subroutine test3(b)
312e0ca7b44SSteve Scalpone    integer, intent(inout) :: b(..)
313e0ca7b44SSteve Scalpone    !ERROR: Must be a constant value
314e0ca7b44SSteve Scalpone    integer, parameter :: i = rank(b)
315e0ca7b44SSteve Scalpone  end subroutine
316e0ca7b44SSteve Scalpone
317b09c8905SPeter Klausler  subroutine s13
318b09c8905SPeter Klausler    external :: s_external
319b09c8905SPeter Klausler    procedure(), pointer :: ptr
320b09c8905SPeter Klausler    !Ok - don't emit an error about incompatible Subroutine attribute
321b09c8905SPeter Klausler    ptr => s_external
322b09c8905SPeter Klausler    call ptr
323b09c8905SPeter Klausler  end subroutine
324bd28a0a5SPeter Klausler
325bd28a0a5SPeter Klausler  subroutine s14
326bd28a0a5SPeter Klausler    procedure(real), pointer :: ptr
327bd28a0a5SPeter Klausler    sf(x) = x + 1.
328bd28a0a5SPeter Klausler    !ERROR: Statement function 'sf' may not be the target of a pointer assignment
329bd28a0a5SPeter Klausler    ptr => sf
330bd28a0a5SPeter Klausler  end subroutine
331*d9af9cf4SPeter Klausler
332*d9af9cf4SPeter Klausler  subroutine s15
333*d9af9cf4SPeter Klausler    use m0
334*d9af9cf4SPeter Klausler    intrinsic sin
335*d9af9cf4SPeter Klausler    p=>sin ! ok
336*d9af9cf4SPeter Klausler  end
33764ab3302SCarolineConcattoend
338