public inbox for fortran@gcc.gnu.org
 help / color / mirror / Atom feed
* [Patch, fortran] PR80156 - [7 Regression] Generic DTIO interface reported missing if public statement preceeds the interface block
@ 2017-03-25 13:28 Paul Richard Thomas
  2017-03-25 14:12 ` Jerry DeLisle
  0 siblings, 1 reply; 3+ messages in thread
From: Paul Richard Thomas @ 2017-03-25 13:28 UTC (permalink / raw)
  To: fortran, gcc-patches

[-- Attachment #1: Type: text/plain, Size: 1114 bytes --]

Dear All,

This regression arose from my patch for PR79382. I have removed the
compile time error but have prevented the ICE by ensuring that the
dtio generic symbol has flavor FL_PROCEDURE. dtio_23.f90 has been
modified to incorporate the test for this PR and not to check for the
now absent error message. At the moment, I do not see how to recover
the error. However, with this patch applied, no incorrect code is
generated and the spurious error is suppressed.

Bootstraps and regtests on FC23/x86_64 - OK for trunk?

Paul

2017-03-25  Paul Thomas  <pault@gcc.gnu.org>

    PR fortran/80156
    PR fortran/79382
    * decl.c (access_attr_decl): Remove the error for an absent
    generic DTIO interface and ensure that symbol has the flavor
    FL_PROCEDURE.

2017-03-25  Paul Thomas  <pault@gcc.gnu.org>

    PR fortran/80156
    PR fortran/79382
    * gfortran.dg/dtio_23.f90 : Remove the dg-error and add the
    testcase for PR80156. Add a main programme that tests that
    the typebound generic is accessible.


-- 
"If you can't explain it simply, you don't understand it well enough"
- Albert Einstein

[-- Attachment #2: submit.diff --]
[-- Type: text/plain, Size: 3514 bytes --]

Index: gcc/fortran/decl.c
===================================================================
*** gcc/fortran/decl.c	(revision 246255)
--- gcc/fortran/decl.c	(working copy)
*************** access_attr_decl (gfc_statement st)
*** 7569,7591 ****
  	case INTERFACE_GENERIC:
  	case INTERFACE_DTIO:
  
- 	  if (type == INTERFACE_DTIO
- 	      && gfc_current_ns->proc_name
- 	      && gfc_current_ns->proc_name->attr.flavor == FL_MODULE)
- 	    {
- 	      gfc_find_symbol (name, gfc_current_ns, 0, &sym);
- 	      if (sym == NULL)
- 		{
- 		  gfc_error ("The GENERIC DTIO INTERFACE at %C is not "
- 			     "present in the MODULE '%s'",
- 			     gfc_current_ns->proc_name->name);
- 		  return MATCH_ERROR;
- 		}
- 	    }
- 
  	  if (gfc_get_symbol (name, NULL, &sym))
  	    goto done;
  
  	  if (!gfc_add_access (&sym->attr,
  			       (st == ST_PUBLIC)
  			       ? ACCESS_PUBLIC : ACCESS_PRIVATE,
--- 7569,7583 ----
  	case INTERFACE_GENERIC:
  	case INTERFACE_DTIO:
  
  	  if (gfc_get_symbol (name, NULL, &sym))
  	    goto done;
  
+ 	  if (type == INTERFACE_DTIO
+ 	      && gfc_current_ns->proc_name
+ 	      && gfc_current_ns->proc_name->attr.flavor == FL_MODULE
+ 	      && sym->attr.flavor == FL_UNKNOWN)
+ 	    sym->attr.flavor = FL_PROCEDURE;
+ 
  	  if (!gfc_add_access (&sym->attr,
  			       (st == ST_PUBLIC)
  			       ? ACCESS_PUBLIC : ACCESS_PRIVATE,
Index: gcc/testsuite/gfortran.dg/dtio_23.f90
===================================================================
*** gcc/testsuite/gfortran.dg/dtio_23.f90	(revision 246255)
--- gcc/testsuite/gfortran.dg/dtio_23.f90	(working copy)
***************
*** 1,8 ****
  ! { dg-do compile }
  !
! ! Test fix for the original in PR79832.
  !
  ! Contributed by Walt Brainerd  <walt.brainerd@gmail.com>
  !
  module dollar_mod
  
--- 1,9 ----
  ! { dg-do compile }
  !
! ! Test fix for the original in PR793822 and for PR80156.
  !
  ! Contributed by Walt Brainerd  <walt.brainerd@gmail.com>
+ ! and (PR80156)  <pedsxing@gmx.net>
  !
  module dollar_mod
  
*************** module dollar_mod
*** 16,22 ****
        generic :: write(formatted) => Write_dollar
     end type dollar_type
  
!    PRIVATE :: write (formatted) ! { dg-error "is not present" }
  
  contains
  
--- 17,23 ----
        generic :: write(formatted) => Write_dollar
     end type dollar_type
  
!    PRIVATE :: write (formatted) ! This used to ICE
  
  contains
  
*************** subroutine Write_dollar &
*** 35,37 ****
--- 36,76 ----
  end subroutine Write_dollar
  
  end module dollar_mod
+ 
+ module pr80156
+ 
+    implicit none
+    private
+ 
+    type, public :: String
+       character(len=:), allocatable :: raw
+    end type
+ 
+    public :: write(unformatted) ! Gave an error due to the first fix for PR79382.
+    interface write(unformatted)
+       module procedure writeUnformatted
+    end interface
+ 
+ contains
+ 
+    subroutine writeUnformatted(self, unit, iostat, iomsg)
+       class(String)   , intent(in)    :: self
+       integer         , intent(in)    :: unit
+       integer         , intent(out)   :: iostat
+       character(len=*), intent(inout) :: iomsg
+ 
+       if (allocated(self%raw)) then
+          write (unit, iostat=iostat, iomsg=iomsg) self%raw
+       else
+          write (unit, iostat=iostat, iomsg=iomsg) ''
+       endif
+ 
+    end subroutine
+ 
+ end module
+ 
+   use dollar_mod
+   type(dollar_type) :: money
+   money = dollar_type(50.0)
+   print '(DT)', money ! Make sure that the typebound generic is accessible.
+ end

^ permalink raw reply	[flat|nested] 3+ messages in thread

* Re: [Patch, fortran] PR80156 - [7 Regression] Generic DTIO interface reported missing if public statement preceeds the interface block
  2017-03-25 13:28 [Patch, fortran] PR80156 - [7 Regression] Generic DTIO interface reported missing if public statement preceeds the interface block Paul Richard Thomas
@ 2017-03-25 14:12 ` Jerry DeLisle
  2017-03-25 17:39   ` Paul Richard Thomas
  0 siblings, 1 reply; 3+ messages in thread
From: Jerry DeLisle @ 2017-03-25 14:12 UTC (permalink / raw)
  To: Paul Richard Thomas, fortran, gcc-patches

On 03/25/2017 06:28 AM, Paul Richard Thomas wrote:
> Dear All,
> 
> This regression arose from my patch for PR79382. I have removed the
> compile time error but have prevented the ICE by ensuring that the
> dtio generic symbol has flavor FL_PROCEDURE. dtio_23.f90 has been
> modified to incorporate the test for this PR and not to check for the
> now absent error message. At the moment, I do not see how to recover
> the error. However, with this patch applied, no incorrect code is
> generated and the spurious error is suppressed.
> 
> Bootstraps and regtests on FC23/x86_64 - OK for trunk?
> 
> Paul
> 

Yes, OK. Thanks Paul.

Jerry

^ permalink raw reply	[flat|nested] 3+ messages in thread

* Re: [Patch, fortran] PR80156 - [7 Regression] Generic DTIO interface reported missing if public statement preceeds the interface block
  2017-03-25 14:12 ` Jerry DeLisle
