1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950515253545556 |
- !gfortran -fopenmp -O3 timings.f90
- program timing2000
- use omp_lib
- implicit none
- integer, parameter :: ntests = 20
- integer :: n, nthreads
- real(kind=8), allocatable, dimension(:,:) :: a,b,c
- real(kind=8) :: t1, t2, elapsed_time
- integer(kind=8) :: tclock1, tclock2, clock_rate
- integer :: i,j,k,itest
- ! Specifier le nombre de Threads a utiliser:
- !!$ print *, "Combien de threads avec OpenMP? "
- !!$ read *, nthreads
- !!nthreads=8
- !!$ call omp_set_num_threads(nthreads)
- !omp_get_num_threads()
- n=2000
- !print *, "multiplication de matrices (n,n), entrer n: "
- !read *, n
- allocate(a(n,n), b(n,n), c(n,n))
- ! pour la demo, a = b = ones(n)
- a = 1.d0
- b = 1.d0
- call system_clock(tclock1) ! top depart du timer general
- call cpu_time(t1) ! top depart du timer cpu
- do itest=1,ntests
- !$omp parallel do private(i,k)
- do j = 1,n
- do i = 1,n
- c(i,j) = 0.d0
- do k=1,n
- c(i,j) = c(i,j) + a(i,k)*b(k,j)
- enddo
- enddo
- enddo
- enddo
- call cpu_time(t2) ! top final du timer cpu
- print 10, ntests, n, n, t2-t1
- 10 format( i4, " multiplications de matrices (", i4, "x", i4, " ) : temps CPU = ",f12.8, " secondes")
-
- call system_clock(tclock2, clock_rate)
- elapsed_time = float(tclock2 - tclock1) / float(clock_rate)
- print 11, elapsed_time
- 11 format("Elapsed time = ",f12.8, " seconds")
- end program timing2000
|