2020-05-12 02:38:53 +08:00
|
|
|
! RUN: %S/test_modfile.sh %s %t %f18
|
2018-07-20 04:28:24 +08:00
|
|
|
! Check modfile generation for generic interfaces
|
2019-08-21 03:05:44 +08:00
|
|
|
module m1
|
2018-07-20 04:28:24 +08:00
|
|
|
interface foo
|
2019-03-19 02:48:02 +08:00
|
|
|
real function s1(x,y)
|
[flang] Handle alternative names for relational operators
10.1.6.2 says:
> The operators <, <=, >, >=, ==, and /= always have the same interpretations
> as the operators .LT., .LE., .GT., .GE., .EQ., and .NE., respectively.
That means we have to treat `operator(<)` like `operator(.lt.)`,
for example. `<>` is a third alias for `.NE.`.
We can't just choose always to use one form (e.g. replacing `operator(.lt.)`
with `operator(<)`). This is because all symbols names are `CharBlock`s
referring to the cooked character stream so that they have proper source
provenance. Also, if a user prefers one style and uses it consistently,
that's the form they should see in messages.
So the fix is to use whatever form is found in the source, but also to
look up symbols by the other names when necessary. To assist this, add
`GenericSpecInfo::GetAllNames()` to return all of the names of a generic
spec. Each place a generic spec can occur we have to use these to look
for the symbol.
Also reorganize the `AddUse()` overloads to work with this change.
Fixes flang-compiler/f18#746.
Original-commit: flang-compiler/f18@7f06f175d5033f0728f67b1be25ecd53df1f8de5
Reviewed-on: https://github.com/flang-compiler/f18/pull/752
2019-09-18 07:57:09 +08:00
|
|
|
real, intent(in) :: x
|
|
|
|
logical, intent(in) :: y
|
2019-03-19 02:48:02 +08:00
|
|
|
end function
|
|
|
|
complex function s2(x,y)
|
[flang] Handle alternative names for relational operators
10.1.6.2 says:
> The operators <, <=, >, >=, ==, and /= always have the same interpretations
> as the operators .LT., .LE., .GT., .GE., .EQ., and .NE., respectively.
That means we have to treat `operator(<)` like `operator(.lt.)`,
for example. `<>` is a third alias for `.NE.`.
We can't just choose always to use one form (e.g. replacing `operator(.lt.)`
with `operator(<)`). This is because all symbols names are `CharBlock`s
referring to the cooked character stream so that they have proper source
provenance. Also, if a user prefers one style and uses it consistently,
that's the form they should see in messages.
So the fix is to use whatever form is found in the source, but also to
look up symbols by the other names when necessary. To assist this, add
`GenericSpecInfo::GetAllNames()` to return all of the names of a generic
spec. Each place a generic spec can occur we have to use these to look
for the symbol.
Also reorganize the `AddUse()` overloads to work with this change.
Fixes flang-compiler/f18#746.
Original-commit: flang-compiler/f18@7f06f175d5033f0728f67b1be25ecd53df1f8de5
Reviewed-on: https://github.com/flang-compiler/f18/pull/752
2019-09-18 07:57:09 +08:00
|
|
|
complex, intent(in) :: x
|
|
|
|
logical, intent(in) :: y
|
2019-03-19 02:48:02 +08:00
|
|
|
end function
|
2018-07-20 04:28:24 +08:00
|
|
|
end interface
|
2019-03-20 04:38:54 +08:00
|
|
|
generic :: operator ( + ) => s1, s2
|
[flang] Handle alternative names for relational operators
10.1.6.2 says:
> The operators <, <=, >, >=, ==, and /= always have the same interpretations
> as the operators .LT., .LE., .GT., .GE., .EQ., and .NE., respectively.
That means we have to treat `operator(<)` like `operator(.lt.)`,
for example. `<>` is a third alias for `.NE.`.
We can't just choose always to use one form (e.g. replacing `operator(.lt.)`
with `operator(<)`). This is because all symbols names are `CharBlock`s
referring to the cooked character stream so that they have proper source
provenance. Also, if a user prefers one style and uses it consistently,
that's the form they should see in messages.
So the fix is to use whatever form is found in the source, but also to
look up symbols by the other names when necessary. To assist this, add
`GenericSpecInfo::GetAllNames()` to return all of the names of a generic
spec. Each place a generic spec can occur we have to use these to look
for the symbol.
Also reorganize the `AddUse()` overloads to work with this change.
Fixes flang-compiler/f18#746.
Original-commit: flang-compiler/f18@7f06f175d5033f0728f67b1be25ecd53df1f8de5
Reviewed-on: https://github.com/flang-compiler/f18/pull/752
2019-09-18 07:57:09 +08:00
|
|
|
interface operator ( /= )
|
|
|
|
logical function f1(x, y)
|
|
|
|
real, intent(in) :: x
|
|
|
|
logical, intent(in) :: y
|
|
|
|
end function
|
|
|
|
end interface
|
|
|
|
interface
|
|
|
|
logical function f2(x, y)
|
|
|
|
complex, intent(in) :: x
|
|
|
|
logical, intent(in) :: y
|
|
|
|
end function
|
|
|
|
logical function f3(x, y)
|
|
|
|
integer, intent(in) :: x
|
|
|
|
logical, intent(in) :: y
|
|
|
|
end function
|
|
|
|
end interface
|
|
|
|
generic :: operator(.ne.) => f2
|
|
|
|
generic :: operator(<>) => f3
|
|
|
|
private :: operator( .ne. )
|
2018-07-20 04:28:24 +08:00
|
|
|
interface bar
|
|
|
|
procedure :: s1
|
|
|
|
procedure :: s2
|
|
|
|
procedure :: s3
|
|
|
|
procedure :: s4
|
|
|
|
end interface
|
2019-03-20 04:38:54 +08:00
|
|
|
interface operator( .bar.)
|
2019-03-19 02:48:02 +08:00
|
|
|
procedure :: s1
|
|
|
|
procedure :: s2
|
|
|
|
procedure :: s3
|
|
|
|
procedure :: s4
|
|
|
|
end interface
|
2018-07-20 04:28:24 +08:00
|
|
|
contains
|
2019-03-19 02:48:02 +08:00
|
|
|
logical function s3(x,y)
|
[flang] Handle alternative names for relational operators
10.1.6.2 says:
> The operators <, <=, >, >=, ==, and /= always have the same interpretations
> as the operators .LT., .LE., .GT., .GE., .EQ., and .NE., respectively.
That means we have to treat `operator(<)` like `operator(.lt.)`,
for example. `<>` is a third alias for `.NE.`.
We can't just choose always to use one form (e.g. replacing `operator(.lt.)`
with `operator(<)`). This is because all symbols names are `CharBlock`s
referring to the cooked character stream so that they have proper source
provenance. Also, if a user prefers one style and uses it consistently,
that's the form they should see in messages.
So the fix is to use whatever form is found in the source, but also to
look up symbols by the other names when necessary. To assist this, add
`GenericSpecInfo::GetAllNames()` to return all of the names of a generic
spec. Each place a generic spec can occur we have to use these to look
for the symbol.
Also reorganize the `AddUse()` overloads to work with this change.
Fixes flang-compiler/f18#746.
Original-commit: flang-compiler/f18@7f06f175d5033f0728f67b1be25ecd53df1f8de5
Reviewed-on: https://github.com/flang-compiler/f18/pull/752
2019-09-18 07:57:09 +08:00
|
|
|
logical, intent(in) :: x,y
|
2019-03-19 02:48:02 +08:00
|
|
|
end function
|
|
|
|
integer function s4(x,y)
|
[flang] Handle alternative names for relational operators
10.1.6.2 says:
> The operators <, <=, >, >=, ==, and /= always have the same interpretations
> as the operators .LT., .LE., .GT., .GE., .EQ., and .NE., respectively.
That means we have to treat `operator(<)` like `operator(.lt.)`,
for example. `<>` is a third alias for `.NE.`.
We can't just choose always to use one form (e.g. replacing `operator(.lt.)`
with `operator(<)`). This is because all symbols names are `CharBlock`s
referring to the cooked character stream so that they have proper source
provenance. Also, if a user prefers one style and uses it consistently,
that's the form they should see in messages.
So the fix is to use whatever form is found in the source, but also to
look up symbols by the other names when necessary. To assist this, add
`GenericSpecInfo::GetAllNames()` to return all of the names of a generic
spec. Each place a generic spec can occur we have to use these to look
for the symbol.
Also reorganize the `AddUse()` overloads to work with this change.
Fixes flang-compiler/f18#746.
Original-commit: flang-compiler/f18@7f06f175d5033f0728f67b1be25ecd53df1f8de5
Reviewed-on: https://github.com/flang-compiler/f18/pull/752
2019-09-18 07:57:09 +08:00
|
|
|
integer, intent(in) :: x,y
|
2019-03-19 02:48:02 +08:00
|
|
|
end function
|
2018-07-20 04:28:24 +08:00
|
|
|
end
|
2019-08-21 03:05:44 +08:00
|
|
|
!Expect: m1.mod
|
|
|
|
!module m1
|
2019-08-01 06:53:46 +08:00
|
|
|
! interface foo
|
|
|
|
! procedure::s1
|
|
|
|
! procedure::s2
|
|
|
|
! end interface
|
2018-07-20 04:28:24 +08:00
|
|
|
! interface
|
2019-03-19 02:48:02 +08:00
|
|
|
! function s1(x,y)
|
[flang] Handle alternative names for relational operators
10.1.6.2 says:
> The operators <, <=, >, >=, ==, and /= always have the same interpretations
> as the operators .LT., .LE., .GT., .GE., .EQ., and .NE., respectively.
That means we have to treat `operator(<)` like `operator(.lt.)`,
for example. `<>` is a third alias for `.NE.`.
We can't just choose always to use one form (e.g. replacing `operator(.lt.)`
with `operator(<)`). This is because all symbols names are `CharBlock`s
referring to the cooked character stream so that they have proper source
provenance. Also, if a user prefers one style and uses it consistently,
that's the form they should see in messages.
So the fix is to use whatever form is found in the source, but also to
look up symbols by the other names when necessary. To assist this, add
`GenericSpecInfo::GetAllNames()` to return all of the names of a generic
spec. Each place a generic spec can occur we have to use these to look
for the symbol.
Also reorganize the `AddUse()` overloads to work with this change.
Fixes flang-compiler/f18#746.
Original-commit: flang-compiler/f18@7f06f175d5033f0728f67b1be25ecd53df1f8de5
Reviewed-on: https://github.com/flang-compiler/f18/pull/752
2019-09-18 07:57:09 +08:00
|
|
|
! real(4),intent(in)::x
|
|
|
|
! logical(4),intent(in)::y
|
2019-08-13 04:06:59 +08:00
|
|
|
! real(4)::s1
|
2018-07-20 04:28:24 +08:00
|
|
|
! end
|
|
|
|
! end interface
|
|
|
|
! interface
|
2019-03-19 02:48:02 +08:00
|
|
|
! function s2(x,y)
|
[flang] Handle alternative names for relational operators
10.1.6.2 says:
> The operators <, <=, >, >=, ==, and /= always have the same interpretations
> as the operators .LT., .LE., .GT., .GE., .EQ., and .NE., respectively.
That means we have to treat `operator(<)` like `operator(.lt.)`,
for example. `<>` is a third alias for `.NE.`.
We can't just choose always to use one form (e.g. replacing `operator(.lt.)`
with `operator(<)`). This is because all symbols names are `CharBlock`s
referring to the cooked character stream so that they have proper source
provenance. Also, if a user prefers one style and uses it consistently,
that's the form they should see in messages.
So the fix is to use whatever form is found in the source, but also to
look up symbols by the other names when necessary. To assist this, add
`GenericSpecInfo::GetAllNames()` to return all of the names of a generic
spec. Each place a generic spec can occur we have to use these to look
for the symbol.
Also reorganize the `AddUse()` overloads to work with this change.
Fixes flang-compiler/f18#746.
Original-commit: flang-compiler/f18@7f06f175d5033f0728f67b1be25ecd53df1f8de5
Reviewed-on: https://github.com/flang-compiler/f18/pull/752
2019-09-18 07:57:09 +08:00
|
|
|
! complex(4),intent(in)::x
|
|
|
|
! logical(4),intent(in)::y
|
2019-08-13 04:06:59 +08:00
|
|
|
! complex(4)::s2
|
2018-07-20 04:28:24 +08:00
|
|
|
! end
|
|
|
|
! end interface
|
2019-08-01 06:53:46 +08:00
|
|
|
! interface operator(+)
|
|
|
|
! procedure::s1
|
|
|
|
! procedure::s2
|
|
|
|
! end interface
|
[flang] Handle alternative names for relational operators
10.1.6.2 says:
> The operators <, <=, >, >=, ==, and /= always have the same interpretations
> as the operators .LT., .LE., .GT., .GE., .EQ., and .NE., respectively.
That means we have to treat `operator(<)` like `operator(.lt.)`,
for example. `<>` is a third alias for `.NE.`.
We can't just choose always to use one form (e.g. replacing `operator(.lt.)`
with `operator(<)`). This is because all symbols names are `CharBlock`s
referring to the cooked character stream so that they have proper source
provenance. Also, if a user prefers one style and uses it consistently,
that's the form they should see in messages.
So the fix is to use whatever form is found in the source, but also to
look up symbols by the other names when necessary. To assist this, add
`GenericSpecInfo::GetAllNames()` to return all of the names of a generic
spec. Each place a generic spec can occur we have to use these to look
for the symbol.
Also reorganize the `AddUse()` overloads to work with this change.
Fixes flang-compiler/f18#746.
Original-commit: flang-compiler/f18@7f06f175d5033f0728f67b1be25ecd53df1f8de5
Reviewed-on: https://github.com/flang-compiler/f18/pull/752
2019-09-18 07:57:09 +08:00
|
|
|
! interface operator(/=)
|
|
|
|
! procedure::f1
|
|
|
|
! procedure::f2
|
|
|
|
! procedure::f3
|
|
|
|
! end interface
|
|
|
|
! private::operator(/=)
|
|
|
|
! interface
|
|
|
|
! function f1(x,y)
|
|
|
|
! real(4),intent(in)::x
|
|
|
|
! logical(4),intent(in)::y
|
|
|
|
! logical(4)::f1
|
|
|
|
! end
|
|
|
|
! end interface
|
|
|
|
! interface
|
|
|
|
! function f2(x,y)
|
|
|
|
! complex(4),intent(in)::x
|
|
|
|
! logical(4),intent(in)::y
|
|
|
|
! logical(4)::f2
|
|
|
|
! end
|
|
|
|
! end interface
|
|
|
|
! interface
|
|
|
|
! function f3(x,y)
|
|
|
|
! integer(4),intent(in)::x
|
|
|
|
! logical(4),intent(in)::y
|
|
|
|
! logical(4)::f3
|
|
|
|
! end
|
|
|
|
! end interface
|
2019-08-01 06:53:46 +08:00
|
|
|
! interface bar
|
|
|
|
! procedure::s1
|
|
|
|
! procedure::s2
|
|
|
|
! procedure::s3
|
|
|
|
! procedure::s4
|
|
|
|
! end interface
|
|
|
|
! interface operator(.bar.)
|
|
|
|
! procedure::s1
|
|
|
|
! procedure::s2
|
|
|
|
! procedure::s3
|
|
|
|
! procedure::s4
|
|
|
|
! end interface
|
2018-07-20 04:28:24 +08:00
|
|
|
!contains
|
2019-03-19 02:48:02 +08:00
|
|
|
! function s3(x,y)
|
[flang] Handle alternative names for relational operators
10.1.6.2 says:
> The operators <, <=, >, >=, ==, and /= always have the same interpretations
> as the operators .LT., .LE., .GT., .GE., .EQ., and .NE., respectively.
That means we have to treat `operator(<)` like `operator(.lt.)`,
for example. `<>` is a third alias for `.NE.`.
We can't just choose always to use one form (e.g. replacing `operator(.lt.)`
with `operator(<)`). This is because all symbols names are `CharBlock`s
referring to the cooked character stream so that they have proper source
provenance. Also, if a user prefers one style and uses it consistently,
that's the form they should see in messages.
So the fix is to use whatever form is found in the source, but also to
look up symbols by the other names when necessary. To assist this, add
`GenericSpecInfo::GetAllNames()` to return all of the names of a generic
spec. Each place a generic spec can occur we have to use these to look
for the symbol.
Also reorganize the `AddUse()` overloads to work with this change.
Fixes flang-compiler/f18#746.
Original-commit: flang-compiler/f18@7f06f175d5033f0728f67b1be25ecd53df1f8de5
Reviewed-on: https://github.com/flang-compiler/f18/pull/752
2019-09-18 07:57:09 +08:00
|
|
|
! logical(4),intent(in)::x
|
|
|
|
! logical(4),intent(in)::y
|
2019-08-13 04:06:59 +08:00
|
|
|
! logical(4)::s3
|
2018-07-20 04:28:24 +08:00
|
|
|
! end
|
2019-03-19 02:48:02 +08:00
|
|
|
! function s4(x,y)
|
[flang] Handle alternative names for relational operators
10.1.6.2 says:
> The operators <, <=, >, >=, ==, and /= always have the same interpretations
> as the operators .LT., .LE., .GT., .GE., .EQ., and .NE., respectively.
That means we have to treat `operator(<)` like `operator(.lt.)`,
for example. `<>` is a third alias for `.NE.`.
We can't just choose always to use one form (e.g. replacing `operator(.lt.)`
with `operator(<)`). This is because all symbols names are `CharBlock`s
referring to the cooked character stream so that they have proper source
provenance. Also, if a user prefers one style and uses it consistently,
that's the form they should see in messages.
So the fix is to use whatever form is found in the source, but also to
look up symbols by the other names when necessary. To assist this, add
`GenericSpecInfo::GetAllNames()` to return all of the names of a generic
spec. Each place a generic spec can occur we have to use these to look
for the symbol.
Also reorganize the `AddUse()` overloads to work with this change.
Fixes flang-compiler/f18#746.
Original-commit: flang-compiler/f18@7f06f175d5033f0728f67b1be25ecd53df1f8de5
Reviewed-on: https://github.com/flang-compiler/f18/pull/752
2019-09-18 07:57:09 +08:00
|
|
|
! integer(4),intent(in)::x
|
|
|
|
! integer(4),intent(in)::y
|
2019-08-13 04:06:59 +08:00
|
|
|
! integer(4)::s4
|
2018-07-20 04:28:24 +08:00
|
|
|
! end
|
|
|
|
!end
|
2019-02-27 05:08:59 +08:00
|
|
|
|
2019-08-21 03:05:44 +08:00
|
|
|
module m1b
|
|
|
|
use m1
|
|
|
|
end
|
|
|
|
!Expect: m1b.mod
|
|
|
|
!module m1b
|
|
|
|
! use m1,only:foo
|
|
|
|
! use m1,only:s1
|
|
|
|
! use m1,only:s2
|
|
|
|
! use m1,only:operator(+)
|
[flang] Handle alternative names for relational operators
10.1.6.2 says:
> The operators <, <=, >, >=, ==, and /= always have the same interpretations
> as the operators .LT., .LE., .GT., .GE., .EQ., and .NE., respectively.
That means we have to treat `operator(<)` like `operator(.lt.)`,
for example. `<>` is a third alias for `.NE.`.
We can't just choose always to use one form (e.g. replacing `operator(.lt.)`
with `operator(<)`). This is because all symbols names are `CharBlock`s
referring to the cooked character stream so that they have proper source
provenance. Also, if a user prefers one style and uses it consistently,
that's the form they should see in messages.
So the fix is to use whatever form is found in the source, but also to
look up symbols by the other names when necessary. To assist this, add
`GenericSpecInfo::GetAllNames()` to return all of the names of a generic
spec. Each place a generic spec can occur we have to use these to look
for the symbol.
Also reorganize the `AddUse()` overloads to work with this change.
Fixes flang-compiler/f18#746.
Original-commit: flang-compiler/f18@7f06f175d5033f0728f67b1be25ecd53df1f8de5
Reviewed-on: https://github.com/flang-compiler/f18/pull/752
2019-09-18 07:57:09 +08:00
|
|
|
! use m1,only:f1
|
|
|
|
! use m1,only:f2
|
|
|
|
! use m1,only:f3
|
2019-08-21 03:05:44 +08:00
|
|
|
! use m1,only:bar
|
|
|
|
! use m1,only:operator(.bar.)
|
|
|
|
! use m1,only:s3
|
|
|
|
! use m1,only:s4
|
|
|
|
!end
|
|
|
|
|
|
|
|
module m1c
|
|
|
|
use m1, only: myfoo => foo
|
|
|
|
use m1, only: operator(.bar.)
|
|
|
|
use m1, only: operator(.mybar.) => operator(.bar.)
|
|
|
|
use m1, only: operator(+)
|
|
|
|
end
|
|
|
|
!Expect: m1c.mod
|
|
|
|
!module m1c
|
|
|
|
! use m1,only:myfoo=>foo
|
|
|
|
! use m1,only:operator(.bar.)
|
|
|
|
! use m1,only:operator(.mybar.)=>operator(.bar.)
|
|
|
|
! use m1,only:operator(+)
|
|
|
|
!end
|
|
|
|
|
2019-06-15 06:04:13 +08:00
|
|
|
module m2
|
|
|
|
interface foo
|
|
|
|
procedure foo
|
|
|
|
end interface
|
|
|
|
contains
|
|
|
|
complex function foo()
|
|
|
|
foo = 1.0
|
|
|
|
end
|
|
|
|
end
|
2019-02-27 05:08:59 +08:00
|
|
|
!Expect: m2.mod
|
|
|
|
!module m2
|
2019-08-01 06:53:46 +08:00
|
|
|
! interface foo
|
|
|
|
! procedure::foo
|
|
|
|
! end interface
|
2019-02-27 05:08:59 +08:00
|
|
|
!contains
|
|
|
|
! function foo()
|
|
|
|
! complex(4)::foo
|
|
|
|
! end
|
|
|
|
!end
|
2019-06-15 06:04:13 +08:00
|
|
|
|
2019-08-01 06:53:46 +08:00
|
|
|
module m2b
|
|
|
|
type :: foo
|
|
|
|
real :: x
|
|
|
|
end type
|
|
|
|
interface foo
|
|
|
|
end interface
|
|
|
|
private :: bar
|
|
|
|
interface bar
|
|
|
|
end interface
|
|
|
|
end
|
|
|
|
!Expect: m2b.mod
|
|
|
|
!module m2b
|
|
|
|
! interface foo
|
|
|
|
! end interface
|
|
|
|
! type::foo
|
|
|
|
! real(4)::x
|
|
|
|
! end type
|
|
|
|
! interface bar
|
|
|
|
! end interface
|
|
|
|
! private::bar
|
|
|
|
!end
|
|
|
|
|
2019-06-15 06:04:13 +08:00
|
|
|
! Test interface nested inside another interface
|
|
|
|
module m3
|
|
|
|
interface g
|
|
|
|
subroutine s1(f)
|
|
|
|
interface
|
|
|
|
real function f(x)
|
|
|
|
interface
|
|
|
|
subroutine x()
|
|
|
|
end subroutine
|
|
|
|
end interface
|
|
|
|
end function
|
|
|
|
end interface
|
|
|
|
end subroutine
|
|
|
|
end interface
|
|
|
|
end
|
|
|
|
!Expect: m3.mod
|
|
|
|
!module m3
|
2019-08-01 06:53:46 +08:00
|
|
|
! interface g
|
|
|
|
! procedure::s1
|
|
|
|
! end interface
|
2019-06-15 06:04:13 +08:00
|
|
|
! interface
|
|
|
|
! subroutine s1(f)
|
|
|
|
! interface
|
|
|
|
! function f(x)
|
|
|
|
! interface
|
|
|
|
! subroutine x()
|
|
|
|
! end
|
|
|
|
! end interface
|
2019-08-13 04:06:59 +08:00
|
|
|
! real(4)::f
|
2019-06-15 06:04:13 +08:00
|
|
|
! end
|
|
|
|
! end interface
|
|
|
|
! end
|
|
|
|
! end interface
|
|
|
|
!end
|
2019-08-09 07:52:36 +08:00
|
|
|
|
|
|
|
module m4
|
|
|
|
interface foo
|
|
|
|
integer function foo()
|
|
|
|
end function
|
|
|
|
integer function f(x)
|
|
|
|
end function
|
|
|
|
end interface
|
|
|
|
end
|
|
|
|
subroutine s4
|
|
|
|
use m4
|
|
|
|
i = foo()
|
|
|
|
end
|
|
|
|
!Expect: m4.mod
|
|
|
|
!module m4
|
|
|
|
! interface foo
|
|
|
|
! procedure::foo
|
|
|
|
! procedure::f
|
|
|
|
! end interface
|
|
|
|
! interface
|
|
|
|
! function foo()
|
|
|
|
! integer(4)::foo
|
|
|
|
! end
|
|
|
|
! end interface
|
|
|
|
! interface
|
|
|
|
! function f(x)
|
|
|
|
! real(4)::x
|
2019-08-13 04:06:59 +08:00
|
|
|
! integer(4)::f
|
2019-08-09 07:52:36 +08:00
|
|
|
! end
|
|
|
|
! end interface
|
|
|
|
!end
|
|
|
|
|
|
|
|
! Compile contents of m4.mod and verify it gets the same thing again.
|
|
|
|
module m5
|
|
|
|
interface foo
|
|
|
|
procedure::foo
|
|
|
|
procedure::f
|
|
|
|
end interface
|
|
|
|
interface
|
|
|
|
function foo()
|
|
|
|
integer(4)::foo
|
|
|
|
end
|
|
|
|
end interface
|
|
|
|
interface
|
|
|
|
function f(x)
|
|
|
|
integer(4)::f
|
|
|
|
real(4)::x
|
|
|
|
end
|
|
|
|
end interface
|
|
|
|
end
|
|
|
|
!Expect: m5.mod
|
|
|
|
!module m5
|
|
|
|
! interface foo
|
|
|
|
! procedure::foo
|
|
|
|
! procedure::f
|
|
|
|
! end interface
|
|
|
|
! interface
|
|
|
|
! function foo()
|
|
|
|
! integer(4)::foo
|
|
|
|
! end
|
|
|
|
! end interface
|
|
|
|
! interface
|
|
|
|
! function f(x)
|
|
|
|
! real(4)::x
|
2019-08-13 04:06:59 +08:00
|
|
|
! integer(4)::f
|
2019-08-09 07:52:36 +08:00
|
|
|
! end
|
|
|
|
! end interface
|
|
|
|
!end
|
[flang] Handle alternative names for relational operators
10.1.6.2 says:
> The operators <, <=, >, >=, ==, and /= always have the same interpretations
> as the operators .LT., .LE., .GT., .GE., .EQ., and .NE., respectively.
That means we have to treat `operator(<)` like `operator(.lt.)`,
for example. `<>` is a third alias for `.NE.`.
We can't just choose always to use one form (e.g. replacing `operator(.lt.)`
with `operator(<)`). This is because all symbols names are `CharBlock`s
referring to the cooked character stream so that they have proper source
provenance. Also, if a user prefers one style and uses it consistently,
that's the form they should see in messages.
So the fix is to use whatever form is found in the source, but also to
look up symbols by the other names when necessary. To assist this, add
`GenericSpecInfo::GetAllNames()` to return all of the names of a generic
spec. Each place a generic spec can occur we have to use these to look
for the symbol.
Also reorganize the `AddUse()` overloads to work with this change.
Fixes flang-compiler/f18#746.
Original-commit: flang-compiler/f18@7f06f175d5033f0728f67b1be25ecd53df1f8de5
Reviewed-on: https://github.com/flang-compiler/f18/pull/752
2019-09-18 07:57:09 +08:00
|
|
|
|
|
|
|
module m6a
|
|
|
|
interface operator(<)
|
|
|
|
logical function lt(x, y)
|
|
|
|
logical, intent(in) :: x, y
|
|
|
|
end function
|
|
|
|
end interface
|
|
|
|
end
|
|
|
|
!Expect: m6a.mod
|
|
|
|
!module m6a
|
|
|
|
! interface operator(<)
|
|
|
|
! procedure::lt
|
|
|
|
! end interface
|
|
|
|
! interface
|
|
|
|
! function lt(x,y)
|
|
|
|
! logical(4),intent(in)::x
|
|
|
|
! logical(4),intent(in)::y
|
|
|
|
! logical(4)::lt
|
|
|
|
! end
|
|
|
|
! end interface
|
|
|
|
!end
|
|
|
|
|
|
|
|
module m6b
|
|
|
|
use m6a, only: operator(.lt.)
|
|
|
|
end
|
|
|
|
!Expect: m6b.mod
|
|
|
|
!module m6b
|
|
|
|
! use m6a,only:operator(.lt.)
|
|
|
|
!end
|
2020-12-03 07:13:49 +08:00
|
|
|
|
|
|
|
module m7a
|
|
|
|
interface g_integer
|
|
|
|
module procedure s
|
|
|
|
end interface
|
|
|
|
private :: s
|
|
|
|
contains
|
|
|
|
subroutine s(x)
|
|
|
|
integer :: x
|
|
|
|
end
|
|
|
|
end
|
|
|
|
!Expect: m7a.mod
|
|
|
|
!module m7a
|
|
|
|
! interface g_integer
|
|
|
|
! procedure :: s
|
|
|
|
! end interface
|
|
|
|
! private :: s
|
|
|
|
!contains
|
|
|
|
! subroutine s(x)
|
|
|
|
! integer(4) :: x
|
|
|
|
! end
|
|
|
|
!end
|
|
|
|
|
|
|
|
module m7b
|
|
|
|
interface g_real
|
|
|
|
module procedure s
|
|
|
|
end interface
|
|
|
|
private :: s
|
|
|
|
contains
|
|
|
|
subroutine s(x)
|
|
|
|
real :: x
|
|
|
|
end subroutine
|
|
|
|
end
|
|
|
|
!Expect: m7b.mod
|
|
|
|
!module m7b
|
|
|
|
! interface g_real
|
|
|
|
! procedure :: s
|
|
|
|
! end interface
|
|
|
|
! private :: s
|
|
|
|
!contains
|
|
|
|
! subroutine s(x)
|
|
|
|
! real(4) :: x
|
|
|
|
! end
|
|
|
|
!end
|
|
|
|
|
|
|
|
module m7c
|
|
|
|
use m7a, only: g => g_integer
|
|
|
|
use m7b, only: g => g_real
|
|
|
|
interface g
|
|
|
|
module procedure s
|
|
|
|
end interface
|
|
|
|
private :: s
|
|
|
|
contains
|
|
|
|
subroutine s(x)
|
|
|
|
complex :: x
|
|
|
|
end subroutine
|
|
|
|
subroutine test()
|
|
|
|
real :: x
|
|
|
|
integer :: y
|
|
|
|
complex :: z
|
|
|
|
call g(x)
|
|
|
|
call g(y)
|
|
|
|
call g(z)
|
|
|
|
end
|
|
|
|
end
|
|
|
|
!Expect: m7c.mod
|
|
|
|
!module m7c
|
|
|
|
! use m7b, only: g => g_real
|
|
|
|
! use m7a, only: g => g_integer
|
|
|
|
! interface g
|
|
|
|
! procedure :: s
|
|
|
|
! end interface
|
|
|
|
! private :: s
|
|
|
|
!contains
|
|
|
|
! subroutine s(x)
|
|
|
|
! complex(4) :: x
|
|
|
|
! end
|
|
|
|
! subroutine test()
|
|
|
|
! end
|
|
|
|
!end
|
|
|
|
|
|
|
|
! Test m8 is like m7 but without renaming.
|
|
|
|
|
|
|
|
module m8a
|
|
|
|
interface g
|
|
|
|
module procedure s
|
|
|
|
end interface
|
|
|
|
private :: s
|
|
|
|
contains
|
|
|
|
subroutine s(x)
|
|
|
|
integer :: x
|
|
|
|
end
|
|
|
|
end
|
|
|
|
!Expect: m8a.mod
|
|
|
|
!module m8a
|
|
|
|
! interface g
|
|
|
|
! procedure :: s
|
|
|
|
! end interface
|
|
|
|
! private :: s
|
|
|
|
!contains
|
|
|
|
! subroutine s(x)
|
|
|
|
! integer(4) :: x
|
|
|
|
! end
|
|
|
|
!end
|
|
|
|
|
|
|
|
module m8b
|
|
|
|
interface g
|
|
|
|
module procedure s
|
|
|
|
end interface
|
|
|
|
private :: s
|
|
|
|
contains
|
|
|
|
subroutine s(x)
|
|
|
|
real :: x
|
|
|
|
end subroutine
|
|
|
|
end
|
|
|
|
!Expect: m8b.mod
|
|
|
|
!module m8b
|
|
|
|
! interface g
|
|
|
|
! procedure :: s
|
|
|
|
! end interface
|
|
|
|
! private :: s
|
|
|
|
!contains
|
|
|
|
! subroutine s(x)
|
|
|
|
! real(4) :: x
|
|
|
|
! end
|
|
|
|
!end
|
|
|
|
|
|
|
|
module m8c
|
|
|
|
use m8a
|
|
|
|
use m8b
|
|
|
|
interface g
|
|
|
|
module procedure s
|
|
|
|
end interface
|
|
|
|
private :: s
|
|
|
|
contains
|
|
|
|
subroutine s(x)
|
|
|
|
complex :: x
|
|
|
|
end subroutine
|
|
|
|
subroutine test()
|
|
|
|
real :: x
|
|
|
|
integer :: y
|
|
|
|
complex :: z
|
|
|
|
call g(x)
|
|
|
|
call g(y)
|
|
|
|
call g(z)
|
|
|
|
end
|
|
|
|
end
|
|
|
|
!Expect: m8c.mod
|
|
|
|
!module m8c
|
|
|
|
! use m8b, only: g
|
|
|
|
! use m8a, only: g
|
|
|
|
! interface g
|
|
|
|
! procedure :: s
|
|
|
|
! end interface
|
|
|
|
! private :: s
|
|
|
|
!contains
|
|
|
|
! subroutine s(x)
|
|
|
|
! complex(4) :: x
|
|
|
|
! end
|
|
|
|
! subroutine test()
|
|
|
|
! end
|
|
|
|
!end
|
|
|
|
|
|
|
|
! Merging a use-associated generic with a local generic
|
|
|
|
|
|
|
|
module m9a
|
|
|
|
interface g
|
|
|
|
module procedure s
|
|
|
|
end interface
|
|
|
|
private :: s
|
|
|
|
contains
|
|
|
|
subroutine s(x)
|
|
|
|
integer :: x
|
|
|
|
end
|
|
|
|
end
|
|
|
|
!Expect: m9a.mod
|
|
|
|
!module m9a
|
|
|
|
! interface g
|
|
|
|
! procedure :: s
|
|
|
|
! end interface
|
|
|
|
! private :: s
|
|
|
|
!contains
|
|
|
|
! subroutine s(x)
|
|
|
|
! integer(4) :: x
|
|
|
|
! end
|
|
|
|
!end
|
|
|
|
|
|
|
|
module m9b
|
|
|
|
use m9a
|
|
|
|
interface g
|
|
|
|
module procedure s
|
|
|
|
end interface
|
|
|
|
private :: s
|
|
|
|
contains
|
|
|
|
subroutine s(x)
|
|
|
|
real :: x
|
|
|
|
end
|
|
|
|
subroutine test()
|
|
|
|
call g(1)
|
|
|
|
call g(1.0)
|
|
|
|
end
|
|
|
|
end
|
|
|
|
!Expect: m9b.mod
|
|
|
|
!module m9b
|
|
|
|
! use m9a,only:g
|
|
|
|
! interface g
|
|
|
|
! procedure::s
|
|
|
|
! end interface
|
|
|
|
! private::s
|
|
|
|
!contains
|
|
|
|
! subroutine s(x)
|
|
|
|
! real(4)::x
|
|
|
|
! end
|
|
|
|
! subroutine test()
|
|
|
|
! end
|
|
|
|
!end
|
|
|
|
|
2020-12-16 23:06:53 +08:00
|
|
|
! Verify that equivalent names are used when generic operators are merged
|
|
|
|
|
|
|
|
module m10a
|
|
|
|
interface operator(.ne.)
|
|
|
|
end interface
|
|
|
|
end
|
|
|
|
!Expect: m10a.mod
|
|
|
|
!module m10a
|
|
|
|
! interface operator(.ne.)
|
|
|
|
! end interface
|
|
|
|
!end
|
|
|
|
|
|
|
|
module m10b
|
|
|
|
interface operator(<>)
|
|
|
|
end interface
|
|
|
|
end
|
|
|
|
!Expect: m10b.mod
|
|
|
|
!module m10b
|
|
|
|
! interface operator(<>)
|
|
|
|
! end interface
|
|
|
|
!end
|
|
|
|
|
|
|
|
module m10c
|
|
|
|
use m10a
|
|
|
|
use m10b
|
|
|
|
interface operator(/=)
|
|
|
|
end interface
|
|
|
|
end
|
|
|
|
!Expect: m10c.mod
|
|
|
|
!module m10c
|
|
|
|
! use m10b,only:operator(.ne.)
|
|
|
|
! use m10a,only:operator(.ne.)
|
|
|
|
! interface operator(.ne.)
|
|
|
|
! end interface
|
|
|
|
!end
|
|
|
|
|
|
|
|
module m10d
|
|
|
|
use m10a
|
|
|
|
use m10c
|
|
|
|
private :: operator(<>)
|
|
|
|
end
|
|
|
|
!Expect: m10d.mod
|
|
|
|
!module m10d
|
|
|
|
! use m10c,only:operator(.ne.)
|
|
|
|
! use m10a,only:operator(.ne.)
|
|
|
|
! interface operator(.ne.)
|
|
|
|
! end interface
|
|
|
|
! private::operator(.ne.)
|
|
|
|
!end
|
2021-01-15 08:31:48 +08:00
|
|
|
|
|
|
|
module m11a
|
|
|
|
contains
|
|
|
|
subroutine s1()
|
|
|
|
end
|
|
|
|
end
|
|
|
|
!Expect: m11a.mod
|
|
|
|
!module m11a
|
|
|
|
!contains
|
|
|
|
! subroutine s1()
|
|
|
|
! end
|
|
|
|
!end
|
|
|
|
|
|
|
|
module m11b
|
|
|
|
use m11a
|
|
|
|
interface g
|
|
|
|
module procedure s1
|
|
|
|
end interface
|
|
|
|
end
|
|
|
|
!Expect: m11b.mod
|
|
|
|
!module m11b
|
|
|
|
! use m11a,only:s1
|
|
|
|
! interface g
|
|
|
|
! procedure::s1
|
|
|
|
! end interface
|
|
|
|
!end
|