@ 2017-03-25 17:39   ` Paul Richard Thomas
  0 siblings, 0 replies; 3+ messages in thread
From: Paul Richard Thomas @ 2017-03-25 17:39 UTC (permalink / raw)
  To: Jerry DeLisle; +Cc: fortran, gcc-patches

Hi Jerry,

Committed as revision 246476.

Thanks

Paul

On 25 March 2017 at 14:12, Jerry DeLisle <jvdelisle@charter.net> wrote:
> On 03/25/2017 06:28 AM, Paul Richard Thomas wrote:
>> Dear All,
>>
>> This regression arose from my patch for PR79382. I have removed the
>> compile time error but have prevented the ICE by ensuring that the
>> dtio generic symbol has flavor FL_PROCEDURE. dtio_23.f90 has been
>> modified to incorporate the test for this PR and not to check for the
>> now absent error message. At the moment, I do not see how to recover
>> the error. However, with this patch applied, no incorrect code is
>> generated and the spurious error is suppressed.
>>
>> Bootstraps and regtests on FC23/x86_64 - OK for trunk?
>>
>> Paul
>>
>
> Yes, OK. Thanks Paul.
>
> Jerry



-- 
"If you can't explain it simply, you don't understand it well enough"
- Albert Einstein

^ permalink raw reply	[flat|nested] 3+ messages in thread

end of thread, other threads:[~2017-03-25 17:39 UTC | newest]

Thread overview: 3+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2017-03-25 13:28 [Patch, fortran] PR80156 - [7 Regression] Generic DTIO interface reported missing if public statement preceeds the interface block Paul Richard Thomas
2017-03-25 14:12 ` Jerry DeLisle
2017-03-25 17:39   ` Paul Richard Thomas

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).