module data !-------------------------------------------------------------------------------------------------- ! This module holds most of the data needed for postprocessing, with the exception of work arrays !-------------------------------------------------------------------------------------------------- implicit none save !-------------------------------------------------------------------------------------------------- ! Array sizes !-------------------------------------------------------------------------------------------------- integer(4) :: mx ! Number of modes in the x direction mx = 2*mgalx/3 integer(4) :: my ! Number of modes in the y direction integer(4) :: mz ! Number of modes in the z direction mz = 2*mgalz/3 - 1 integer(4) :: mgalx ! Number of modes for dealiasing in the x-direction (collocation points) integer(4) :: mgalz ! Number of modes for dealiasing in the z-direction (collocation points) integer(4), parameter :: debug = 0 integer(4) sml !-------------------------------------------------------------------------------------------------- ! 1,2,3 digit numbers for io !-------------------------------------------------------------------------------------------------- character(1) dig1(10) ! 1 digit numbers character(2) dig2(100) ! 2 digit numbers character(3) dig3(1000) ! 3 digit numbers !-------------------------------------------------------------------------------------------------- ! The zero modes for the u,w velocities !-------------------------------------------------------------------------------------------------- real(4), allocatable, dimension(:) :: u00, w00 !-------------------------------------------------------------------------------------------------- ! A few parameters of the simulation !-------------------------------------------------------------------------------------------------- real(8) :: time ! Large field (only double precision variable!) real(4) :: Re ! Reynolds number of the simulation real(4) :: retau ! Reynolds number based on utau and h real(4) :: utau real(4) :: lx ! length of box in x direction real(4) :: lz ! length of box in z direction real(4) :: a0 ! I have no idea of what this is integer(4) :: fieldno ! field number , ranging from first_field to last_field integer(4) :: first_field ! field number of the first field to be read in integer(4) :: last_field ! field number of the last field to be read in !-------------------------------------------------------------------------------------------------- ! Used to scale the wavenumbers !-------------------------------------------------------------------------------------------------- real(4) :: alpha ! This is 1/(x_length) real(4) :: beta ! This is 1/(y_length) !-------------------------------------------------------------------------------------------------- ! Indexes which make wavenumber handling easier !-------------------------------------------------------------------------------------------------- real(8), allocatable, dimension(:) :: alp2 ! The kx wavenumber squared for a certain mode (0:mx/2-1) ! Allocated in generate_indices ! Deallocated in io.f90, subroutine cleanup real(8), allocatable, dimension(:) :: bet2 ! The kz wavenumber squared for a certain mode (0:mz-1) ! Allocated in generate_indices ! Deallocated in io.f90, subroutine cleanup real(8), allocatable, dimension(:) :: kx, kz ! Wavenumbers kx and kz, scaled apropriately ! Allocated in generate_indices ! Deallocated in io.f90, subroutine cleanup !-------------------------------------------------------------------------------------------------- ! Useful constants !-------------------------------------------------------------------------------------------------- real(8), parameter :: pi=3.14159265358979323846Q0 !-------------------------------------------------------------------------------------------------- ! True and False values !-------------------------------------------------------------------------------------------------- integer, parameter :: true = 1 integer, parameter :: false = 0 contains !-------------------------------------------------------------------------------------------------- subroutine generate_indices() !-------------------------------------------------------------------------------------------------- ! This subroutine generates the indices that will be used in the Poisson solution !-------------------------------------------------------------------------------------------------- implicit none integer(4) :: i, k allocate (alp2(0:(mx/2)-1), bet2(0:mz-1)) allocate (kx(0:(mx/2)-1), kz(0:mz-1)) do k = 0, (mz - 1)/2 bet2(k) = (beta*k)**2 kz(k) = beta*k end do do k = (mz + 1)/2, mz - 1 kz(k) = beta*(k - mz) bet2(k) = (beta*(k - mz))**2 end do do i = 0, (mx/2)-1 kx(i) = alpha*i alp2(i) = (alpha*i)**2 end do end subroutine generate_indices end module data