xref: /llvm-project/flang/test/Semantics/move_alloc.f90 (revision f9b089a7c01dd3fe7de3d397520172ec3b8fb9f1)
1! RUN: %python %S/test_errors.py %s %flang_fc1
2! Check for semantic errors in move_alloc() subroutine calls
3program main
4  integer, allocatable :: a(:)[:], b(:)[:], f(:), g(:)
5  type alloc_component
6    integer, allocatable :: a(:)
7  end type
8  type(alloc_component) :: c[*], d[*]
9  !ERROR: 'e' is an ALLOCATABLE coarray and must have a deferred coshape
10  integer, allocatable :: e(:)[*]
11  integer status, coindexed_status[*]
12  character(len=1) message, coindexed_message[*]
13  integer :: nonAllocatable(10)
14  type t
15  end type
16  class(t), allocatable :: t1
17  type(t), allocatable :: t2
18  character, allocatable :: ca*2, cb*3
19
20  ! standards conforming
21  allocate(a(3)[*])
22  a = [ 1, 2, 3 ]
23  call move_alloc(a, b, status, message)
24
25  !ERROR: too many actual arguments for intrinsic 'move_alloc'
26  call move_alloc(a, b, status, message, 1)
27
28  ! standards non-conforming
29  !ERROR: 'from' argument to 'move_alloc' may not be a coindexed object
30  call move_alloc(c[1]%a, f)
31
32  !ERROR: 'to' argument to 'move_alloc' may not be a coindexed object
33  call move_alloc(f, d[1]%a)
34
35  !ERROR: 'stat' argument to 'move_alloc' may not be a coindexed object
36  call move_alloc(f, g, coindexed_status[1])
37
38  !ERROR: 'errmsg' argument to 'move_alloc' may not be a coindexed object
39  call move_alloc(f, g, status, coindexed_message[1])
40
41  !ERROR: 'errmsg' argument to 'move_alloc' may not be a coindexed object
42  call move_alloc(f, g, errmsg=coindexed_message[1])
43
44  !ERROR: 'errmsg' argument to 'move_alloc' may not be a coindexed object
45  call move_alloc(f, g, errmsg=coindexed_message[1], stat=status)
46
47  !ERROR: 'stat' argument to 'move_alloc' may not be a coindexed object
48  call move_alloc(f, g, stat=coindexed_status[1])
49
50  !ERROR: 'stat' argument to 'move_alloc' may not be a coindexed object
51  call move_alloc(f, g, errmsg=message, stat=coindexed_status[1])
52
53  !ERROR: 'from' argument to 'move_alloc' may not be a coindexed object
54  !ERROR: 'to' argument to 'move_alloc' may not be a coindexed object
55  !ERROR: 'stat' argument to 'move_alloc' may not be a coindexed object
56  !ERROR: 'errmsg' argument to 'move_alloc' may not be a coindexed object
57  call move_alloc(c[1]%a, d[1]%a, stat=coindexed_status[1], errmsg=coindexed_message[1])
58
59  !ERROR: Argument #1 to MOVE_ALLOC must be allocatable
60  call move_alloc(nonAllocatable, f)
61  !ERROR: Argument #2 to MOVE_ALLOC must be allocatable
62  call move_alloc(f, nonAllocatable)
63
64  !ERROR: When MOVE_ALLOC(FROM=) is polymorphic, TO= must also be polymorphic
65  call move_alloc(t1, t2)
66  call move_alloc(t2, t1) ! ok
67
68  !ERROR: Actual argument for 'to=' has bad type or kind 'CHARACTER(KIND=1,LEN=3_8)'
69  call move_alloc(ca, cb)
70
71  !ERROR: Argument #1 to MOVE_ALLOC must be allocatable
72  call move_alloc(f(::2), g)
73  !ERROR: Argument #2 to MOVE_ALLOC must be allocatable
74  call move_alloc(f, g(::2))
75
76end program main
77