Commit 86307f49 by Tobias Burnus Committed by Tobias Burnus

re PR fortran/57035 (TS29113's C535b: Wrongly accept DIMENSION(..) to TRANSFER)

2013-05-21  Tobias Burnus  <burnus@net-b.de>

        PR fortran/57035
        * intrinsic.c (do_check): Add contraint check for
        NO_ARG_CHECK, assumed rank and assumed type.
        * gfortran.texi (NO_ARG_CHECK): Minor wording change,
        allow PRESENT intrinsic.

2013-05-21  Tobias Burnus  <burnus@net-b.de>

        PR fortran/57035
        * gfortran.dg/assumed_type_5.f90: New.
        * gfortran.dg/assumed_rank_1.f90: Comment invalid statement.
        * gfortran.dg/assumed_rank_2.f90: Ditto.
        * gfortran.dg/assumed_type_3.f90: Update dg-error.
        * gfortran.dg/no_arg_check_3.f90: Ditto.

From-SVN: r199158
parent ee49aa34
2013-05-21 Tobias Burnus <burnus@net-b.de>
PR fortran/57035
* intrinsic.c (do_check): Add contraint check for
NO_ARG_CHECK, assumed rank and assumed type.
* gfortran.texi (NO_ARG_CHECK): Minor wording change,
allow PRESENT intrinsic.
2013-05-20 Tobias Burnus <burnus@net-b.de> 2013-05-20 Tobias Burnus <burnus@net-b.de>
PR fortran/48858 PR fortran/48858
......
...@@ -2694,17 +2694,18 @@ with this attribute actual arguments of any type and kind (similar to ...@@ -2694,17 +2694,18 @@ with this attribute actual arguments of any type and kind (similar to
@code{TYPE(*)}), scalars and arrays of any rank (no equivalent @code{TYPE(*)}), scalars and arrays of any rank (no equivalent
in Fortran standard) are accepted. As with @code{TYPE(*)}, the argument in Fortran standard) are accepted. As with @code{TYPE(*)}, the argument
is unlimited polymorphic and no type information is available. is unlimited polymorphic and no type information is available.
Additionally, the same restrictions apply, i.e. the argument may only be Additionally, the argument may only be passed to dummy arguments
passed to dummy arguments with the @code{NO_ARG_CHECK} attribute and as with the @code{NO_ARG_CHECK} attribute and as argument to the
argument to the @code{C_LOC} intrinsic function of the @code{ISO_C_BINDING} @code{PRESENT} intrinsic function and to @code{C_LOC} of the
module. @code{ISO_C_BINDING} module.
Variables with @code{NO_ARG_CHECK} attribute shall be of assumed-type Variables with @code{NO_ARG_CHECK} attribute shall be of assumed-type
(@code{TYPE(*)}; recommended) or of an intrinsic numeric type; they (@code{TYPE(*)}; recommended) or of type @code{INTEGER}, @code{LOGICAL},
shall not have the @code{ALLOCATE}, @code{CODIMENSION}, @code{INTENT(OUT)}, @code{REAL} or @code{COMPLEX}. They shall not have the @code{ALLOCATE},
@code{POINTER} or @code{VALUE} attribute; furthermore, they shall be @code{CODIMENSION}, @code{INTENT(OUT)}, @code{POINTER} or @code{VALUE}
either scalar or of assumed-size (@code{dimension(*)}). As @code{TYPE(*)}, attribute; furthermore, they shall be either scalar or of assumed-size
the @code{NO_ARG_CHECK} attribute requires an explicit interface. (@code{dimension(*)}). As @code{TYPE(*)}, the @code{NO_ARG_CHECK} attribute
requires an explicit interface.
@itemize @itemize
@item @code{NO_ARG_CHECK} -- disable the type, kind and rank checking @item @code{NO_ARG_CHECK} -- disable the type, kind and rank checking
......
...@@ -182,10 +182,66 @@ static bool ...@@ -182,10 +182,66 @@ static bool
do_check (gfc_intrinsic_sym *specific, gfc_actual_arglist *arg) do_check (gfc_intrinsic_sym *specific, gfc_actual_arglist *arg)
{ {
gfc_expr *a1, *a2, *a3, *a4, *a5; gfc_expr *a1, *a2, *a3, *a4, *a5;
gfc_actual_arglist *a;
if (arg == NULL) if (arg == NULL)
return (*specific->check.f0) (); return (*specific->check.f0) ();
/* Check TS29113, C407b for assumed type and C535b for assumed-rank,
and a likewise check for NO_ARG_CHECK. */
for (a = arg; a; a = a->next)
{
if (!a->expr)
continue;
if (a->expr->expr_type == EXPR_VARIABLE
&& (a->expr->symtree->n.sym->attr.ext_attr
& (1 << EXT_ATTR_NO_ARG_CHECK))
&& specific->id != GFC_ISYM_C_LOC
&& specific->id != GFC_ISYM_PRESENT)
{
gfc_error ("Variable with NO_ARG_CHECK attribute at %L is only "
"permitted as argument to the intrinsic functions "
"C_LOC and PRESENT", &a->expr->where);
return false;
}
else if (a->expr->ts.type == BT_ASSUMED
&& specific->id != GFC_ISYM_LBOUND
&& specific->id != GFC_ISYM_PRESENT
&& specific->id != GFC_ISYM_RANK
&& specific->id != GFC_ISYM_SHAPE
&& specific->id != GFC_ISYM_SIZE
&& specific->id != GFC_ISYM_UBOUND
&& specific->id != GFC_ISYM_C_LOC)
{
gfc_error ("Assumed-type argument at %L is not permitted as actual"
" argument to the intrinsic %s", &a->expr->where,
gfc_current_intrinsic);
return false;
}
else if (a->expr->ts.type == BT_ASSUMED && a != arg)
{
gfc_error ("Assumed-type argument at %L is only permitted as "
"first actual argument to the intrinsic %s",
&a->expr->where, gfc_current_intrinsic);
return false;
}
if (a->expr->rank == -1 && !specific->inquiry)
{
gfc_error ("Assumed-rank argument at %L is only permitted as actual "
"argument to intrinsic inquiry functions",
&a->expr->where);
return false;
}
if (a->expr->rank == -1 && arg != a)
{
gfc_error ("Assumed-rank argument at %L is only permitted as first "
"actual argument to the intrinsic inquiry function %s",
&a->expr->where, gfc_current_intrinsic);
return false;
}
}
a1 = arg->expr; a1 = arg->expr;
arg = arg->next; arg = arg->next;
if (arg == NULL) if (arg == NULL)
......
2013-05-21 Tobias Burnus <burnus@net-b.de>
PR fortran/57035
* gfortran.dg/assumed_type_5.f90: New.
* gfortran.dg/assumed_rank_1.f90: Comment invalid statement.
* gfortran.dg/assumed_rank_2.f90: Ditto.
* gfortran.dg/assumed_type_3.f90: Update dg-error.
* gfortran.dg/no_arg_check_3.f90: Ditto.
2013-05-21 Jakub Jelinek <jakub@redhat.com> 2013-05-21 Jakub Jelinek <jakub@redhat.com>
PR tree-optimization/57331 PR tree-optimization/57331
......
...@@ -52,11 +52,11 @@ contains ...@@ -52,11 +52,11 @@ contains
subroutine bar(a,b, prsnt) subroutine bar(a,b, prsnt)
integer, pointer, optional, intent(in) :: a(..),b(..) integer, pointer, optional, intent(in) :: a(..),b(..)
logical, value :: prsnt logical, value :: prsnt
! The following is not valid, but it goes past the constraint check
! Technically, it could be allowed and might be in Fortran 2015:
if (.not. associated(a)) call abort() if (.not. associated(a)) call abort()
if (present(b)) then if (present(b)) then
if (.not. associated(a,b)) call abort() ! The following is not valid.
! Technically, it could be allowed and might be in Fortran 2015:
! if (.not. associated(a,b)) call abort()
else else
if (.not. associated(a)) call abort() if (.not. associated(a)) call abort()
end if end if
......
...@@ -45,11 +45,11 @@ contains ...@@ -45,11 +45,11 @@ contains
subroutine bar(a,b, prsnt) subroutine bar(a,b, prsnt)
integer, pointer, optional, intent(in) :: a(..),b(..) integer, pointer, optional, intent(in) :: a(..),b(..)
logical, value :: prsnt logical, value :: prsnt
! The following is not valid, but it goes past the constraint check
! Technically, it could be allowed and might be in Fortran 2015:
if (.not. associated(a)) call abort() if (.not. associated(a)) call abort()
if (present(b)) then if (present(b)) then
if (.not. associated(a,b)) call abort() ! The following is not valid
! Technically, it could be allowed and might be in Fortran 2015:
! if (.not. associated(a,b)) call abort()
else else
if (.not. associated(a)) call abort() if (.not. associated(a)) call abort()
end if end if
......
...@@ -110,7 +110,7 @@ end subroutine twelf ...@@ -110,7 +110,7 @@ end subroutine twelf
subroutine thirteen(x, y) subroutine thirteen(x, y)
type(*) :: x type(*) :: x
integer :: y(:) integer :: y(:)
print *, ubound(y, dim=x) ! { dg-error "must be INTEGER" } print *, ubound(y, dim=x) ! { dg-error "Assumed-type argument at .1. is only permitted as first actual argument to the intrinsic ubound" }
end subroutine thirteen end subroutine thirteen
subroutine fourteen(x) subroutine fourteen(x)
......
! { dg-do compile }
!
! PR fortran/57035
!
!
subroutine assumed_rank (a)
use iso_c_binding
integer, intent(in), target :: a(..)
integer :: c(1:4)
type(c_ptr) :: xx
c = ubound(c,a) ! { dg-error "Assumed-rank argument at .1. is only permitted as first actual argument to the intrinsic inquiry function ubound" }
c = transfer(a,1) ! { dg-error "Assumed-rank argument at .1. is only permitted as actual argument to intrinsic inquiry functions" }
xx = c_loc(a)
end subroutine
subroutine assumed_type (a)
use iso_c_binding
type(*), intent(in), target :: a
integer :: c(1:4)
type(c_ptr) :: xx
c = ubound(c,a) ! { dg-error "Assumed-type argument at .1. is only permitted as first actual argument to the intrinsic ubound" }
c = transfer(a,1) ! { dg-error "Assumed-type argument at .1. is not permitted as actual argument to the intrinsic transfer" }
xx = c_loc(a)
end subroutine
subroutine no_arg_check (a)
use iso_c_binding
integer, intent(in), target :: a
!gcc$ attributes no_arg_check :: a
integer :: c(1:4)
type(c_ptr) :: xx
c = ubound(c,a) ! { dg-error "Variable with NO_ARG_CHECK attribute at .1. is only permitted as argument to the intrinsic functions C_LOC and PRESENT" }
c = transfer(a,1) ! { dg-error "Variable with NO_ARG_CHECK attribute at .1. is only permitted as argument to the intrinsic functions C_LOC and PRESENT" }
xx = c_loc(a)
end subroutine
...@@ -114,7 +114,7 @@ subroutine thirteen(x, y) ...@@ -114,7 +114,7 @@ subroutine thirteen(x, y)
!GCC$ attributes NO_ARG_CHECK :: x !GCC$ attributes NO_ARG_CHECK :: x
integer :: x integer :: x
integer :: y(:) integer :: y(:)
print *, ubound(y, dim=x) ! { dg-error "must be INTEGER" } print *, ubound(y, dim=x) ! { dg-error "Variable with NO_ARG_CHECK attribute at .1. is only permitted as argument to the intrinsic functions C_LOC and PRESENT" }
end subroutine thirteen end subroutine thirteen
subroutine fourteen(x) subroutine fourteen(x)
......
...@@ -10,9 +10,9 @@ subroutine foo(x, y) ...@@ -10,9 +10,9 @@ subroutine foo(x, y)
integer(8) :: ii integer(8) :: ii
procedure() :: proc procedure() :: proc
ii = sizeof (x) ! { dg-error "shall not be TYPE\(.\)" } ii = sizeof (x) ! { dg-error "Assumed-type argument at .1. is not permitted as actual argument to the intrinsic sizeof" }
ii = c_sizeof (x) ! { dg-error "shall not be TYPE\(.\)" } ii = c_sizeof (x) ! { dg-error "Assumed-type argument at .1. is not permitted as actual argument to the intrinsic c_sizeof" }
ii = storage_size (x) ! { dg-error "shall not be TYPE\(.\)" } ii = storage_size (x) ! { dg-error "Assumed-type argument at .1. is not permitted as actual argument to the intrinsic storage_size" }
ii = sizeof (y) ! { dg-error "shall not be an assumed-size array" } ii = sizeof (y) ! { dg-error "shall not be an assumed-size array" }
ii = c_sizeof (y) ! { dg-error "shall not be an assumed-size array" } ii = c_sizeof (y) ! { dg-error "shall not be an assumed-size array" }
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment