Re: [Patch, Fortran, F03] PR 84385: Reject invalid SELECT TYPE selector (allocate_with_source_22.f03)

2018-02-14 Thread Janus Weil
2018-02-14 22:30 GMT+01:00 Janus Weil :
> 2018-02-14 22:16 GMT+01:00 Steve Kargl :
>> On Wed, Feb 14, 2018 at 10:10:09PM +0100, Janus Weil wrote:
>>>
>>> Regtests cleanly on x86_64-linux-gnu. Ok for trunk?
>>>
>>
>> Looks okay to me with two question below.
>>
>>> Index: gcc/fortran/match.c
>>> ===
>>> --- gcc/fortran/match.c   (revision 257635)
>>> +++ gcc/fortran/match.c   (working copy)
>>> @@ -6201,9 +6201,10 @@ gfc_match_select_type (void)
>>>|| CLASS_DATA (expr1)->attr.codimension)
>>>&& expr1->ref
>>>&& expr1->ref->type == REF_ARRAY
>>> +  && expr1->ref->u.ar.type == AR_FULL
>>>&& expr1->ref->next == NULL);
>>>
>>> -  /* Check for F03:C811.  */
>>> +  /* Check for F03:C811 (F08:C835).  */
>>
>> Is there a testcase that causes gfortran to emit
>> an error message for violation of F03:C811?  If no,
>> could you commit one?
>
> Good point: Yes, there is such a test case, but it does not cover the
> case that is fixed with the patch. I have now added this case to
> select_type_1.f03, see updated patch in attachment.

I have just committed this updated patch as r257673. Thanks for the
review, Steve.

Cheers,
Janus


Re: [Patch, Fortran, F03] PR 84385: Reject invalid SELECT TYPE selector (allocate_with_source_22.f03)

2018-02-14 Thread Janus Weil
2018-02-14 22:16 GMT+01:00 Steve Kargl :
> On Wed, Feb 14, 2018 at 10:10:09PM +0100, Janus Weil wrote:
>>
>> Regtests cleanly on x86_64-linux-gnu. Ok for trunk?
>>
>
> Looks okay to me with two question below.
>
>> Index: gcc/fortran/match.c
>> ===
>> --- gcc/fortran/match.c   (revision 257635)
>> +++ gcc/fortran/match.c   (working copy)
>> @@ -6201,9 +6201,10 @@ gfc_match_select_type (void)
>>|| CLASS_DATA (expr1)->attr.codimension)
>>&& expr1->ref
>>&& expr1->ref->type == REF_ARRAY
>> +  && expr1->ref->u.ar.type == AR_FULL
>>&& expr1->ref->next == NULL);
>>
>> -  /* Check for F03:C811.  */
>> +  /* Check for F03:C811 (F08:C835).  */
>
> Is there a testcase that causes gfortran to emit
> an error message for violation of F03:C811?  If no,
> could you commit one?

Good point: Yes, there is such a test case, but it does not cover the
case that is fixed with the patch. I have now added this case to
select_type_1.f03, see updated patch in attachment.

Cheers,
Janus
Index: gcc/fortran/match.c
===
--- gcc/fortran/match.c (revision 257671)
+++ gcc/fortran/match.c (working copy)
@@ -6201,9 +6201,10 @@ gfc_match_select_type (void)
 || CLASS_DATA (expr1)->attr.codimension)
 && expr1->ref
 && expr1->ref->type == REF_ARRAY
+&& expr1->ref->u.ar.type == AR_FULL
 && expr1->ref->next == NULL);
 
-  /* Check for F03:C811.  */
+  /* Check for F03:C811 (F08:C835).  */
   if (!expr2 && (expr1->expr_type != EXPR_VARIABLE
 || (!class_array && expr1->ref != NULL)))
 {
Index: gcc/testsuite/gfortran.dg/allocate_with_source_22.f03
===
--- gcc/testsuite/gfortran.dg/allocate_with_source_22.f03   (revision 
257671)
+++ gcc/testsuite/gfortran.dg/allocate_with_source_22.f03   (working copy)
@@ -27,7 +27,7 @@ subroutine test_class()
   ! with -fcheck=bounds.
   if (size(b) /= 4) call abort()
   if (any(b(1:2)%i /= [ 1,2])) call abort()
-  select type (b(1))
+  select type (b1 => b(1))
 class is (tt)
   continue
 class default
Index: gcc/testsuite/gfortran.dg/allocate_with_source_23.f03
===
--- gcc/testsuite/gfortran.dg/allocate_with_source_23.f03   (revision 
257671)
+++ gcc/testsuite/gfortran.dg/allocate_with_source_23.f03   (working copy)
@@ -28,7 +28,7 @@ subroutine test_class_correct()
   allocate(b(1:4), source=a(1))
   if (size(b) /= 4) call abort()
   if (any(b(:)%i /= [ 1,1,1,1])) call abort()
-  select type (b(1))
+  select type (b1 => b(1))
 class is (tt)
   continue
 class default
@@ -46,7 +46,7 @@ subroutine test_class_fail()
   allocate(b(1:4), source=a) ! Fail expected: sizes do not conform
   if (size(b) /= 4) call abort()
   if (any(b(1:2)%i /= [ 1,2])) call abort()
-  select type (b(1))
+  select type (b1 => b(1))
 class is (tt)
   continue
 class default
Index: gcc/testsuite/gfortran.dg/select_type_1.f03
===
--- gcc/testsuite/gfortran.dg/select_type_1.f03 (revision 257671)
+++ gcc/testsuite/gfortran.dg/select_type_1.f03 (working copy)
@@ -23,6 +23,7 @@
   end type
 
   class(t1), pointer :: a => NULL()
+  class(t1), allocatable, dimension(:) :: ca
   type(t1), target :: b
   type(t2), target :: c
   a => b
@@ -32,6 +33,7 @@
 
   select type (3.5)  ! { dg-error "is not a named variable" }
   select type (a%cp) ! { dg-error "is not a named variable" }
+  select type (ca(1))! { dg-error "is not a named variable" }
   select type (b)! { dg-error "Selector shall be polymorphic" }
   end select
 


Re: [Patch, Fortran, F03] PR 84385: Reject invalid SELECT TYPE selector (allocate_with_source_22.f03)

2018-02-14 Thread Steve Kargl
On Wed, Feb 14, 2018 at 10:10:09PM +0100, Janus Weil wrote:
> 
> Regtests cleanly on x86_64-linux-gnu. Ok for trunk?
> 

Looks okay to me with two question below.

> Index: gcc/fortran/match.c
> ===
> --- gcc/fortran/match.c   (revision 257635)
> +++ gcc/fortran/match.c   (working copy)
> @@ -6201,9 +6201,10 @@ gfc_match_select_type (void)
>|| CLASS_DATA (expr1)->attr.codimension)
>&& expr1->ref
>&& expr1->ref->type == REF_ARRAY
> +  && expr1->ref->u.ar.type == AR_FULL
>&& expr1->ref->next == NULL);
>  
> -  /* Check for F03:C811.  */
> +  /* Check for F03:C811 (F08:C835).  */

Is there a testcase that causes gfortran to emit
an error message for violation of F03:C811?  If no,
could you commit one?

-- 
Steve