File: template_array_05.f90

package info (click to toggle)
lfortran 0.45.0-1
  • links: PTS, VCS
  • area: main
  • in suites: sid, trixie
  • size: 46,332 kB
  • sloc: cpp: 137,068; f90: 51,260; python: 6,444; ansic: 4,277; yacc: 2,285; fortran: 806; sh: 524; makefile: 30; javascript: 15
file content (90 lines) | stat: -rw-r--r-- 1,913 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
module template_array_05_m

    implicit none
    private
    public :: vector_t, matrix_t

    requirement op(t, plus_t)
        type, deferred :: t
        pure elemental function plus_t(l, r) result(rs)
            type(t), intent(in) :: l, r
            type(t) :: rs
        end function
    end requirement

    template vector_t(t, plus_t, n)
        require :: op(t, plus_t)
        integer :: n
        
        private
        public :: add_array

        type :: vector
            type(t) :: elements(n)
        end type
    contains
        pure function add_vector(a, b) result(r)
            type(vector), intent(in) :: a, b
            type(vector) :: r
            r%elements = plus_t(a%elements, b%elements)
        end function
    end template

    template matrix_t(t, plus_t, n)
        require :: op(t, plus_t)
        integer :: n
        
        private
        public :: add_matrix

        type :: matrix
            type(t) :: elements(n, n)
        end type
    contains
        pure function add_matrix(a, b) result(r)
            type(matrix), intent(in) :: a, b
            type(matrix) :: r
            r%elements = plus_t(a%elements, b%elements)
        end function
    end template

end module

program template_array_05

use template_array_05_m

integer, parameter :: n = 10
instantiate vector_t(integer, operator(+), n), &
    only: int_vector => vector, &
          int_add_vector => add_vector

type(int_vector) :: a, b, c

integer :: i, j
do i = 1, n
    a%elements(i) = i
    b%elements(i) = i
end do

c = int_add_vector(a, b)
print *, c%elements

instantiate matrix_t(integer, operator(+), n), &
    only: int_matrix => matrix, &
          int_add_matrix => add_matrix

type(int_matrix) :: am, bm, cm

do i = 1, n
    do j = 1, n
        am%elements(i,j) = i + j
        bm%elements(i,j) = i + j
    end do
end do

cm = int_add_matrix(am, bm)

print *, cm%elements

end