source: Sophya/trunk/Eval/Speed/matrixf.f90@ 1727

Last change on this file since 1727 was 1727, checked in by ansari, 24 years ago

programme de test de performances - calcul avec tableaux en f90 - Reza 31/10/01

File size: 1.4 KB
RevLine 
[1727]1 PROGRAM MAIN
2 IMPLICIT NONE
3
4! declaration d'interface de fonction
5 interface
6 subroutine check_table(k, a, b, c)
7 integer, intent (in) :: k
8 double precision, intent (in), dimension(:,:) :: a,b,c
9 end subroutine check_table
10 end interface
11
12 integer, parameter :: NL = 2, NC=2
13 double precision, dimension (NL, NC) :: m1,m2,m3,m4
14
15 integer :: i,j,k
16
17 integer :: N = 5000000
18
19 print *, '--- timing test : N=', N, ' NL=', NL, ' NC=',NC
20 do k=1,N
21 m1 = 0
22 m2 = 0
23 do i=1,NL
24 do j=1,NC
25 m1(i,j) = k*300+10.*i+j
26 m2(i,j) = k*550+20.*i+2.*j;
27 enddo
28 enddo
29 m3 = m1+m2;
30 m4 = m1*m2;
31 call check_table(k, m2, m3, m4)
32! if (k .eq. 1) then
33! print *, 'm1=', m1
34! print *, 'm2=', m2
35! print *, 'm3=', m3
36! print *, 'm4=', m4
37! endif
38 enddo
39
40 print *, '------- end of matrixf.f90 ------------'
41 end
42
43
44 subroutine check_table(k, a, b, c)
45 integer, intent (in) :: k
46 double precision, intent (in), dimension(:,:) :: a,b,c
47
48 if ((k.eq.1) .or. (k.eq.50)) then
49 print *, 'check_table(',k, '...) size(a,1)= ', size(a,1), &
50 ' size(a,2)= ', size(a,2)
51 endif
52 end subroutine check_table
53
Note: See TracBrowser for help on using the repository browser.