Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Semantics / boz-literal-constants.f90
blobe6392f6f030e526a243ed29bdbfc867c43ef5a57
1 ! RUN: %python %S/test_errors.py %s %flang_fc1
2 ! Confirm enforcement of constraints and restrictions in 7.7
3 ! C7107, C7108, C7109
5 subroutine bozchecks
6 ! Type declaration statements
7 integer :: f, realpart = B"0101", img = B"1111", resint
8 logical :: resbit
9 complex :: rescmplx
10 real :: dbl, e
11 interface
12 subroutine explicit(n, x, c)
13 integer :: n
14 real :: x
15 character :: c
16 end subroutine
17 end interface
18 ! C7107
19 !ERROR: Invalid digit ('a') in BOZ literal 'b"110a"'
20 integer, parameter :: a = B"110A"
21 !ERROR: Invalid digit ('2') in BOZ literal 'b"1232"'
22 integer, parameter :: b = B"1232"
23 !ERROR: BOZ literal 'b"010101010101010101010101011111111111111111111111111111111111111111111111111111111111111111111111111111111111000000000000000000000000000000000000"' too large
24 integer, parameter :: b1 = B"010101010101010101010101011111111111111111111&
25 &111111111111111111111111111111111111111111111&
26 &111111111111111111000000000000000000000000000&
27 &000000000"
28 ! C7108
29 !ERROR: Invalid digit ('8') in BOZ literal 'o"8"'
30 integer :: c = O"8"
31 !ERROR: Invalid digit ('a') in BOZ literal 'o"a"'
32 integer :: d = O"A"
34 ! C7109
35 ! A) can appear only in data statement
36 ! B) Argument to intrinsics listed from 16.9 below
37 ! BGE, BGT, BLE, BLT, CMPLX, DBLE, DSHIFTL,
38 ! DSHIFTR, IAND, IEOR, INT, IOR, MERGE_BITS, REAL
39 ! and legacy aliases AND, OR, XOR
41 ! part A
42 data f / Z"AA" / ! OK
43 !ERROR: DATA statement value could not be converted to the type 'COMPLEX(4)' of the object 'rescmplx'
44 data rescmplx / B"010101" /
45 ! part B
46 resbit = BGE(B"0101", B"1111")
47 resbit = BGT(Z"0101", B"1111")
48 resbit = BLE(B"0101", B"1111")
49 resbit = BLT(B"0101", B"1111")
51 res = CMPLX (realpart, img, 4)
52 res = CMPLX (B"0101", B"1111", 4)
54 !WARNING: underflow on REAL(8) to REAL(4) conversion
55 dbl = DBLE(B"1111")
56 dbl = DBLE(realpart)
58 !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
59 dbl = DSHIFTL(B"0101",B"0101",2)
60 !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
61 dbl = DSHIFTR(B"1010",B"1010",2)
62 dbl = DSHIFTL(B"0101",5,2) ! OK
63 dbl = DSHIFTR(B"1010",5,2) ! OK
65 !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
66 resint = IAND(B"0001", B"0011")
67 resint = IAND(B"0001", 3)
68 !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
69 resint = AND(B"0001", B"0011")
70 resint = AND(B"0001", 3)
72 !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
73 resint = IEOR(B"0001", B"0011")
74 resint = IEOR(B"0001", 3)
75 !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
76 resint = XOR(B"0001", B"0011")
77 resint = XOR(B"0001", 3)
79 resint = INT(B"1010")
81 !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
82 res = IOR(B"0101", B"0011")
83 res = IOR(B"0101", 3)
84 !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
85 res = OR(B"0101", B"0011")
86 res = OR(B"0101", 3)
88 res = MERGE_BITS(13,3,11)
89 res = MERGE_BITS(B"1101",3,11)
90 !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
91 res = MERGE_BITS(B"1101",B"0011",11)
92 !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
93 res = MERGE_BITS(B"1101",B"0011",B"1011")
94 res = MERGE_BITS(B"1101",3,B"1011")
96 !ERROR: Typeless (BOZ) not allowed for 'x=' argument
97 res = KIND(z'feedface')
99 res = REAL(B"1101")
102 call explicit(z'deadbeef', o'666', 'a')
104 !ERROR: Actual argument 'z'55'' associated with dummy argument 'c=' is not a variable or typed expression
105 call explicit(z'deadbeef', o'666', b'01010101')
107 !ERROR: BOZ argument requires an explicit interface
108 call implictSub(Z'12345')
110 !ERROR: Output item must not be a BOZ literal constant
111 print "(Z18)", Z"76543210"
112 end subroutine