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