public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/109223] New: parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails
@ 2023-03-21  1:56 urbanjost at comcast dot net
  2023-03-21  2:42 ` [Bug fortran/109223] " urbanjost at comcast dot net
                   ` (7 more replies)
  0 siblings, 8 replies; 9+ messages in thread
From: urbanjost at comcast dot net @ 2023-03-21  1:56 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109223

            Bug ID: 109223
           Summary: parameters for a type on IMPLICIT do not work. For
                    example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails
           Product: gcc
           Version: 12.2.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: urbanjost at comcast dot net
  Target Milestone: ---

This fails on the IMPLICIT statement

      program testit
      use, intrinsic :: iso_fortran_env, only : qp=>real128
      implicit type(real(kind=qp)) (a-z) ! this should work but fails
      ! surprising (to me) this works, which I thought broke the syntax rules
      ! implicit real(kind=qp) (a-z)       
      type(real(kind=QP)) :: quad
         print '(*(g0))', "kind(long) = ", kind(long), &
         & "; expected is ", kind(quad)
      end program testit

The expected output is

      kind(long) = 16; expected is 16

The "Fortran Standard" implies type parameters are standard:

      8.7      IMPLICIT statement
      1 In a scoping unit, an IMPLICIT statement specifies a type, and possibly
        type parameters, for all implicitly typed data entities whose names
        begin with one of the letters specified in the statement. An IMPLICIT
        NONE statement can indicate that no implicit typing rules are to apply
        in a particular scoping unit, or that external and dummy procedures
        need to be explicitly given the EXTERNAL attribute.

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

* [Bug fortran/109223] parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails
  2023-03-21  1:56 [Bug fortran/109223] New: parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails urbanjost at comcast dot net
@ 2023-03-21  2:42 ` urbanjost at comcast dot net
  2023-03-21  5:37 ` kargl at gcc dot gnu.org
                   ` (6 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: urbanjost at comcast dot net @ 2023-03-21  2:42 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109223

--- Comment #1 from urbanjost at comcast dot net ---
*** Bug 109226 has been marked as a duplicate of this bug. ***

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

* [Bug fortran/109223] parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails
  2023-03-21  1:56 [Bug fortran/109223] New: parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails urbanjost at comcast dot net
  2023-03-21  2:42 ` [Bug fortran/109223] " urbanjost at comcast dot net
