OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-old/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [entry_6.f90] - Diff between revs 154 and 816

Go to most recent revision | Only display areas with differences | Details | Blame | View Log

Rev 154 Rev 816
! { dg-do run }
! { dg-do run }
! Tests the fix for PR24558, which reported that module
! Tests the fix for PR24558, which reported that module
! alternate function entries did not work.
! alternate function entries did not work.
!
!
! Contributed by Erik Edelmann  
! Contributed by Erik Edelmann  
!
!
module foo
module foo
contains
contains
    function n1 (a)
    function n1 (a)
        integer :: n1, n2, a, b
        integer :: n1, n2, a, b
        integer, save :: c
        integer, save :: c
        c = a
        c = a
        n1 = c**3
        n1 = c**3
        return
        return
    entry n2 (b)
    entry n2 (b)
        n2 = c * b
        n2 = c * b
        n2 = n2**2
        n2 = n2**2
        return
        return
    end function n1
    end function n1
    function z1 (u)
    function z1 (u)
        complex :: z1, z2, u, v
        complex :: z1, z2, u, v
        z1 = (1.0, 2.0) * u
        z1 = (1.0, 2.0) * u
        return
        return
    entry z2 (v)
    entry z2 (v)
        z2 = (3, 4) * v
        z2 = (3, 4) * v
        return
        return
    end function z1
    end function z1
    function n3 (d)
    function n3 (d)
        integer :: n3, d
        integer :: n3, d
        n3 = n2(d) * n1(d) ! Check sibling references.
        n3 = n2(d) * n1(d) ! Check sibling references.
        return
        return
    end function n3
    end function n3
    function c1 (a)
    function c1 (a)
        character(4) :: c1, c2, a, b
        character(4) :: c1, c2, a, b
        c1 = a
        c1 = a
        if (a .eq. "abcd") c1 = "ABCD"
        if (a .eq. "abcd") c1 = "ABCD"
        return
        return
    entry c2 (b)
    entry c2 (b)
        c2 = b
        c2 = b
        if (b .eq. "wxyz") c2 = "WXYZ"
        if (b .eq. "wxyz") c2 = "WXYZ"
        return
        return
    end function c1
    end function c1
end module foo
end module foo
    use foo
    use foo
    if (n1(9) .ne. 729) call abort ()
    if (n1(9) .ne. 729) call abort ()
    if (n2(2) .ne. 324) call abort ()
    if (n2(2) .ne. 324) call abort ()
    if (n3(19) .ne. 200564019) call abort ()
    if (n3(19) .ne. 200564019) call abort ()
    if (c1("lmno") .ne. "lmno") call abort ()
    if (c1("lmno") .ne. "lmno") call abort ()
    if (c1("abcd") .ne. "ABCD") call abort ()
    if (c1("abcd") .ne. "ABCD") call abort ()
    if (c2("lmno") .ne. "lmno") call abort ()
    if (c2("lmno") .ne. "lmno") call abort ()
    if (c2("wxyz") .ne. "WXYZ") call abort ()
    if (c2("wxyz") .ne. "WXYZ") call abort ()
    if (z1((3,4)) .ne. (-5, 10)) call abort ()
    if (z1((3,4)) .ne. (-5, 10)) call abort ()
    if (z2((5,6)) .ne. (-9, 38)) call abort ()
    if (z2((5,6)) .ne. (-9, 38)) call abort ()
 end
 end
! { dg-final { cleanup-modules "foo" } }
! { dg-final { cleanup-modules "foo" } }
 
 

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.