aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorWojtek Kosior <kwojtus@protonmail.com>2019-04-25 13:01:35 +0200
committerWojtek Kosior <kwojtus@protonmail.com>2019-04-25 13:01:35 +0200
commit2cef86b7eca2dbf96cda5909de27754249dc9259 (patch)
tree601a022ab30841fea3ddb5a65679de5b447cad53
parent672895c4e7070176d5782b499d3cdc153cfd814d (diff)
downloadfortran-assignment1-2cef86b7eca2dbf96cda5909de27754249dc9259.tar.gz
fortran-assignment1-2cef86b7eca2dbf96cda5909de27754249dc9259.zip
create function for measuring, make selection of mul implementations possible
-rw-r--r--src/main.F9075
1 files changed, 51 insertions, 24 deletions
diff --git a/src/main.F90 b/src/main.F90
index 2649e10..43eeabb 100644
--- a/src/main.F90
+++ b/src/main.F90
@@ -4,41 +4,33 @@ PROGRAM mul
USE dotmat
IMPLICIT none
- real(kind=4), dimension(:,:), allocatable :: mat1, mat2, res
- real :: start, end
- integer :: dim = 10
+ integer, parameter :: seed = 123456
+ real :: time
+ integer :: dim = 10, multype = 1, realtype = 4
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)
+ SELECT CASE(realtype)
+ CASE (4)
+ time = measure_4(dim)
+ ! CASE (8)
+ ! time = measure_8(dim)
+ ! CASE (16)
+ ! time = measure_16(dim)
+ CASE default
+ write (*, *) "wrong kind for real: ", realtype
- call cpu_time(end)
-
- print '(I11," ",ES11.5)', dim, end - start
+ END SELECT
+
+ print '(I11," ",ES11.5)', dim, time
dim = dim * 2
-
- deallocate(mat1)
- deallocate(mat2)
- deallocate(res)
END DO
CONTAINS
- SUBROUTINE init_random_seed(seed)
- integer, intent(in) :: seed
+ SUBROUTINE init_random_seed()
integer :: i, n
call random_seed(size = n)
@@ -46,5 +38,40 @@ CONTAINS
call random_seed(put = (/ ((seed + i) * 37, i = 1, n) /))
END SUBROUTINE init_random_seed
+
+
+ real FUNCTION measure_4(dim) result(time)
+ integer, intent(in) :: dim
+ real(kind=4), dimension(:,:), allocatable :: mat1, mat2, res
+ real :: start, end
+ call init_random_seed()
+
+ allocate(mat1(dim,dim))
+ allocate(mat2(dim,dim))
+ allocate(res(dim,dim))
+
+ call random_number(mat1)
+ call random_number(mat2)
+
+ call cpu_time(start)
+
+ SELECT CASE(multype)
+ CASE (1)
+ res = naivmull(mat1, mat2)
+ CASE (2)
+ res = bettmull(mat1, mat2)
+ CASE (3)
+ res = dotmull(mat1, mat2)
+ CASE default
+ res = matmul(mat1, mat2)
+
+ END SELECT
+
+ call cpu_time(end)
+
+ time = end - start
+
+ END FUNCTION measure_4
+
END PROGRAM mul