run_kadath_reader Module Procedure

module procedure run_kadath_reader module subroutine run_kadath_reader(this, mpi_ranks, nx, ny, nz, xmin, xmax, ymin, ymax, zmin, zmax, coords, lapse, shift_x, shift_y, shift_z, g_xx, g_xy, g_xz, g_yy, g_yz, g_zz, k_xx, k_xy, k_xz, k_yy, k_yz, k_zz, mass_density, specific_energy, pressure, v_eul_x, v_eul_y, v_eul_z, filename)

Uses

  • proc~~run_kadath_reader~~UsesGraph proc~run_kadath_reader run_kadath_reader IFPORT IFPORT proc~run_kadath_reader->IFPORT module~utility utility proc~run_kadath_reader->module~utility constants constants module~utility->constants matrix matrix module~utility->matrix

Calls the MPI-parallelized version of the function KadathExportBNS within Kadath

Created: FT 28.06.2022 Last update: FT 28.06.2022


endif ifdef GFORTRAN

endif

Arguments

Type IntentOptional Attributes Name
class(bnsfuka), intent(inout) :: this

bnsfuka object which this PROCEDURE is a member of

integer, intent(in) :: mpi_ranks

Number of MPI ranks

integer, intent(in) :: nx

Number of lattice points in the direction

integer, intent(in) :: ny

Number of lattice points in the direction

integer, intent(in) :: nz

Number of lattice points in the direction

double precision, intent(in) :: xmin

Minimum value for over the lattice

double precision, intent(in) :: xmax

Maximum value for over the lattice

double precision, intent(in) :: ymin

Minimum value for over the lattice

double precision, intent(in) :: ymax

Maximum value for over the lattice

double precision, intent(in) :: zmin

Minimum value for over the lattice

double precision, intent(in) :: zmax

Maximum value for over the lattice

double precision, intent(inout), DIMENSION(nx,ny,nz,3) :: coords

Array containing the \(\mathrm{ID}\) on a lattice. First three indices run over the lattice's dimensions, the fourth one runs ovr the fields

double precision, intent(inout), DIMENSION(nx,ny,nz) :: lapse
double precision, intent(inout), DIMENSION(nx,ny,nz) :: shift_x
double precision, intent(inout), DIMENSION(nx,ny,nz) :: shift_y
double precision, intent(inout), DIMENSION(nx,ny,nz) :: shift_z
double precision, intent(inout), DIMENSION(nx,ny,nz) :: g_xx
double precision, intent(inout), DIMENSION(nx,ny,nz) :: g_xy
double precision, intent(inout), DIMENSION(nx,ny,nz) :: g_xz
double precision, intent(inout), DIMENSION(nx,ny,nz) :: g_yy
double precision, intent(inout), DIMENSION(nx,ny,nz) :: g_yz
double precision, intent(inout), DIMENSION(nx,ny,nz) :: g_zz
double precision, intent(inout), DIMENSION(nx,ny,nz) :: k_xx
double precision, intent(inout), DIMENSION(nx,ny,nz) :: k_xy
double precision, intent(inout), DIMENSION(nx,ny,nz) :: k_xz
double precision, intent(inout), DIMENSION(nx,ny,nz) :: k_yy
double precision, intent(inout), DIMENSION(nx,ny,nz) :: k_yz
double precision, intent(inout), DIMENSION(nx,ny,nz) :: k_zz
double precision, intent(inout), DIMENSION(nx,ny,nz) :: mass_density
double precision, intent(inout), DIMENSION(nx,ny,nz) :: specific_energy
double precision, intent(inout), DIMENSION(nx,ny,nz) :: pressure
double precision, intent(inout), DIMENSION(nx,ny,nz) :: v_eul_x
double precision, intent(inout), DIMENSION(nx,ny,nz) :: v_eul_y
double precision, intent(inout), DIMENSION(nx,ny,nz) :: v_eul_z
character(len=*), intent(in) :: filename

Path to the \(\mathrm{ID}\) file output by \(\texttt{FUKA}\), as given in the parameter fe sphincs_id_parameters.dat


Calls

proc~~run_kadath_reader~~CallsGraph proc~run_kadath_reader run_kadath_reader changedirqq changedirqq proc~run_kadath_reader->changedirqq makedirqq makedirqq proc~run_kadath_reader->makedirqq

Called by

proc~~run_kadath_reader~~CalledByGraph proc~run_kadath_reader run_kadath_reader interface~run_kadath_reader run_kadath_reader interface~run_kadath_reader->proc~run_kadath_reader

Contents


Variables

Type Visibility Attributes Name Initial
logical, private, parameter :: debug = .FALSE.
character(len=:), private, ALLOCATABLE :: dir_id
logical, private :: dir_out
logical, private :: exist
character(len=:), private, ALLOCATABLE :: filename_id
character(len=:), private, ALLOCATABLE :: filename_par
type(namefile), private, DIMENSION(mpi_ranks) :: filenames_ranks

ifdef working_dir

ifdef GFORTRAN

define stringize_start(x) "&

define stringize_end(x) &x"

work_dir= stringize_start(working_dir) stringize_end(working_dir)

else

define stringize(x) tostring(x)

define tostring(x) #x

work_dir= stringize(working_dir)

endif

else

PRINT , " ERROR! No value assigned to the variable working_dir in the ", & "SConstruct file! Please assign a value to it!" PRINT , " * Stopping..." PRINT * STOP

endif

ifdef __INTEL_COMPILER

double precision, private, DIMENSION(:,:), ALLOCATABLE :: grid_tmp
integer, private :: i
integer, private :: i_char
integer, private :: i_file
integer, private :: i_rank
integer, private :: ios
integer, private :: j
integer, private :: k
integer, private :: length_work_dir
character(len=3), private :: mpi_ranks_str
integer, private :: n_first_ranks
integer, private :: n_last_rank
integer, private :: nchars
integer, private :: nlines
integer, private :: npoints_prev
integer, private :: nz_rank(mpi_ranks)
integer, private :: nz_rem
logical(kind=4), private :: status
integer, private, parameter :: unit_par = 3480
integer, private, DIMENSION(mpi_ranks) :: unit_rank
integer, private :: unit_rank_prev
character(len=:), private, ALLOCATABLE :: work_dir

Derived Types

type ::  namefile

Components

Type Visibility Attributes Name Initial
character(len=:), public, ALLOCATABLE :: name