• Home
  • Line#
  • Scopes#
  • Navigate#
  • Raw
  • Download
1! RUN: %S/test_errors.sh %s %t %f18
2! Confirm enforcement of constraints and restrictions in 7.7
3! C7107, C7108, C7109
4
5subroutine 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  ! C7107
12  !ERROR: Invalid digit ('a') in BOZ literal 'b"110a"'
13  integer, parameter :: a = B"110A"
14  !ERROR: Invalid digit ('2') in BOZ literal 'b"1232"'
15  integer, parameter :: b = B"1232"
16  !ERROR: BOZ literal 'b"010101010101010101010101011111111111111111111111111111111111111111111111111111111111111111111111111111111111000000000000000000000000000000000000"' too large
17  integer, parameter :: b1 = B"010101010101010101010101011111111111111111111&
18                              &111111111111111111111111111111111111111111111&
19                              &111111111111111111000000000000000000000000000&
20                              &000000000"
21  ! C7108
22  !ERROR: Invalid digit ('8') in BOZ literal 'o"8"'
23  integer :: c = O"8"
24  !ERROR: Invalid digit ('a') in BOZ literal 'o"a"'
25  integer :: d = O"A"
26
27  ! C7109
28  !    A) can appear only in data statement
29  !    B) Argument to intrinsics listed from 16.9 below
30  !       BGE, BGT, BLE, BLT, CMPLX, DBLE, DSHIFTL,
31  !       DSHIFTR, IAND, IEOR, INT, IOR, MERGE_BITS, REAL
32
33  ! part A
34  data f / Z"AA" / ! OK
35  !ERROR: DATA statement value could not be converted to the type 'COMPLEX(4)' of the object 'rescmplx'
36  data rescmplx / B"010101" /
37  ! part B
38  resbit = BGE(B"0101", B"1111")
39  resbit = BGT(Z"0101", B"1111")
40  resbit = BLE(B"0101", B"1111")
41  resbit = BLT(B"0101", B"1111")
42
43  res = CMPLX (realpart, img, 4)
44  res = CMPLX (B"0101", B"1111", 4)
45
46  dbl = DBLE(B"1111")
47  dbl = DBLE(realpart)
48
49  !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
50  dbl = DSHIFTL(B"0101",B"0101",2)
51  !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
52  dbl = DSHIFTR(B"1010",B"1010",2)
53  dbl = DSHIFTL(B"0101",5,2) ! OK
54  dbl = DSHIFTR(B"1010",5,2) ! OK
55
56  !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
57  resint = IAND(B"0001", B"0011")
58  resint = IAND(B"0001", 3)
59
60  !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
61  resint = IEOR(B"0001", B"0011")
62  resint = IEOR(B"0001", 3)
63
64  resint = INT(B"1010")
65
66  !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
67  res = IOR(B"0101", B"0011")
68  res = IOR(B"0101", 3)
69
70  res = MERGE_BITS(13,3,11)
71  res = MERGE_BITS(B"1101",3,11)
72  !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
73  res = MERGE_BITS(B"1101",B"0011",11)
74  !ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
75  res = MERGE_BITS(B"1101",B"0011",B"1011")
76  res = MERGE_BITS(B"1101",3,B"1011")
77
78  res = REAL(B"1101")
79end subroutine
80