source: Sophya/trunk/Eval/JET/f90mtx.f90@ 3155

Last change on this file since 3155 was 2366, checked in by ansari, 23 years ago

Ajout fonctions Sin/Cos/... ds jet.h + prog en f90 - Reza 18/4/2003

File size: 2.4 KB
RevLine 
[2366]1program main
2 ! Programme test de perfo tableaux f90
3 ! Reza Ansari - Avril 2003
4 implicit none
5 parameter NR = 1000
6 parameter NC = 500
7 real(8) , dimension(:,:), allocatable :: mx1, mx2, mx3, mx4, mx5
8 integer i,j,k,ntime
9 real(8) x,y,z,c1,c2,c3
10 integer count
11 integer nra,nca
12
13 count = 0
14 ntime = 50
15 nra = NR
16 nca = NC
17
18 allocate(mx1(NR,NC))
19 allocate(mx2(NR,NC))
20 allocate(mx3(NR,NC))
21! allocate(mx4(NR,NC))
22 allocate(mx5(NR,NC))
23
24 call finittim()
25 print *,' f90mtx - NR=' , NR, ' NC=' , NC
26 print *,' Remplissage MX1 MX2 (NRxNC) - NTimes=', ntime
27 do k=1,ntime/5
28 x = k*0.00314
29 y = sin(X)
30 do i=1,NR
31 do j=1,NC
32 mx1(i,j) = k*300.+10.*i+j+x
33 mx2(I,J) = k*550.+20.*i+2.*j+y
34 mx3(I,J) = k*860.+40.*i+7.*j+y*3.14
35 enddo
36 enddo
37 if (k.eq.5) print *, 'FILLMTX - 5 -> ', mx1(12,14)
38 if (k.EQ.15) print *, 'FILLMTX - 15 -> ', mx2(12,15)
39 call random_number(x)
40 call random_number(y)
41 call random_number(z)
42 i = x*NR
43 j = y*NC
44 if ((z>0.98).or.(k.eq.15).or.(k.eq.35)) &
45 print *, 'FillMtx/Check: ', &
46 k, mx1(i,j), mx2(i,j), mx3(i,j), &
47 ' x,y,z=',z,y,z
48 enddo
49
50 print *, 'FIN Remplissage '
51 call fprttim(1)
52
53 do k=1,ntime
54 c1 = k*0.035
55 c2 = cos(c1)+0.04
56 c3 = sin(c1*5.)
57 call opemtx(nra, nca, c1,c2,c3, mx1,mx2,mx3,mx5,count)
58 call random_number(x)
59 call random_number(y)
60! call random_number(z)
61 z = 0
62 i = x*NR
63 j = y*NC
64 if ((z>0.98).or.(k.eq.15).or.(k.eq.35)) &
65 print *, 'FillMtx/Check: ', k, i,j, &
66 mx1(i,j),mx2(i,j), mx3(i,j), &
67 ' c1,c2,c3=', c1,c2,c3, &
68 ' x,y,z=' , x,y,z
69
70 enddo
71 print *, 'FIN MX5 = C1*MX1 + MX1 * MX2*C2 + MX2C3 '
72 call fprttim(2)
73
74 print *, ' NCount appel opemtx = ' , count
75 print *, ' ------ FIN programme f90mtx ---------- '
76end program main
77
78subroutine opemtx(nra,nca,c1,c2,c3,mx1,mx2,mx3,mx,count)
79 integer :: nra,nca,count
80 real(8), dimension(nra,nca) :: mx1,mx2,mx3
81 real(8), dimension(nra,nca) :: mx
82 real(8) :: c1,c2,c3
83 mx = c1*mx1+c2*mx2+c3*mx3
84 count = count+1
85 if ((count.eq.9).or.(count.eq.36)) &
86 print *, 'opemtx-count=' , count, ' mx1,2,3= ', &
87 mx1(count,19), mx2(count,19), mx3(count, 19), &
88 ' c1,c2,c3=', c1,c2,c3, &
89 ' mx= ' , mx(count,19)
90 return
91end subroutine opemtx
92
93
Note: See TracBrowser for help on using the repository browser.