aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorWojtek Kosior <kwojtus@protonmail.com>2019-04-25 11:59:43 +0200
committerWojtek Kosior <kwojtus@protonmail.com>2019-04-25 11:59:43 +0200
commit672895c4e7070176d5782b499d3cdc153cfd814d (patch)
treefa4d286c1aa52e4569bb791abae233af912553a5
parent755d7e5b94b0a978460523eef8b39ab3e5866e5f (diff)
downloadfortran-assignment1-672895c4e7070176d5782b499d3cdc153cfd814d.tar.gz
fortran-assignment1-672895c4e7070176d5782b499d3cdc153cfd814d.zip
basic time-measuring loop
-rw-r--r--src/main.F9066
1 files changed, 35 insertions, 31 deletions
diff --git a/src/main.F90 b/src/main.F90
index f898e1a..2649e10 100644
--- a/src/main.F90
+++ b/src/main.F90
@@ -4,42 +4,46 @@ PROGRAM mul
USE dotmat
IMPLICIT none
- real(kind=4), dimension(:,:), allocatable :: mat1, mat2, res1, res2
-
- call init_random_seed()
-
- allocate(mat1(10,10))
- allocate(mat2(10,10))
- allocate(res1(10,10))
- allocate(res2(10,10))
-
- call random_number(mat1)
- call random_number(mat2)
-
- print *, "mat1:", char(10), mat1
- print *, "mat2:", char(10), mat2
-
- res1 = naivmull(mat1, mat2)
- res2 = matmul(mat1, mat2)
-
- print *, "res:", char(10), res1
- print *, "res_diff:", char(10), res1 - res2
-
+ real(kind=4), dimension(:,:), allocatable :: mat1, mat2, res
+ real :: start, end
+ integer :: dim = 10
+
+ DO WHILE (dim < 2000)
+
+ call init_random_seed(123456)
+
+ allocate(mat1(dim,dim))
+ allocate(mat2(dim,dim))
+ allocate(res(dim,dim))
+
+ call random_number(mat1)
+ call random_number(mat2)
+
+ call cpu_time(start)
+
+ res = naivmull(mat1, mat2)
+
+ call cpu_time(end)
+
+ print '(I11," ",ES11.5)', dim, end - start
+
+ dim = dim * 2
+
+ deallocate(mat1)
+ deallocate(mat2)
+ deallocate(res)
+
+ END DO
+
CONTAINS
- SUBROUTINE init_random_seed()
- integer :: i, n, clock
- integer, dimension(:), allocatable :: seed
+ SUBROUTINE init_random_seed(seed)
+ integer, intent(in) :: seed
+ integer :: i, n
call random_seed(size = n)
- allocate(seed(n))
-
- call system_clock(count = clock)
-
- seed = clock + 37 * (/ (i - 1, i = 1, n) /)
-
- call random_seed(put = seed)
+ call random_seed(put = (/ ((seed + i) * 37, i = 1, n) /))
END SUBROUTINE init_random_seed