How to generalize the function/subroutine to any data type?

Dear all,

I read the small code by @certik
The code is simply read in a integer matrix A, and output its diagonal elements in array d.

    function diag(A) result(d)
    integer, intent(in) :: A(:,:)
    integer :: d(size(A,1))
    integer :: i
    do i = 1, size(A,1)
        d(i) = A(i,i)
    end do
    end function

Now, if A is complex number, or real number matrix, do we need to write diag function for each of the different types of A?

I know there is elemental function which can smartly use a scalar function for vector function,
but here, is there a way that Fortran can just use one diag function, and it can smartly apply this function to any data type of the input matrix A?

Things like below for example

  function diag(A) result(d)
  **type(any)**, intent(in) :: A(:,:)
  **type(A)** :: d(size(A,1))
  integer :: i
  do i = 1, size(A,1)
      d(i) = A(i,i)
  end do
  end function

Thanks much!

PS
Code is from below link,

1 Like

Apart from generic types, we can make a macro for creating a diagonal-matrix view via pointers (based on the linked codes by :cowboy_hat_face: , just for fun…)

#define set_diag_view( arr, diag ) \
diag( 1:size(arr) ) => arr; diag => diag( 1::size(arr,1)+1 )

program main
    implicit none
    integer :: n, i
    integer, allocatable, target :: a(:,:)
    real,    allocatable, target :: b(:,:)
    integer, pointer :: da(:)
    real,    pointer :: db(:)

    print *, "input n:"
    read *, n

    a = reshape( [(i, i=1,n**2)], [n,n] )
    b = a

    set_diag_view( a, da )
    set_diag_view( b, db )

    da(:) = 100
    db(:) = 200.0

    print *
    print *, "n = ", n
    print *, "a = ", a
    print *, "b = ", b
end

$ gfortran test.F90 && ./a.out
 input n:
2

 n =            2
 a =          100           2           3         100
 b =    200.000000       2.00000000       3.00000000       200.000000    
2 Likes
module template_array
    implicit none
    private
    public :: test_template

    requirement operations(t)

        type :: t; end type
    end requirement
!
    template array_tmpl(t)

        requires operations(t)
        private
        public :: diag_t

    contains

        subroutine diag_t(a,b)
            type(t), intent(in) :: a(:,:), b(:)
            integer::i
            do i=1,size(b)
                b(i)=a(i,i)
            end do
        end subroutine

    end template

contains

    subroutine test_template()
        instantiate array_tmpl(integer), only: diag_int => diag_t
        instantiate array_tmpl(real), only: diag_r4 => diag_t

        integer :: ai(2,2),di(2)
        real :: ar(2,2),dr(2)
        ai(1,1) = 1;ai(1,2) = 2
        ai(2,1) = 3;ai(2,2) = 4
        call diag_int(ai,di)
        print *, di
        ar(1,1)=1.;ar(1,2)=2.
        ar(2,1)=3.;ar(2,2)=4.
        call diag_r4(ar,dr)
        print *, dr
    end subroutine

end module

program template_array_03

    use template_array
    implicit none

    call test_template()

end program

lfortran template,
but not now

syntax error: Token '(' is unexpected here
  --> input:35:36
   |
35 |         instantiate array_tmpl(real(8)), only: diag_r8 => diag_t
   |                                    ^ 
1 Like

I think you desire a syntax similar to what I (and many others) wished for in this post. Such syntax is not going to be seen in Fortran ever, or anytime soon, based on the discussions in the above thread.

1 Like

@CRquantum yes, the new generics, being proposed for F202Y and that have a prototype in LFortran will be able to handle this case, you just declare it as generic, write it once, and it will work for all types.

1 Like