OpenCores
URL https://opencores.org/ocsvn/openrisc_2011-10-31/openrisc_2011-10-31/trunk

Subversion Repositories openrisc_2011-10-31

[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [char_result_11.f90] - Diff between revs 149 and 154

Only display areas with differences | Details | Blame | View Log

Rev 149 Rev 154
! { dg-do link }
! { dg-do link }
! PR 23675: Character function of module-variable length
! PR 23675: Character function of module-variable length
! PR 25716: Implicit kind conversions in in expressions written to *.mod-files.
! PR 25716: Implicit kind conversions in in expressions written to *.mod-files.
module cutils
module cutils
    implicit none
    implicit none
    private
    private
    type t
    type t
        integer :: k = 25
        integer :: k = 25
        integer :: kk(3) = (/30, 40, 50 /)
        integer :: kk(3) = (/30, 40, 50 /)
    end type t
    end type t
    integer :: m1 = 25, m2 = 25, m3 = 25, m4 = 25, m5 = 25
    integer :: m1 = 25, m2 = 25, m3 = 25, m4 = 25, m5 = 25
    integer :: n5 = 3, n7 = 3, n9 = 3
    integer :: n5 = 3, n7 = 3, n9 = 3
    integer(1) :: n1 = 3, n2 = 3, n3 = 3, n4 = 3, n6 = 3, n8 = 3
    integer(1) :: n1 = 3, n2 = 3, n3 = 3, n4 = 3, n6 = 3, n8 = 3
    character(10) :: s = "abcdefghij"
    character(10) :: s = "abcdefghij"
    integer :: x(4) = (/ 30, 40, 50, 60 /)
    integer :: x(4) = (/ 30, 40, 50, 60 /)
    type(t), save :: tt1(5), tt2(5)
    type(t), save :: tt1(5), tt2(5)
    public :: IntToChar1, IntToChar2, IntToChar3, IntToChar4, IntToChar5, &
    public :: IntToChar1, IntToChar2, IntToChar3, IntToChar4, IntToChar5, &
                IntToChar6, IntToChar7, IntToChar8
                IntToChar6, IntToChar7, IntToChar8
contains
contains
    pure integer function get_k(tt)
    pure integer function get_k(tt)
        type(t), intent(in) :: tt
        type(t), intent(in) :: tt
        get_k = tt%k
        get_k = tt%k
    end function get_k
    end function get_k
    function IntToChar1(integerValue) result(a)
    function IntToChar1(integerValue) result(a)
        integer, intent(in) :: integerValue
        integer, intent(in) :: integerValue
        character(len=m1)  :: a
        character(len=m1)  :: a
        write(a, *) integerValue
        write(a, *) integerValue
    end function IntToChar1
    end function IntToChar1
    function IntToChar2(integerValue) result(a)
    function IntToChar2(integerValue) result(a)
        integer, intent(in) :: integerValue
        integer, intent(in) :: integerValue
        character(len=m2+n1)  :: a
        character(len=m2+n1)  :: a
        write(a, *) integerValue
        write(a, *) integerValue
    end function IntToChar2
    end function IntToChar2
    function IntToChar3(integerValue) result(a)
    function IntToChar3(integerValue) result(a)
        integer, intent(in) :: integerValue
        integer, intent(in) :: integerValue
        character(len=iachar(s(n2:n3)))  :: a
        character(len=iachar(s(n2:n3)))  :: a
        write(a, *) integerValue
        write(a, *) integerValue
    end function IntToChar3
    end function IntToChar3
    function IntToChar4(integerValue) result(a)
    function IntToChar4(integerValue) result(a)
        integer, intent(in) :: integerValue
        integer, intent(in) :: integerValue
        character(len=tt1(n4)%k)  :: a
        character(len=tt1(n4)%k)  :: a
        write(a, *) integerValue
        write(a, *) integerValue
    end function IntToChar4
    end function IntToChar4
    function IntToChar5(integerValue) result(a)
    function IntToChar5(integerValue) result(a)
        integer, intent(in) :: integerValue
        integer, intent(in) :: integerValue
        character(len=maxval((/m3, n5/)))  :: a
        character(len=maxval((/m3, n5/)))  :: a
        write(a, *) integerValue
        write(a, *) integerValue
    end function IntToChar5
    end function IntToChar5
    function IntToChar6(integerValue) result(a)
    function IntToChar6(integerValue) result(a)
        integer, intent(in) :: integerValue
        integer, intent(in) :: integerValue
        character(len=x(n6))  :: a
        character(len=x(n6))  :: a
        write(a, *) integerValue
        write(a, *) integerValue
    end function IntToChar6
    end function IntToChar6
    function IntToChar7(integerValue) result(a)
    function IntToChar7(integerValue) result(a)
        integer, intent(in) :: integerValue
        integer, intent(in) :: integerValue
        character(len=tt2(min(m4, n7, 2))%kk(n8))  :: a
        character(len=tt2(min(m4, n7, 2))%kk(n8))  :: a
        write(a, *) integerValue
        write(a, *) integerValue
    end function IntToChar7
    end function IntToChar7
    function IntToChar8(integerValue) result(a)
    function IntToChar8(integerValue) result(a)
        integer, intent(in) :: integerValue
        integer, intent(in) :: integerValue
        character(len=get_k(t(m5, (/31, n9, 53/))))  :: a
        character(len=get_k(t(m5, (/31, n9, 53/))))  :: a
        write(a, *) integerValue
        write(a, *) integerValue
    end function IntToChar8
    end function IntToChar8
end module cutils
end module cutils
program test
program test
    use cutils
    use cutils
    implicit none
    implicit none
    character(25) :: str
    character(25) :: str
    str = IntToChar1(3)
    str = IntToChar1(3)
    print *, str
    print *, str
    str = IntToChar2(3)
    str = IntToChar2(3)
    print *, str
    print *, str
    str = IntToChar3(3)
    str = IntToChar3(3)
    print *, str
    print *, str
    str = IntToChar4(3)
    str = IntToChar4(3)
    print *, str
    print *, str
    str = IntToChar5(3)
    str = IntToChar5(3)
    print *, str
    print *, str
    str = IntToChar6(3)
    str = IntToChar6(3)
    print *, str
    print *, str
    str = IntToChar7(3)
    str = IntToChar7(3)
    print *, str
    print *, str
    str = IntToChar8(3)
    str = IntToChar8(3)
    print *, str
    print *, str
end program test
end program test
! { dg-final { cleanup-modules "cutils" } }
! { dg-final { cleanup-modules "cutils" } }
 
 

powered by: WebSVN 2.1.0

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