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

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

extension prog test perfo f90 - Reza - 31/10/01

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