You can not select more than 25 topics
Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
80 lines
2.7 KiB
80 lines
2.7 KiB
! RUN: %S/test_errors.sh %s %t %f18
|
|
! Confirm enforcement of constraints and restrictions in 7.7
|
|
! C7107, C7108, C7109
|
|
|
|
subroutine bozchecks
|
|
! Type declaration statements
|
|
integer :: f, realpart = B"0101", img = B"1111", resint
|
|
logical :: resbit
|
|
complex :: rescmplx
|
|
real :: dbl, e
|
|
! C7107
|
|
!ERROR: Invalid digit ('a') in BOZ literal 'b"110a"'
|
|
integer, parameter :: a = B"110A"
|
|
!ERROR: Invalid digit ('2') in BOZ literal 'b"1232"'
|
|
integer, parameter :: b = B"1232"
|
|
!ERROR: BOZ literal 'b"010101010101010101010101011111111111111111111111111111111111111111111111111111111111111111111111111111111111000000000000000000000000000000000000"' too large
|
|
integer, parameter :: b1 = B"010101010101010101010101011111111111111111111&
|
|
&111111111111111111111111111111111111111111111&
|
|
&111111111111111111000000000000000000000000000&
|
|
&000000000"
|
|
! C7108
|
|
!ERROR: Invalid digit ('8') in BOZ literal 'o"8"'
|
|
integer :: c = O"8"
|
|
!ERROR: Invalid digit ('a') in BOZ literal 'o"a"'
|
|
integer :: d = O"A"
|
|
|
|
! C7109
|
|
! A) can appear only in data statement
|
|
! B) Argument to intrinsics listed from 16.9 below
|
|
! BGE, BGT, BLE, BLT, CMPLX, DBLE, DSHIFTL,
|
|
! DSHIFTR, IAND, IEOR, INT, IOR, MERGE_BITS, REAL
|
|
|
|
! part A
|
|
data f / Z"AA" / ! OK
|
|
!ERROR: DATA statement value could not be converted to the type 'COMPLEX(4)' of the object 'rescmplx'
|
|
data rescmplx / B"010101" /
|
|
! part B
|
|
resbit = BGE(B"0101", B"1111")
|
|
resbit = BGT(Z"0101", B"1111")
|
|
resbit = BLE(B"0101", B"1111")
|
|
resbit = BLT(B"0101", B"1111")
|
|
|
|
res = CMPLX (realpart, img, 4)
|
|
res = CMPLX (B"0101", B"1111", 4)
|
|
|
|
dbl = DBLE(B"1111")
|
|
dbl = DBLE(realpart)
|
|
|
|
!ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
|
|
dbl = DSHIFTL(B"0101",B"0101",2)
|
|
!ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
|
|
dbl = DSHIFTR(B"1010",B"1010",2)
|
|
dbl = DSHIFTL(B"0101",5,2) ! OK
|
|
dbl = DSHIFTR(B"1010",5,2) ! OK
|
|
|
|
!ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
|
|
resint = IAND(B"0001", B"0011")
|
|
resint = IAND(B"0001", 3)
|
|
|
|
!ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
|
|
resint = IEOR(B"0001", B"0011")
|
|
resint = IEOR(B"0001", 3)
|
|
|
|
resint = INT(B"1010")
|
|
|
|
!ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
|
|
res = IOR(B"0101", B"0011")
|
|
res = IOR(B"0101", 3)
|
|
|
|
res = MERGE_BITS(13,3,11)
|
|
res = MERGE_BITS(B"1101",3,11)
|
|
!ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
|
|
res = MERGE_BITS(B"1101",B"0011",11)
|
|
!ERROR: Typeless (BOZ) not allowed for both 'i=' & 'j=' arguments
|
|
res = MERGE_BITS(B"1101",B"0011",B"1011")
|
|
res = MERGE_BITS(B"1101",3,B"1011")
|
|
|
|
res = REAL(B"1101")
|
|
end subroutine
|