@ 2023-03-21  5:37 ` kargl at gcc dot gnu.org
  2023-03-21  5:41 ` kargl at gcc dot gnu.org
                   ` (5 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: kargl at gcc dot gnu.org @ 2023-03-21  5:37 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109223

kargl at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |kargl at gcc dot gnu.org

--- Comment #2 from kargl at gcc dot gnu.org ---
Why do you think it should work?

R863 implicit-stmt       is IMPLICIT implicit-spec-list
                         or IMPLICIT NONE [ ( [ implicit-none-spec-list ] ) ]

R864 implicit-spec       is declaration-type-spec ( letter-spec-list )

R865 letter-spec         is letter [-­ letter ]

R866 implicit-none-spec  is EXTERNAL
                         or TYPE

My reading of the EBNF is that TYPE can only following NONE.
Your code lacks NONE.

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

* [Bug fortran/109223] parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails
  2023-03-21  1:56 [Bug fortran/109223] New: parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails urbanjost at comcast dot net
  2023-03-21  2:42 ` [Bug fortran/109223] " urbanjost at comcast dot net
  2023-03-21  5:37 ` kargl at gcc dot gnu.org
@ 2023-03-21  5:41 ` kargl at gcc dot gnu.org
  2023-03-21 11:57 ` urbanjost at comcast dot net
                   ` (4 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: kargl at gcc dot gnu.org @ 2023-03-21  5:41 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109223

--- Comment #3 from kargl at gcc dot gnu.org ---
(In reply to kargl from comment #2)
> Why do you think it should work?
> 
> R863 implicit-stmt       is IMPLICIT implicit-spec-list
>                          or IMPLICIT NONE [ ( [ implicit-none-spec-list ] ) ]
> 
> R864 implicit-spec       is declaration-type-spec ( letter-spec-list )
> 
> R865 letter-spec         is letter [-­ letter ]
> 
> R866 implicit-none-spec  is EXTERNAL
>                          or TYPE
> 
> My reading of the EBNF is that TYPE can only following NONE.
> Your code lacks NONE.

Replying to self.  In fact, the syntax requires (TYPE) not TYPE.
More importantly TYPE does not take a declaration-type-spec.

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

* [Bug fortran/109223] parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails
  2023-03-21  1:56 [Bug fortran/109223] New: parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails urbanjost at comcast dot net
                   ` (2 preceding siblings ...)
  2023-03-21  5:41 ` kargl at gcc dot gnu.org
@ 2023-03-21 11:57 ` urbanjost at comcast dot net
  2023-03-21 14:57 ` kargl at gcc dot gnu.org
                   ` (3 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: urbanjost at comcast dot net @ 2023-03-21 11:57 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109223

--- Comment #4 from urbanjost at comcast dot net ---
User-defined types work and as I read the ISO standard are supported, and
TYPE(REAL) works; it is only when a parameter is added that it fails; nvfortran
fails for user-defined type declared below it but it works with one defined via
a USE from a module; while gfortran allows the type to be defined after the
use,
but I consider that a nvfortran bug myself. 

Rereading the spec "type" and "type arguments" could be interpreted as meaning
just something like "REAL(KIND=QP) (A)" which does work, but I do not see where
the excludes "TYPE(REAL(QP))", particularly since "TYPE(REAL)" and all other
type declaration syntax appears to work?

program testit
use, intrinsic :: iso_fortran_env, only :
real_kinds,sp=>real32,dp=>real64,qp=>real128
implicit type(null) (a)
implicit type(real) (f)  
implicit real(dp) (d)  
!implicit type(real(kind=qp)) (c) ! <== OK in a declaration, error in IMPLICIT
type null
end type null
! the syntax works for a declaration
type(real)          :: float_default
type(real(kind=sp)) :: float
type(real(kind=dp)) :: long
type(real(kind=qp)) :: quad
end program testit

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

* [Bug fortran/109223] parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails
  2023-03-21  1:56 [Bug fortran/109223] New: parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails urbanjost at comcast dot net
                   ` (3 preceding siblings ...)
  2023-03-21 11:57 ` urbanjost at comcast dot net
@ 2023-03-21 14:57 ` kargl at gcc dot gnu.org
  2023-03-21 19:28 ` sgk at troutmask dot apl.washington.edu
                   ` (2 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: kargl at gcc dot gnu.org @ 2023-03-21 14:57 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109223

--- Comment #5 from kargl at gcc dot gnu.org ---
(In reply to urbanjost from comment #4)
> User-defined types work and as I read the ISO standard are supported, and
> TYPE(REAL) works; it is only when a parameter is added that it fails;
> nvfortran fails for user-defined type declared below it but it works with
> one defined via a USE from a module; while gfortran allows the type to be
> defined after the use,
> but I consider that a nvfortran bug myself. 

Ah, yeah, you're right.  I failed to follow the EBNF in R864.
It seems that gfortran is getting tripped up with the character
following the basic type name, ie., the kind selector part.

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

* [Bug fortran/109223] parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails
  2023-03-21  1:56 [Bug fortran/109223] New: parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails urbanjost at comcast dot net
                   ` (4 preceding siblings ...)
  2023-03-21 14:57 ` kargl at gcc dot gnu.org
@ 2023-03-21 19:28 ` sgk at troutmask dot apl.washington.edu
  2023-03-21 20:05 ` sgk at troutmask dot apl.washington.edu
  2023-03-22  1:26 ` kargl at gcc dot gnu.org
  7 siblings, 0 replies; 9+ messages in thread
From: sgk at troutmask dot apl.washington.edu @ 2023-03-21 19:28 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109223

--- Comment #6 from Steve Kargl <sgk at troutmask dot apl.washington.edu> ---
On Tue, Mar 21, 2023 at 02:57:49PM +0000, kargl at gcc dot gnu.org wrote:
> https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109223
> 
> --- Comment #5 from kargl at gcc dot gnu.org ---
> (In reply to urbanjost from comment #4)
> > User-defined types work and as I read the ISO standard are supported, and
> > TYPE(REAL) works; it is only when a parameter is added that it fails;
> > nvfortran fails for user-defined type declared below it but it works with
> > one defined via a USE from a module; while gfortran allows the type to be
> > defined after the use,
> > but I consider that a nvfortran bug myself. 
> 
> Ah, yeah, you're right.  I failed to follow the EBNF in R864.
> It seems that gfortran is getting tripped up with the character
> following the basic type name, ie., the kind selector part.
> 


So, there is a chunk of code in decl.cc(4682-4689 or so),

  if (implicit_flag == 1)
    {
        if (matched_type && gfc_match_char (')') != MATCH_YES)
          return MATCH_ERROR;

        return MATCH_YES;
    }

causing the problem.  The implicit_flag == 1 conditional was
added in 2004 (revision e5ddaa24beae) to check for 'IMPLICIT
CHARACTER'.  The code block was updated in revision 0fb56814562a
when 'TYPE(intrinsic-type-spec)' was added to gfortran.

I have no idea how this was suppose to work.

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

* [Bug fortran/109223] parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails
  2023-03-21  1:56 [Bug fortran/109223] New: parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails urbanjost at comcast dot net
                   ` (5 preceding siblings ...)
  2023-03-21 19:28 ` sgk at troutmask dot apl.washington.edu
@ 2023-03-21 20:05 ` sgk at troutmask dot apl.washington.edu
  2023-03-22  1:26 ` kargl at gcc dot gnu.org
  7 siblings, 0 replies; 9+ messages in thread
From: sgk at troutmask dot apl.washington.edu @ 2023-03-21 20:05 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109223

--- Comment #7 from Steve Kargl <sgk at troutmask dot apl.washington.edu> ---
On Tue, Mar 21, 2023 at 12:27:58PM -0700, Steve Kargl wrote:
> 
> So, there is a chunk of code in decl.cc(4682-4689 or so),
> 
>   if (implicit_flag == 1)
>     {
> 	if (matched_type && gfc_match_char (')') != MATCH_YES)
> 	  return MATCH_ERROR;
> 
> 	return MATCH_YES;
>     }
> 
> causing the problem.  The implicit_flag == 1 conditional was
> added in 2004 (revision e5ddaa24beae) to check for 'IMPLICIT
> CHARACTER'.  The code block was updated in revision 0fb56814562a
> when 'TYPE(intrinsic-type-spec)' was added to gfortran.
> 
> I have no idea how this was suppose to work.

Well, I figured that out.  The code allows

'implicit real (a-z)'

to be parsed and compiled.  The downside is that it
blocks OP's code.  A simplied code

program testit
!  implicit real    (a-z)           ! Works
!  implicit real(4) (a-z)           ! Works
   implicit type(real(4)) (a-z)     ! Whoops.
   type(real(4)) :: quad
   if (kind(quad) /= 4) stop 1
end program testit

So, 'type(intrinsic-type-spec)' seems to be broken
when placed in 'implicit type(intrinsic-type-spec)'.

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

* [Bug fortran/109223] parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails
  2023-03-21  1:56 [Bug fortran/109223] New: parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails urbanjost at comcast dot net
                   ` (6 preceding siblings ...)
  2023-03-21 20:05 ` sgk at troutmask dot apl.washington.edu
@ 2023-03-22  1:26 ` kargl at gcc dot gnu.org
  7 siblings, 0 replies; 9+ messages in thread
From: kargl at gcc dot gnu.org @ 2023-03-22  1:26 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109223

kargl at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Last reconfirmed|                            |2023-03-22
     Ever confirmed|0                           |1
             Status|UNCONFIRMED                 |NEW
           Priority|P3                          |P4

--- Comment #8 from kargl at gcc dot gnu.org ---
Confirmed.

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

end of thread, other threads:[~2023-03-22  1:26 UTC | newest]

Thread overview: 9+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2023-03-21  1:56 [Bug fortran/109223] New: parameters for a type on IMPLICIT do not work. For example: IMPLICIT TYPE(REAL(KIND=REAL128)) fails urbanjost at comcast dot net
2023-03-21  2:42 ` [Bug fortran/109223] " urbanjost at comcast dot net
2023-03-21  5:37 ` kargl at gcc dot gnu.org
2023-03-21  5:41 ` kargl at gcc dot gnu.org
2023-03-21 11:57 ` urbanjost at comcast dot net
2023-03-21 14:57 ` kargl at gcc dot gnu.org
2023-03-21 19:28 ` sgk at troutmask dot apl.washington.edu
2023-03-21 20:05 ` sgk at troutmask dot apl.washington.edu
2023-03-22  1:26 ` kargl at gcc dot gnu.org

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).