Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Semantics / stopped_images.f90
blob8caab8e61991a480b14daaeab21eb5df29430713
1 ! RUN: %python %S/test_errors.py %s %flang_fc1
2 ! Check for semantic errors in stopped_images() function calls
3 ! as defined in 16.9.183 in the Fortran 2018 standard
5 program stopped_images_test
6 use iso_fortran_env, only: team_type
7 use iso_c_binding, only: c_int32_t, c_int64_t
8 implicit none
10 type(team_type) home, league(2)
11 integer n, i, array(1), non_constant
12 integer, allocatable :: stopped(:)
13 integer, allocatable :: wrong_rank(:,:)
14 logical non_integer, non_team
15 character, allocatable :: wrong_result(:)
17 !___ standard-conforming statement with no optional arguments present ___
18 stopped = stopped_images()
20 !___ standard-conforming statements with optional team argument present ___
21 stopped = stopped_images(home)
22 stopped = stopped_images(team=home)
23 stopped = stopped_images(league(1))
25 !___ standard-conforming statements with optional kind argument present ___
26 stopped = stopped_images(kind=c_int32_t)
28 !___ standard-conforming statements with both optional arguments present ___
29 stopped = stopped_images(home, c_int32_t)
30 stopped = stopped_images(team=home, kind=c_int32_t)
31 stopped = stopped_images(kind=c_int32_t, team=home)
33 !___ non-conforming statements ___
35 !ERROR: Actual argument for 'team=' has bad type 'LOGICAL(4)'
36 stopped = stopped_images(non_team)
38 !ERROR: 'team=' argument has unacceptable rank 1
39 stopped = stopped_images(league)
41 !ERROR: Actual argument for 'team=' has bad type 'INTEGER(4)'
42 stopped = stopped_images(team=-1)
44 !ERROR: Actual argument for 'team=' has bad type 'INTEGER(4)'
45 stopped = stopped_images(team=i, kind=c_int32_t)
47 !ERROR: Actual argument for 'team=' has bad type 'INTEGER(4)'
48 stopped = stopped_images(i, c_int32_t)
50 !ERROR: Actual argument for 'team=' has bad type 'INTEGER(4)'
51 stopped = stopped_images(c_int32_t)
53 !ERROR: repeated keyword argument to intrinsic 'stopped_images'
54 stopped = stopped_images(team=home, team=league(1))
56 !ERROR: 'kind=' argument must be a constant scalar integer whose value is a supported kind for the intrinsic result type
57 stopped = stopped_images(kind=non_constant)
59 !ERROR: Actual argument for 'kind=' has bad type 'LOGICAL(4)'
60 stopped = stopped_images(home, non_integer)
62 !ERROR: Actual argument for 'kind=' has bad type 'LOGICAL(4)'
63 stopped = stopped_images(kind=non_integer)
65 !ERROR: 'kind=' argument has unacceptable rank 1
66 stopped = stopped_images(kind=array)
68 !ERROR: repeated keyword argument to intrinsic 'stopped_images'
69 stopped = stopped_images(kind=c_int32_t, kind=c_int64_t)
71 !ERROR: too many actual arguments for intrinsic 'stopped_images'
72 stopped = stopped_images(home, c_int32_t, 3)
74 !ERROR: Actual argument for 'team=' has bad type 'REAL(4)'
75 stopped = stopped_images(3.4)
77 !ERROR: unknown keyword argument to intrinsic 'stopped_images'
78 stopped = stopped_images(kinds=c_int32_t)
80 !ERROR: unknown keyword argument to intrinsic 'stopped_images'
81 stopped = stopped_images(home, kinds=c_int32_t)
83 !ERROR: unknown keyword argument to intrinsic 'stopped_images'
84 stopped = stopped_images(my_team=home)
86 !ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches scalar INTEGER(4) and rank 1 array of INTEGER(4)
87 n = stopped_images()
89 !ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches rank 2 array of INTEGER(4) and rank 1 array of INTEGER(4)
90 wrong_rank = stopped_images()
92 !ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches operand types CHARACTER(KIND=1) and INTEGER(4)
93 wrong_result = stopped_images()
95 end program stopped_images_test