Skip to content

Instantly share code, notes, and snippets.

@drikosev
Last active June 10, 2020 09:39
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save drikosev/628ec40198f0a73bdef256b4cf8d0e3c to your computer and use it in GitHub Desktop.
Save drikosev/628ec40198f0a73bdef256b4cf8d0e3c to your computer and use it in GitHub Desktop.
! { dg-do run }
! { dg-options "-fopenmp" }
! By default: -fallow-invalid-boz
! By default: Warn only few known non portable uses
! whereas -Wno-invalid-boz disables all related warnings,
! and -Winvalid-boz enables all related warnings.
program boz_extensions
integer, parameter :: p0 = Z'1234'
real,parameter :: rc = real(z'50CB9F09')
real,parameter :: r2 = z'50CB9F09'
class(*), allocatable :: pr
type q
integer :: i
integer :: a(2)
real :: r
end type
type t
integer :: i
type(q) :: q
real :: r
end type
type(t) :: x,y
type(t) :: a(1)
type(t) :: b(1)
real, dimension (2) :: i,i2
real, dimension (2) :: j,j2
real, dimension (2) :: k,k2
real, dimension (2) :: l
real, save :: s = 1.0+z'1'
data x /t(1+z'1',q(1+z'1',[integer::z'1',z'1'],z'50CB9F09'),z'50CB9F09')/
data y /t(1+z'1',q(1+z'1',[ z'1',z'1'],z'50CB9F09'),z'50CB9F09')/
a=[t(1+z'1',q(1+z'1',[integer::z'1',z'1'],z'50CB9F09'),z'50CB9F09')]
b=[t(1+z'1',q(1+z'1',[ z'1',z'1'],z'50CB9F09'),z'50CB9F09')]!{ dg-warning "BOZ" }
i=(/ 1 +z'1', z'50CB9F09' /) ! { dg-warning "BOZ literal" }
j=(/ 2.0 , z'50CB9F09' /) ! { dg-warning "BOZ literal" }
k=(/ 1.0+z'1', z'50CB9F09' /) ! { dg-warning "BOZ literal" }
l=(/ z'50CB9F09' , z'50CB9F09'/)
i2=(/ integer :: 1 +z'1', z'50CB9F09' /)
j2=(/ real :: 2.0 , z'50CB9F09' /)
k2=(/ real :: 1.0+z'1', z'50CB9F09' /)
print *, "*101. i=", i
print *, "*111. i2=", i2
print *, "*201. j=", j
print *, "*211. j2=", j2
print *, "*301. k=", k
print *, "*311. k2=", k2
print *, " 401. l=", l
print *, " 501. x%i=", x%i
print *, " 502. x%q%i=", x%q%i
print *, " 503. x%q%a(1)=", x%q%a(1)
print *, " 504. x%q%a(2)=", x%q%a(2)
print *, " 505. x%q%r=", x%q%r
print *, " 506. x%r=", x%r
print *, " 511. x%i=", y%i
print *, " 512. y%q%i=", y%q%i
print *, " y%q%a(1)=", y%q%a(1)
print *, " y%q%a(2)=", y%q%a(2)
print *, " 515. y%q%r=", y%q%r
print *, " 516. y%r=", y%r
print *, " 521. a(1)%i=", a(1)%i
print *, " 522. a(1)%q%i=", a(1)%q%i
print *, " a(1)%q%a(1)=", a(1)%q%a(1)
print *, " a(1)%q%a(2)=", a(1)%q%a(2)
print *, " 525. a(1)%q%r=", a(1)%q%r
print *, " 526. a(1)%r=", a(1)%r
print *, " 531. b(1)%i=", b(1)%i
print *, " 532. b(1)%q%i=", b(1)%q%i
print *, "* b(1)%q%a(1)=", b(1)%q%a(1)
print *, "* b(1)%q%a(2)=", b(1)%q%a(2)
print *, " 535. b(1)%q%r=", b(1)%q%r
print *, " 536. b(1)%r=", b(1)%r
print *, " 700. z'2' = 1+z'1' (", z'2' == 1+z'1',")"
print *, " 710. rc=", rc
print *, " 711. r2=", r2
print *, " 712. p0=", p0
print *, " 713. s=", s
if ( i(1) /= 2.0 ) stop 101
if ( i(2) /= 1.35552179E+09 ) stop 102
if ( i2(1) /= 2.0 ) stop 111
if ( i2(2) /= 1.35552179E+09 ) stop 112
if ( j(1) /= 2.0 ) stop 201
if ( j(2) /= 2.73295790E+10 ) stop 202
if ( j2(1) /= 2.0 ) stop 211
if ( j2(2) /= 2.73295790E+10 ) stop 212
if ( k(1) /= 1.0 ) stop 301
if ( k(2) /= 2.73295790E+10 ) stop 302
if ( k2(1) /= 1.0 ) stop 311
if ( k2(2) /= 2.73295790E+10 ) stop 312
if ( l(1) /= 2.73295790E+10 ) stop 401
if ( l(2) /= 2.73295790E+10 ) stop 402
if ( x%i /= 2 ) stop 501
if ( x%q%i /= 2 ) stop 502
if ( x%q%a(1) /= 1 ) stop 503
if ( x%q%a(2) /= 1 ) stop 504
if ( x%q%r /= 2.73295790E+10 ) stop 505
if ( x%r /= 2.73295790E+10 ) stop 506
if ( y%i /= 2 ) stop 511
if ( y%q%i /= 2 ) stop 512
if ( y%q%a(1) /= 1 ) stop 513
if ( y%q%a(2) /= 1 ) stop 514
if ( y%q%r /= 2.73295790E+10 ) stop 515
if ( y%r /= 2.73295790E+10 ) stop 516
if ( a(1)%i /= 2 ) stop 521
if ( a(1)%q%i /= 2 ) stop 522
if ( a(1)%q%a(1) /= 1 ) stop 523
if ( a(1)%q%a(2) /= 1 ) stop 524
if ( a(1)%q%r /= 2.73295790E+10 ) stop 525
if ( a(1)%r /= 2.73295790E+10 ) stop 526
if ( b(1)%i /= 2 ) stop 531
if ( b(1)%q%i /= 2 ) stop 532
if ( b(1)%q%a(1) /= 1 ) stop 533
if ( b(1)%q%a(2) /= 1 ) stop 534
if ( b(1)%q%r /= 2.73295790E+10 ) stop 535
if ( b(1)%r /= 2.73295790E+10 ) stop 536
if ( z'2' /= 1+z'1' ) stop 700
if ( rc /= 2.73295790E+10 ) stop 710
if ( r2 /= 2.73295790E+10 ) stop 711
if ( p0 /= 4660 ) stop 712
if ( s /= 1.0 ) stop 713
call sub(Z'1', z'50CB9F09' ) ! { dg-warning "BOZ literal" }
call array()
!$ pr = Z'17571' ! { dg-warning "BOZ literal" }
call op()
call boz_intrinsics()
call nested_tqpn_i()
call nested_tqpn_r()
contains
subroutine sub(si,sr)
integer si, ls
real sr
print *, "*814. si=", si
print *, "*815. sr=", sr
if ( si /= 1 ) stop 814
if ( sr /= 2.73295790E+10 ) stop 815
ls = f(Z'1', z'50CB9F09' ) ! { dg-warning "BOZ literal" }
end
integer function f(si,sr)
integer si, ls
real sr
print *, "*816. si=", si
print *, "*817. sr=", sr
if ( si /= 1 ) stop 816
if ( sr /= 2.73295790E+10 ) stop 817
f=1
end
subroutine array
integer :: n(z'f') = [z'1', z'2', z'3', z'4', z'5', z'6', z'7', &
& z'8', z'9', z'a', z'b', z'c', z'd', z'e', z'f']
integer i
print *, " 918.n(1:2)=", n(1:2)
do i = z'1', z'e'
if (i /= n(i) ) stop 918
end do
end subroutine
subroutine op()
integer z
real sr
print *, "1001. z=", z'1' + z'2'
print *, "1002. -z=", -z'3'
print *, "1003. +z=", +z'3'
if ( ( z'1' + z'2' ) /= 3 ) stop 1001
if ( ( -z'3' ) /=-3 ) stop 1002
if ( ( +z'3' ) /=+3 ) stop 1003
end
subroutine boz_intrinsics()
!BGE, BLT, CMPLX, DBLE, DSHIFTL, DSHIFTR, IAND, IEOR, INT, IOR, MERGE_BITS, REAL
!$ print *, "2001. ", BGE (Z"1",Z"2")
!$ print *, "2002. ", BLT (Z"2",Z"1")
print *, "2003. ", CMPLX(z'50CB9F09'), CMPLX(z'50CB9F09',z'50CB9F09') !std
print *, "2004. ", DBLE(Z'3FD34413509F79FF') !std
!$ print *, "2005. ", DSHIFTL(Z"1",Z"2",Z"1")
!$ print *, "2006. ", DSHIFTR(Z"1",Z"2",Z"1")
print *, "2007. ", IAND(Z"1",Z"2")
print *, "2008. ", IEOR(Z"1",Z"2")
print *, "2009. ", INT(Z"1") !std
print *, "2010. ", IOR(Z"1",Z"2")
!$ print *, "2011. ", MERGE_BITS(Z"1",Z"2",Z"3")
print *, "2012. ", REAL(z'50CB9F09') !std
!$ if ( BGE (Z"1",Z"2") ) stop 2001
!$ if ( BLT (Z"2",Z"1") ) stop 2002
if ( CMPLX(z'50CB9F09',z'50CB9F09') /= (2.7329579E+10,2.7329579E+10)) stop 2003
if ( DBLE(Z'3FD34413509F79FF') /= 0.30102999566398120d0) stop 2004
if ( IAND(Z"1",Z"2") /= (0 ) ) stop 2007
if ( IEOR(Z"1",Z"2") /= (3 ) ) stop 2008
if ( INT(Z"1") /= (1 ) ) stop 2009
if ( IOR(Z"1",Z"2") /= (3 ) ) stop 2010
if ( REAL(z'50CB9F09') /= (2.7329579E+10)) stop 2012
end subroutine
subroutine nested_tqpn_i()
type n
integer :: i(2)
end type
type p
type(n) :: n(1)
end type
type q
integer :: i
type(p) :: p(2)
real :: r
end type
type t
integer :: i
type(q) :: q
real :: r
end type
type(t) :: d, w(1)
data d / &
t( &
z'1', &
q( &
z'1', &
[ &
p([n([ 2, z'2'])]), &
p([n([z'2', 2 ])]) &
] , &
z'50CB9F09' &
), &
z'50CB9F09' &
) &
/
w = [ &
t( &
z'1', &
q( &
z'1', &
[ &
p([n([ 2, z'2'])]), & ! { dg-warning "BOZ literal" }
p([n([z'2', 2 ])]) & ! { dg-warning "BOZ literal" }
] , &
z'50CB9F09' &
), &
z'50CB9F09' &
) &
]
print *, "3001. w(1)%i=", w(1)%i
print *, "3002. w(1)%q%i=", w(1)%q%i
print *, " w(1)%q%p(1)%i(1)=", w(1)%q%p(1)%n(1)%i(1)
print *, "*w(1)%q%p(1)%i(2)=", w(1)%q%p(1)%n(1)%i(2)
print *, "*w(1)%q%p(2)%i(1)=", w(1)%q%p(2)%n(1)%i(1)
print *, " w(1)%q%p(2)%i(2)=", w(1)%q%p(2)%n(1)%i(2)
print *, "3007. w(1)%q%r=", w(1)%q%r
print *, "3008. w(1)%r=", w(1)%r
print *, "3111. d%i=", d%i
print *, "3112. d%q%i=", d%q%i
print *, " d%q%p(1)%i(1)=", d%q%p(1)%n(1)%i(1)
print *, " d%q%p(1)%i(2)=", d%q%p(1)%n(1)%i(2)
print *, " d%q%p(2)%i(1)=", d%q%p(2)%n(1)%i(1)
print *, " d%q%p(2)%i(2)=", d%q%p(2)%n(1)%i(2)
print *, "3117. d%q%r=", d%q%r
print *, "3118. d%r=", d%r
if ( w(1)%i /= 1 ) stop 3001
if ( w(1)%q%i /= 1 ) stop 3002
if ( w(1)%q%p(1)%n(1)%i(1) /= 2 ) stop 3003
if ( w(1)%q%p(1)%n(1)%i(2) /= 2 ) stop 3004
if ( w(1)%q%p(2)%n(1)%i(1) /= 2 ) stop 3005
if ( w(1)%q%p(2)%n(1)%i(2) /= 2 ) stop 3006
if ( w(1)%q%r /= 2.73295790E+10 ) stop 3007
if ( w(1)%r /= 2.73295790E+10 ) stop 3008
if ( d%i /= 1 ) stop 3011
if ( d%q%i /= 1 ) stop 3012
if ( d%q%p(1)%n(1)%i(1) /= 2 ) stop 3013
if ( d%q%p(1)%n(1)%i(2) /= 2 ) stop 3014
if ( d%q%p(2)%n(1)%i(1) /= 2 ) stop 3015
if ( d%q%p(2)%n(1)%i(2) /= 2 ) stop 3016
if ( d%q%r /= 2.73295790E+10) stop 3017
if ( d%r /= 2.73295790E+10) stop 3018
end subroutine
subroutine nested_tqpn_r()
type n
real :: i(2)
end type
type p
type(n) :: n(1)
end type
type q
integer :: i
type(p) :: p(2)
real :: r
end type
type t
integer :: i
type(q) :: q
real :: r
end type
type(t) :: c, r(1)
data c /&
t( &
z'1', &
q( &
z'1', &
[ &
p([n([ 2, z'50CB9F09'])]), &
p([n([z'50CB9F09', 2.0 ])]) & ! { dg-warning "BOZ literal" }
] , &
z'50CB9F09' &
), &
z'50CB9F09' &
) &
/
r = [ &
t( &
z'1', &
q( &
z'1', &
[ &
p([n([ 2, z'50CB9F09'])]), & ! { dg-warning "BOZ literal" }
p([n([z'50CB9F09', 2.0 ])]) & ! { dg-warning "BOZ literal" }
] , &
z'50CB9F09' &
), &
z'50CB9F09' &
) &
]
print *, "4001. r(1)%i=", r(1)%i
print *, "4002. r(1)%q%i=", r(1)%q%i
print *, " r(1)%q%p(1)%i(1)=", r(1)%q%p(1)%n(1)%i(1)
print *, "*r(1)%q%p(1)%i(2)=", r(1)%q%p(1)%n(1)%i(2)
print *, "*r(1)%q%p(2)%i(1)=", r(1)%q%p(2)%n(1)%i(1)
print *, " r(1)%q%p(2)%i(2)=", r(1)%q%p(2)%n(1)%i(2)
print *, "4007. r(1)%q%r=", r(1)%q%r
print *, "4008. r(1)%r=", r(1)%r
print *, "4111. c%i=", c%i
print *, "4112. c%q%i=", c%q%i
print *, " c%q%p(1)%i(1)=", c%q%p(1)%n(1)%i(1)
print *, " c%q%p(1)%i(2)=", c%q%p(1)%n(1)%i(2)
print *, "* c%q%p(2)%i(1)=", c%q%p(2)%n(1)%i(1)
print *, " c%q%p(2)%i(2)=", c%q%p(2)%n(1)%i(2)
print *, "4117. c%q%r=", c%q%r
print *, "4118. c%r=", c%r
if ( r(1)%i /= 1 ) stop 4001
if ( r(1)%q%i /= 1 ) stop 4002
if ( r(1)%q%p(1)%n(1)%i(1) /= 2.0 ) stop 4003
if ( r(1)%q%p(1)%n(1)%i(2) /= 1.35552179E+09 ) stop 4004
if ( r(1)%q%p(2)%n(1)%i(1) /= 2.73295790E+10 ) stop 4005
if ( r(1)%q%p(2)%n(1)%i(2) /= 2.0 ) stop 4006
if ( r(1)%q%r /= 2.73295790E+10 ) stop 4007
if ( r(1)%r /= 2.73295790E+10 ) stop 4008
if ( c%i /= 1 ) stop 4011
if ( c%q%i /= 1 ) stop 4012
if ( c%q%p(1)%n(1)%i(1) /= 2.0 ) stop 4013
if ( c%q%p(1)%n(1)%i(2) /= 1.35552179E+09 ) stop 4014
if ( c%q%p(2)%n(1)%i(1) /= 2.73295790E+10 ) stop 4015
if ( c%q%p(2)%n(1)%i(2) /= 2.0 ) stop 4016
if ( c%q%r /= 2.73295790E+10 ) stop 4017
if ( c%r /= 2.73295790E+10 ) stop 4018
end subroutine
! Returns the length of the utf-8 sequence that begins at character.
!
! Note: I've found the limits (ie Z'E0') used in this function in
! another Fortran program and my assumption here is that these
! limits are equivalent to the ones used in file "dictionary.c"
! which is also restricted to UTF-8 up to 4 bytes.
!
function ulen(ch)
use iso_c_binding, only: c_char
implicit none
character(kind=c_char), intent(in) ::ch
integer :: ulen, ich
ulen=0
ich = ichar(ch)
if ( ich < Z'80' ) THEN
ulen=1
else if ( (ich > ( Z'C0' + 1)) .and. ( ich < Z'E0' )) THEN
ulen=2
else if ( ich < Z'F0' ) THEN
ulen=3
else if ( ich <= Z'F4' ) THEN
ulen=4
else
ulen=1 !assume we process larger sequqences, 1 by 1 bytes
end if
end function
end
boz_extensions.f90:356.36:
p([n([z'50CB9F09', 2.0 ])]) & ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant before element at (1) in array constructor
boz_extensions.f90:370.29:
p([n([ 2, z'50CB9F09'])]), & ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant at (1) cannot appear in an array constructor
boz_extensions.f90:371.36:
p([n([z'50CB9F09', 2.0 ])]) & ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant before element at (1) in array constructor
boz_extensions.f90:278.29:
p([n([ 2, z'2'])]), & ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant at (1) cannot appear in an array constructor
boz_extensions.f90:279.29:
p([n([z'2', 2 ])]) & ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant before element at (1) in array constructor
boz_extensions.f90:163.19:
ls = f(Z'1', z'50CB9F09' ) ! { dg-warning "BOZ literal" }
1
Warning: A BOZ literal constant at (1) cannot appear as an actual argument in a function reference
boz_extensions.f90:38.22:
b=[t(1+z'1',q(1+z'1',[ z'1',z'1'],z'50CB9F09'),z'50CB9F09')]!{ dg-warning "BOZ" }
1
Warning: BOZ literal constant at (1) cannot appear in a typeless array constructor
boz_extensions.f90:40.16:
i=(/ 1 +z'1', z'50CB9F09' /) ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant at (1) cannot appear in an array constructor
boz_extensions.f90:41.14:
j=(/ 2.0 , z'50CB9F09' /) ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant at (1) cannot appear in an array constructor
boz_extensions.f90:42.16:
k=(/ 1.0+z'1', z'50CB9F09' /) ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant at (1) cannot appear in an array constructor
boz_extensions.f90:143.18:
call sub(Z'1', z'50CB9F09' ) ! { dg-warning "BOZ literal" }
1
Warning: A BOZ literal constant at (1) cannot appear as an actual argument in a function reference
boz_extensions.f90:9.36:
integer, parameter :: p0 = Z'1234'
1
Warning: BOZ literal constant at (1) is neither a data-stmt-constant nor an actual argument to INT, REAL, DBLE, or CMPLX intrinsic function
boz_extensions.f90:11.36:
real,parameter :: r2 = z'50CB9F09'
1
Warning: BOZ literal constant at (1) is neither a data-stmt-constant nor an actual argument to INT, REAL, DBLE, or CMPLX intrinsic function
boz_extensions.f90:32.27:
real, save :: s = 1.0+z'1'
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a numeric operator
boz_extensions.f90:34.48:
data x /t(1+z'1',q(1+z'1',[integer::z'1',z'1'],z'50CB9F09'),z'50CB9F09')/
1
Warning: BOZ literal constant at (1) cannot appear in a structure constructor
boz_extensions.f90:35.48:
data y /t(1+z'1',q(1+z'1',[ z'1',z'1'],z'50CB9F09'),z'50CB9F09')/
1
Warning: BOZ literal constant at (1) cannot appear in a structure constructor
boz_extensions.f90:37.37:
a=[t(1+z'1',q(1+z'1',[integer::z'1',z'1'],z'50CB9F09'),z'50CB9F09')]
1
Warning: BOZ literal constant near (1) cannot appear in an array constructor
boz_extensions.f90:38.37:
b=[t(1+z'1',q(1+z'1',[ z'1',z'1'],z'50CB9F09'),z'50CB9F09')]!{ dg-warning "BOZ" }
1
Warning: BOZ literal constant at (1) cannot appear in an array constructor
boz_extensions.f90:40.16:
i=(/ 1 +z'1', z'50CB9F09' /) ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant at (1) cannot appear in an array constructor
boz_extensions.f90:41.14:
j=(/ 2.0 , z'50CB9F09' /) ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant at (1) cannot appear in an array constructor
boz_extensions.f90:42.16:
k=(/ 1.0+z'1', z'50CB9F09' /) ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant at (1) cannot appear in an array constructor
boz_extensions.f90:43.20:
l=(/ z'50CB9F09' , z'50CB9F09'/)
1
Warning: BOZ literal constant at (1) cannot appear in an array constructor
boz_extensions.f90:45.27:
i2=(/ integer :: 1 +z'1', z'50CB9F09' /)
1
Warning: BOZ literal constant near (1) cannot appear in an array constructor
boz_extensions.f90:46.25:
j2=(/ real :: 2.0 , z'50CB9F09' /)
1
Warning: BOZ literal constant near (1) cannot appear in an array constructor
boz_extensions.f90:47.27:
k2=(/ real :: 1.0+z'1', z'50CB9F09' /)
1
Warning: BOZ literal constant near (1) cannot appear in an array constructor
boz_extensions.f90:143.18:
call sub(Z'1', z'50CB9F09' ) ! { dg-warning "BOZ literal" }
1
Warning: A BOZ literal constant at (1) cannot appear as an actual argument in a subroutine reference
boz_extensions.f90:178.25:
integer :: n(z'f') = [z'1', z'2', z'3', z'4', z'5', z'6', z'7', &
1
Warning: BOZ literal constant at (1) is neither a data-stmt-constant nor an actual argument to INT, REAL, DBLE, or CMPLX intrinsic function
boz_extensions.f90:266.16:
z'50CB9F09' &
1
Warning: BOZ literal constant at (1) cannot appear in a structure constructor
boz_extensions.f90:279.24:
p([n([z'2', 2 ])]) & ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant at (1) cannot appear in an array constructor
boz_extensions.f90:358.16:
z'50CB9F09' &
1
Warning: BOZ literal constant at (1) cannot appear in a structure constructor
boz_extensions.f90:371.24:
p([n([z'50CB9F09', 2.0 ])]) & ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant at (1) cannot appear in an array constructor
boz_extensions.f90:178.18:
integer :: n(z'f') = [z'1', z'2', z'3', z'4', z'5', z'6', z'7', &
1
Warning: BOZ literal constant near (1) cannot appear as a Specification expression
boz_extensions.f90:438.17:
if ( ich < Z'80' ) THEN
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a relational operator
boz_extensions.f90:440.51:
else if ( (ich > ( Z'C0' + 1)) .and. ( ich < Z'E0' )) THEN
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a relational operator
boz_extensions.f90:440.25:
else if ( (ich > ( Z'C0' + 1)) .and. ( ich < Z'E0' )) THEN
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a numeric operator
boz_extensions.f90:442.22:
else if ( ich < Z'F0' ) THEN
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a relational operator
boz_extensions.f90:444.23:
else if ( ich <= Z'F4' ) THEN
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a relational operator
boz_extensions.f90:371.24:
p([n([z'50CB9F09', 2.0 ])]) & ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant at (1) cannot appear in a array constructor
boz_extensions.f90:368.16:
z'1', &
1
Warning: BOZ literal constant at (1) cannot appear in a structure constructor
boz_extensions.f90:373.16:
z'50CB9F09' &
1
Warning: BOZ literal constant at (1) cannot appear in a structure constructor
boz_extensions.f90:366.13:
z'1', &
1
Warning: BOZ literal constant at (1) cannot appear in a structure constructor
boz_extensions.f90:375.13:
z'50CB9F09' &
1
Warning: BOZ literal constant at (1) cannot appear in a structure constructor
boz_extensions.f90:279.24:
p([n([z'2', 2 ])]) & ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant at (1) cannot appear in a array constructor
boz_extensions.f90:276.16:
z'1', &
1
Warning: BOZ literal constant at (1) cannot appear in a structure constructor
boz_extensions.f90:281.16:
z'50CB9F09' &
1
Warning: BOZ literal constant at (1) cannot appear in a structure constructor
boz_extensions.f90:274.13:
z'1', &
1
Warning: BOZ literal constant at (1) cannot appear in a structure constructor
boz_extensions.f90:283.13:
z'50CB9F09' &
1
Warning: BOZ literal constant at (1) cannot appear in a structure constructor
boz_extensions.f90:213.31:
print *, "2007. ", IAND(Z"1",Z"2")
1
Warning: Arguments of iand at (1) cannot both be BOZ literal constants
boz_extensions.f90:214.31:
print *, "2008. ", IEOR(Z"1",Z"2")
1
Warning: Arguments of ieor at (1) cannot both be BOZ literal constants
boz_extensions.f90:216.30:
print *, "2010. ", IOR(Z"1",Z"2")
1
Warning: Arguments of ior at (1) cannot both be BOZ literal constants
boz_extensions.f90:225.13:
if ( IAND(Z"1",Z"2") /= (0 ) ) stop 2007
1
Warning: Arguments of iand at (1) cannot both be BOZ literal constants
boz_extensions.f90:226.13:
if ( IEOR(Z"1",Z"2") /= (3 ) ) stop 2008
1
Warning: Arguments of ieor at (1) cannot both be BOZ literal constants
boz_extensions.f90:228.12:
if ( IOR(Z"1",Z"2") /= (3 ) ) stop 2010
1
Warning: Arguments of ior at (1) cannot both be BOZ literal constants
boz_extensions.f90:192.33:
print *, "1001. z=", z'1' + z'2'
1
Warning: BOZ Literal Constant at (1) cannot appear as operand of binary operator +
boz_extensions.f90:193.39:
print *, "1002. -z=", -z'3'
1
Warning: BOZ literal constant at (1) cannot be an operand of unary operator -
boz_extensions.f90:194.39:
print *, "1003. +z=", +z'3'
1
Warning: BOZ literal constant at (1) cannot be an operand of unary operator +
boz_extensions.f90:196.12:
if ( ( z'1' + z'2' ) /= 3 ) stop 1001
1
Warning: BOZ Literal Constant at (1) cannot appear as operand of binary operator +
boz_extensions.f90:197.18:
if ( ( -z'3' ) /=-3 ) stop 1002
1
Warning: BOZ literal constant at (1) cannot be an operand of unary operator -
boz_extensions.f90:198.18:
if ( ( +z'3' ) /=+3 ) stop 1003
1
Warning: BOZ literal constant at (1) cannot be an operand of unary operator +
boz_extensions.f90:182.12:
do i = z'1', z'e'
1
Warning: BOZ literal constant near (1) cannot appear as a Start,End,Step expression in DO loop
boz_extensions.f90:182.18:
do i = z'1', z'e'
1
Warning: BOZ literal constant near (1) cannot appear as a Start,End,Step expression in DO loop
boz_extensions.f90:163.13:
ls = f(Z'1', z'50CB9F09' ) ! { dg-warning "BOZ literal" }
1
Warning: A BOZ literal constant at (1) cannot appear as an actual argument in a function reference
boz_extensions.f90:163.19:
ls = f(Z'1', z'50CB9F09' ) ! { dg-warning "BOZ literal" }
1
Warning: A BOZ literal constant at (1) cannot appear as an actual argument in a function reference
boz_extensions.f90:37.12:
a=[t(1+z'1',q(1+z'1',[integer::z'1',z'1'],z'50CB9F09'),z'50CB9F09')]
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a numeric operator
boz_extensions.f90:37.21:
a=[t(1+z'1',q(1+z'1',[integer::z'1',z'1'],z'50CB9F09'),z'50CB9F09')]
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a numeric operator
boz_extensions.f90:37.43:
a=[t(1+z'1',q(1+z'1',[integer::z'1',z'1'],z'50CB9F09'),z'50CB9F09')]
1
Warning: BOZ literal constant at (1) cannot appear in a structure constructor
boz_extensions.f90:37.56:
a=[t(1+z'1',q(1+z'1',[integer::z'1',z'1'],z'50CB9F09'),z'50CB9F09')]
1
Warning: BOZ literal constant at (1) cannot appear in a structure constructor
boz_extensions.f90:38.12:
b=[t(1+z'1',q(1+z'1',[ z'1',z'1'],z'50CB9F09'),z'50CB9F09')]!{ dg-warning "BOZ" }
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a numeric operator
boz_extensions.f90:38.21:
b=[t(1+z'1',q(1+z'1',[ z'1',z'1'],z'50CB9F09'),z'50CB9F09')]!{ dg-warning "BOZ" }
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a numeric operator
boz_extensions.f90:38.22:
b=[t(1+z'1',q(1+z'1',[ z'1',z'1'],z'50CB9F09'),z'50CB9F09')]!{ dg-warning "BOZ" }
1
Warning: BOZ literal constant at (1) cannot appear in a typeless array constructor
boz_extensions.f90:38.43:
b=[t(1+z'1',q(1+z'1',[ z'1',z'1'],z'50CB9F09'),z'50CB9F09')]!{ dg-warning "BOZ" }
1
Warning: BOZ literal constant at (1) cannot appear in a structure constructor
boz_extensions.f90:38.56:
b=[t(1+z'1',q(1+z'1',[ z'1',z'1'],z'50CB9F09'),z'50CB9F09')]!{ dg-warning "BOZ" }
1
Warning: BOZ literal constant at (1) cannot appear in a structure constructor
boz_extensions.f90:40.15:
i=(/ 1 +z'1', z'50CB9F09' /) ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a numeric operator
boz_extensions.f90:42.15:
k=(/ 1.0+z'1', z'50CB9F09' /) ! { dg-warning "BOZ literal" }
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a numeric operator
boz_extensions.f90:43.3:
l=(/ z'50CB9F09' , z'50CB9F09'/)
1
Warning: BOZ literal constant at (1) is neither a DATA statement value nor an actual argument of INT/REAL/DBLE/CMPLX intrinsic subprogram
boz_extensions.f90:45.26:
i2=(/ integer :: 1 +z'1', z'50CB9F09' /)
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a numeric operator
boz_extensions.f90:47.26:
k2=(/ real :: 1.0+z'1', z'50CB9F09' /)
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a numeric operator
boz_extensions.f90:82.56:
print *, " 700. z'2' = 1+z'1' (", z'2' == 1+z'1',")"
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a numeric operator
boz_extensions.f90:82.41:
print *, " 700. z'2' = 1+z'1' (", z'2' == 1+z'1',")"
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a relational operator
boz_extensions.f90:135.20:
if ( z'2' /= 1+z'1' ) stop 700
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a numeric operator
boz_extensions.f90:135.6:
if ( z'2' /= 1+z'1' ) stop 700
1
Warning: BOZ literal constant near (1) cannot appear as an operand of a relational operator
boz_extensions.f90:143.12:
call sub(Z'1', z'50CB9F09' ) ! { dg-warning "BOZ literal" }
1
Warning: A BOZ literal constant at (1) cannot appear as an actual argument in a function reference
boz_extensions.f90:143.18:
call sub(Z'1', z'50CB9F09' ) ! { dg-warning "BOZ literal" }
1
Warning: A BOZ literal constant at (1) cannot appear as an actual argument in a function reference
*101. i= 2.00000000 1.35552179E+09
*111. i2= 2.00000000 1.35552179E+09
*201. j= 2.00000000 2.73295790E+10
*211. j2= 2.00000000 2.73295790E+10
*301. k= 1.00000000 2.73295790E+10
*311. k2= 1.00000000 2.73295790E+10
401. l= 2.73295790E+10 2.73295790E+10
501. x%i= 2
502. x%q%i= 2
503. x%q%a(1)= 1
504. x%q%a(2)= 1
505. x%q%r= 2.73295790E+10
506. x%r= 2.73295790E+10
511. x%i= 2
512. y%q%i= 2
y%q%a(1)= 1
y%q%a(2)= 1
515. y%q%r= 2.73295790E+10
516. y%r= 2.73295790E+10
521. a(1)%i= 2
522. a(1)%q%i= 2
a(1)%q%a(1)= 1
a(1)%q%a(2)= 1
525. a(1)%q%r= 2.73295790E+10
526. a(1)%r= 2.73295790E+10
531. b(1)%i= 2
532. b(1)%q%i= 2
* b(1)%q%a(1)= 1
* b(1)%q%a(2)= 1
535. b(1)%q%r= 2.73295790E+10
536. b(1)%r= 2.73295790E+10
700. z'2' = 1+z'1' ( T )
710. rc= 2.73295790E+10
711. r2= 2.73295790E+10
712. p0= 4660
713. s= 1.00000000
*814. si= 1
*815. sr= 2.73295790E+10
*816. si= 1
*817. sr= 2.73295790E+10
918.n(1:2)= 1 2
1001. z= 3
1002. -z= -3
1003. +z= 3
2003. ( 2.73295790E+10, 0.00000000 ) ( 2.73295790E+10, 2.73295790E+10)
2004. 0.30102999566398120
2007. 0
2008. 3
2009. 1
2010. 3
2012. 2.73295790E+10
3001. w(1)%i= 1
3002. w(1)%q%i= 1
w(1)%q%p(1)%i(1)= 2
*w(1)%q%p(1)%i(2)= 2
*w(1)%q%p(2)%i(1)= 2
w(1)%q%p(2)%i(2)= 2
3007. w(1)%q%r= 2.73295790E+10
3008. w(1)%r= 2.73295790E+10
3111. d%i= 1
3112. d%q%i= 1
d%q%p(1)%i(1)= 2
d%q%p(1)%i(2)= 2
d%q%p(2)%i(1)= 2
d%q%p(2)%i(2)= 2
3117. d%q%r= 2.73295790E+10
3118. d%r= 2.73295790E+10
4001. r(1)%i= 1
4002. r(1)%q%i= 1
r(1)%q%p(1)%i(1)= 2.00000000
*r(1)%q%p(1)%i(2)= 1.35552179E+09
*r(1)%q%p(2)%i(1)= 2.73295790E+10
r(1)%q%p(2)%i(2)= 2.00000000
4007. r(1)%q%r= 2.73295790E+10
4008. r(1)%r= 2.73295790E+10
4111. c%i= 1
4112. c%q%i= 1
c%q%p(1)%i(1)= 2.00000000
c%q%p(1)%i(2)= 1.35552179E+09
* c%q%p(2)%i(1)= 2.73295790E+10
c%q%p(2)%i(2)= 2.00000000
4117. c%q%r= 2.73295790E+10
4118. c%r= 2.73295790E+10
*101. i= 2.000000 1.3555218E+09
*111. i2= 2.000000 1.3555218E+09
*201. j= 2.000000 2.7329579E+10
*211. j2= 2.000000 2.7329579E+10
*301. k= 1.000000 2.7329579E+10
*311. k2= 1.000000 2.7329579E+10
401. l= 2.7329579E+10 2.7329579E+10
501. x%i= 2
502. x%q%i= 2
503. x%q%a(1)= 1
504. x%q%a(2)= 1
505. x%q%r= 2.7329579E+10
506. x%r= 2.7329579E+10
511. x%i= 2
512. y%q%i= 2
y%q%a(1)= 1
y%q%a(2)= 1
515. y%q%r= 2.7329579E+10
516. y%r= 2.7329579E+10
521. a(1)%i= 2
522. a(1)%q%i= 2
a(1)%q%a(1)= 1
a(1)%q%a(2)= 1
525. a(1)%q%r= 2.7329579E+10
526. a(1)%r= 2.7329579E+10
531. b(1)%i= 2
532. b(1)%q%i= 2
* b(1)%q%a(1)= 1
* b(1)%q%a(2)= 1
535. b(1)%q%r= 2.7329579E+10
536. b(1)%r= 2.7329579E+10
700. z'2' = 1+z'1' ( T )
710. rc= 2.7329579E+10
711. r2= 2.7329579E+10
712. p0= 4660
713. s= 1.000000
*814. si= 1
*815. sr= 2.7329579E+10
*816. si= 1
*817. sr= 2.7329579E+10
918.n(1:2)= 1 2
1001. z= 3
1002. -z= -3
1003. +z= 00000003
2003. (2.7329579E+10,0.000000) (2.7329579E+10,2.7329579E+10)
2004. 0.3010299956639812
2007. 0
2008. 3
2009. 1
2010. 3
2012. 2.7329579E+10
3001. w(1)%i= 1
3002. w(1)%q%i= 1
w(1)%q%p(1)%i(1)= 2
*w(1)%q%p(1)%i(2)= 2
*w(1)%q%p(2)%i(1)= 2
w(1)%q%p(2)%i(2)= 2
3007. w(1)%q%r= 2.7329579E+10
3008. w(1)%r= 2.7329579E+10
3111. d%i= 1
3112. d%q%i= 1
d%q%p(1)%i(1)= 2
d%q%p(1)%i(2)= 2
d%q%p(2)%i(1)= 2
d%q%p(2)%i(2)= 2
3117. d%q%r= 2.7329579E+10
3118. d%r= 2.7329579E+10
4001. r(1)%i= 1
4002. r(1)%q%i= 1
r(1)%q%p(1)%i(1)= 2.000000
*r(1)%q%p(1)%i(2)= 1.3555218E+09
*r(1)%q%p(2)%i(1)= 2.7329579E+10
r(1)%q%p(2)%i(2)= 2.000000
4007. r(1)%q%r= 2.7329579E+10
4008. r(1)%r= 2.7329579E+10
4111. c%i= 1
4112. c%q%i= 1
c%q%p(1)%i(1)= 2.000000
c%q%p(1)%i(2)= 1.3555218E+09
* c%q%p(2)%i(1)= 2.7329579E+10
c%q%p(2)%i(2)= 2.000000
4117. c%q%r= 2.7329579E+10
4118. c%r= 2.7329579E+10
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment