Skip to content
Snippets Groups Projects
Verified Commit e626f926 authored by Dorian Stoll's avatar Dorian Stoll
Browse files

nas-ft: fortran: Make grid size and iterations configurable

parent 69bfdb64
No related branches found
No related tags found
No related merge requests found
...@@ -74,9 +74,9 @@ ...@@ -74,9 +74,9 @@
! This reduces variable startup costs, which is important for such a ! This reduces variable startup costs, which is important for such a
! short benchmark. The other NPB 2 implementations are similar. ! short benchmark. The other NPB 2 implementations are similar.
!--------------------------------------------------------------------- !---------------------------------------------------------------------
call setup()
call alloc_space call alloc_space
call setup()
call init_ui(u0, u1, twiddle, dims(1), dims(2), dims(3)) call init_ui(u0, u1, twiddle, dims(1), dims(2), dims(3))
call compute_indexmap(twiddle, dims(1), dims(2), dims(3)) call compute_indexmap(twiddle, dims(1), dims(2), dims(3))
call compute_initial_conditions(u1, dims(1), dims(2), dims(3)) call compute_initial_conditions(u1, dims(1), dims(2), dims(3))
...@@ -220,13 +220,33 @@ ...@@ -220,13 +220,33 @@
use omp_lib use omp_lib
implicit none implicit none
character(len=32) :: arg
if (command_argument_count() .ne. 4) then
error stop "Invalid number of arguments"
end if
call get_command_argument(1, arg)
read(arg, *) dims(1)
call get_command_argument(2, arg)
read(arg, *) dims(2)
call get_command_argument(3, arg)
read(arg, *) dims(3)
call get_command_argument(4, arg)
read(arg, *) niter
nxp = dims(1) + 1
ntotalp = nxp * dims(2) * dims(3)
maxdim = max(dims(1), max(dims(2), dims(3)))
debug = .FALSE. debug = .FALSE.
write(*, 1000) write(*, 1000)
niter = niter_default write(*, 1001) dims(1), dims(2), dims(3)
write(*, 1001) nx, ny, nz
write(*, 1002) niter write(*, 1002) niter
!$ write(*, 1003) omp_get_max_threads() !$ write(*, 1003) omp_get_max_threads()
write(*, *) write(*, *)
...@@ -237,10 +257,6 @@ ...@@ -237,10 +257,6 @@
1002 format(' Iterations : ', i0) 1002 format(' Iterations : ', i0)
1003 format(' Number of available threads : ', i0) 1003 format(' Number of available threads : ', i0)
dims(1) = nx
dims(2) = ny
dims(3) = nz
!--------------------------------------------------------------------- !---------------------------------------------------------------------
! Set up info for blocking of ffts and transposes. This improves ! Set up info for blocking of ffts and transposes. This improves
...@@ -260,8 +276,6 @@ ...@@ -260,8 +276,6 @@
fftblock = fftblock_default fftblock = fftblock_default
fftblockpad = fftblockpad_default fftblockpad = fftblockpad_default
if (fftblock .ne. fftblock_default) fftblockpad = fftblock+3
return return
end end
...@@ -302,12 +316,12 @@ ...@@ -302,12 +316,12 @@
!$omp& collapse(2) !$omp& collapse(2)
do k = 1, dims(3) do k = 1, dims(3)
do j = 1, dims(2) do j = 1, dims(2)
kk = mod(k-1+nz/2, nz) - nz/2 kk = mod(k-1+dims(3)/2, dims(3)) - dims(3)/2
kk2 = kk*kk kk2 = kk*kk
jj = mod(j-1+ny/2, ny) - ny/2 jj = mod(j-1+dims(2)/2, dims(2)) - dims(2)/2
kj2 = jj*jj+kk2 kj2 = jj*jj+kk2
do i = 1, dims(1) do i = 1, dims(1)
ii = mod(i-1+nx/2, nx) - nx/2 ii = mod(i-1+dims(1)/2, dims(1)) - dims(1)/2
twiddle(i,j,k) = dexp(ap*dble(ii*ii+kj2)) twiddle(i,j,k) = dexp(ap*dble(ii*ii+kj2))
end do end do
end do end do
...@@ -332,8 +346,8 @@ ...@@ -332,8 +346,8 @@
integer dir integer dir
double complex x1(ntotalp), x2(ntotalp) double complex x1(ntotalp), x2(ntotalp)
double complex y1(fftblockpad_default*maxdim), & double complex y1(fftblockpad*maxdim), &
& y2(fftblockpad_default*maxdim) & y2(fftblockpad*maxdim)
!--------------------------------------------------------------------- !---------------------------------------------------------------------
! note: args x1, x2 must be different arrays ! note: args x1, x2 must be different arrays
...@@ -704,9 +718,9 @@ ...@@ -704,9 +718,9 @@
!$omp do !$omp do
do j=1,1024 do j=1,1024
q = mod(j, nx)+1 q = mod(j, dims(1))+1
r = mod(3*j,ny)+1 r = mod(3*j,dims(2))+1
s = mod(5*j,nz)+1 s = mod(5*j,dims(3))+1
local=local+u1(q,r,s) local=local+u1(q,r,s)
end do end do
...@@ -716,7 +730,7 @@ ...@@ -716,7 +730,7 @@
!$omp end parallel !$omp end parallel
chk = chk/ntotal_f chk = chk/dble(dims(1) * dims(2) * dims(3))
write (*, 30) i, REAL(chk), IMAG(chk) write (*, 30) i, REAL(chk), IMAG(chk)
30 format (' T = ', i0, ' Checksum = ', es0.10, " ", es0.10) 30 format (' T = ', i0, ' Checksum = ', es0.10, " ", es0.10)
......
...@@ -8,20 +8,6 @@ ...@@ -8,20 +8,6 @@
module ft_data module ft_data
! CLASS = C
integer nx, ny, nz, maxdim, niter_default
parameter (nx=512, ny=512, nz=512, maxdim=512)
parameter (niter_default=20)
integer kind2
parameter (kind2=4)
! total number of grid points with padding
integer(kind2) nxp, ntotalp
parameter (nxp=nx+1)
parameter (ntotalp=nxp*ny*nz)
double precision ntotal_f
parameter (ntotal_f=dble(nx)*ny*nz)
! If processor array is 1x1 -> 0D grid decomposition ! If processor array is 1x1 -> 0D grid decomposition
...@@ -89,10 +75,14 @@ ...@@ -89,10 +75,14 @@
! roots of unity array ! roots of unity array
! relies on x being largest dimension? ! relies on x being largest dimension?
double complex u(nxp) double complex, dimension(:), allocatable :: u
! number of iterations ! number of iterations
integer niter integer niter
integer maxdim
integer nxp
integer ntotalp
end module ft_data end module ft_data
...@@ -119,10 +109,7 @@ ...@@ -119,10 +109,7 @@
! - twiddle contains exponents for the time evolution operator. ! - twiddle contains exponents for the time evolution operator.
!--------------------------------------------------------------------- !---------------------------------------------------------------------
double complex, allocatable :: & double complex, allocatable :: u0(:), u1(:)
& u0(:), pad1(:), &
& u1(:), pad2(:)
! > u2(:)
double precision, allocatable :: twiddle(:) double precision, allocatable :: twiddle(:)
!--------------------------------------------------------------------- !---------------------------------------------------------------------
! Large arrays are in module so that they are allocated on the ! Large arrays are in module so that they are allocated on the
...@@ -147,20 +134,14 @@ ...@@ -147,20 +134,14 @@
! allocate space dynamically for data arrays ! allocate space dynamically for data arrays
!--------------------------------------------------------------------- !---------------------------------------------------------------------
use ft_data, only : ntotalp use ft_data, only : ntotalp, nxp, u
use ft_fields use ft_fields
implicit none implicit none
integer ios integer ios
allocate (u(nxp), u0(ntotalp), u1(ntotalp), twiddle(ntotalp), stat = ios)
allocate ( &
& u0(ntotalp), pad1(3), &
& u1(ntotalp), pad2(3), &
! > u2(ntotalp),
& twiddle(ntotalp), &
& stat = ios)
if (ios .ne. 0) then if (ios .ne. 0) then
write(*,*) 'Error encountered in allocating space' write(*,*) 'Error encountered in allocating space'
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment