-
Notifications
You must be signed in to change notification settings - Fork 14
/
Copy pathmove_alloc_bench.f90
66 lines (66 loc) · 2.08 KB
/
move_alloc_bench.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
module m
implicit none
contains
pure subroutine grow_vec(x,xadd) ! append xadd(:) to x(:)
real, allocatable, intent(in out) :: x(:)
real , intent(in) :: xadd(:)
real, allocatable :: temp(:)
integer :: nx
if (.not. allocated(x)) allocate (x(0))
nx = size(x)
allocate (temp(nx + size(xadd)))
temp(:nx) = x
temp(nx+1:) = xadd
call move_alloc(temp,x)
end subroutine grow_vec
end module m
!
program grow_array
use m, only: grow_vec
implicit none
real , allocatable :: a(:),xran(:)
integer, parameter :: nmax = 3*10**6, ngrow = 1000, nt = 4
integer :: na
real :: t(nt)
logical :: print_check
allocate (xran(nmax))
call random_number(xran)
print_check = .false.
if (print_check) print "(2a15)","size","max|a-xran|"
call cpu_time(t(1))
allocate (a(0))
na = 0
do ! grow array in a subroutine with copying and move_alloc
call grow_vec(a,xran(na+1:na+ngrow))
na = size(a)
if (na >= nmax) exit
end do
if (print_check) print "(i15,f15.10)",size(a),maxval(abs(a-xran))
call cpu_time(t(2))
a = [real ::]
na = 0
do ! grow array using RESHAPE -- suggested by FortranFan
a = reshape(a,[na+ngrow],pad=xran(na+1:na+ngrow))
na = size(a)
if (size(a) >= nmax) exit
end do
if (print_check) print "(i15,f15.10)",size(a),maxval(abs(a-xran))
call cpu_time(t(3))
a = [real ::]
na = 0
do ! grow array using allocation on assignment (AoA)
a = [a,xran(na+1:na+ngrow)]
na = size(a)
if (size(a) >= nmax) exit
end do
if (print_check) print "(i15,f15.10)",size(a),maxval(abs(a-xran))
call cpu_time(t(4))
print "(/,4a15)","method","move_alloc","reshape","AoA"
print "(a15,3f15.3)","time(s)",t(2:nt) - t(1:nt-1)
end program grow_array
! sample gfortran -O3 output on Windows:
! method move_alloc reshape AoA
! time(s) 4.750 13.734 18.547
! sample gfortran -O3 output on WSL2:
! method move_alloc reshape AoA
! time(s) 3.480 4.528 4.458