Skip to content

Commit

Permalink
Merge branch 'main' into production_DE_openacc_test
Browse files Browse the repository at this point in the history
  • Loading branch information
basava70 committed Sep 25, 2024
2 parents 624a780 + e900ff0 commit a6a0ba4
Show file tree
Hide file tree
Showing 12 changed files with 464 additions and 172 deletions.
5 changes: 4 additions & 1 deletion config/namelist.io
Original file line number Diff line number Diff line change
Expand Up @@ -10,12 +10,15 @@ ldiag_DVD =.false.
ldiag_forc =.false.
ldiag_extflds =.false.
ldiag_trflx =.false.
ldiag_uvw_sqr =.false.
ldiag_trgrd_xyz =.false.

/

&nml_general
io_listsize =120 !number of streams to allocate. shallbe large or equal to the number of streams in &nml_list
vec_autorotate =.false.
compression_level = 0
compression_level = 1
/

! for sea ice related variables use_ice should be true, otherewise there will be no output
Expand Down
3 changes: 1 addition & 2 deletions env/levante.dkrz.de/shell.gnu
Original file line number Diff line number Diff line change
Expand Up @@ -18,8 +18,7 @@ export FC=mpif90 CC=mpicc CXX=mpicxx
# following is only needed for libblas which is needed by params lib and often provided by lapack
#module load intel-oneapi-mkl/2022.0.1-gcc-11.2.0
# so use the LD_LIBRARY_PATH or other paths like prefix paths etc for cmake
#export LD_LIBRARY_PATH=/sw/spack-levante/intel-oneapi-mkl-2022.0.1-ttdktf/mkl/2022.0.1/lib/intel64:$LD_LIBRARY_PATH
spack load intel-oneapi-mkl@2022.0.1%gcc@11.2.0
#export LD_LIBRARY_PATH=/sw/spack-levante/intel-oneapi-mkl-2022.0.1-ttdktf/mkl/2022.0.1/lib/intel64:$LD_LIBRARY_PATH spack load [email protected]%[email protected]

#other alternative blas
#spack load [email protected]%[email protected]
Expand Down
4 changes: 2 additions & 2 deletions src/MOD_PARTIT.F90
Original file line number Diff line number Diff line change
Expand Up @@ -5,12 +5,12 @@ module MOD_PARTIT
USE, intrinsic :: ISO_FORTRAN_ENV, only : int32
USE MOD_WRITE_BINARY_ARRAYS
USE MOD_READ_BINARY_ARRAYS
USE mpi
#if defined(_OPENMP)
USE OMP_LIB
#endif
IMPLICIT NONE
SAVE
include 'mpif.h'
integer, parameter :: MAX_LAENDERECK=16
integer, parameter :: MAX_NEIGHBOR_PARTITIONS=32

Expand Down Expand Up @@ -217,4 +217,4 @@ subroutine READ_T_PARTIT(partit, unit, iostat, iomsg)
read(unit, iostat=iostat, iomsg=iomsg) partit%pe_status
end subroutine READ_T_PARTIT

end module MOD_PARTIT
end module MOD_PARTIT
2 changes: 1 addition & 1 deletion src/fortran_utils.F90
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
! synopsis: basic Fortran utilities, no MPI, dependencies only to INTRINSIC modules
module fortran_utils
use mpi
implicit none

contains
Expand Down Expand Up @@ -48,7 +49,6 @@ function mpirank_to_txt(mpicomm) result(txt)
integer mype
integer npes
integer mpierr
include 'mpif.h'

call MPI_Comm_Rank(mpicomm, mype, mpierr)
call MPI_Comm_Size(mpicomm, npes, mpierr)
Expand Down
515 changes: 389 additions & 126 deletions src/gen_modules_diag.F90

Large diffs are not rendered by default.

3 changes: 1 addition & 2 deletions src/gen_modules_partitioning.F90
Original file line number Diff line number Diff line change
Expand Up @@ -113,7 +113,7 @@ subroutine par_ex(COMM, mype, abort) ! finalizes MPI
#ifndef __oasis
if (present(abort)) then
if (mype==0) write(*,*) 'Run finished unexpectedly!'
call MPI_ABORT(MPI_COMM_WORLD, 1 )
call MPI_ABORT(MPI_COMM_WORLD, 1, error)
else
! TODO: this is where fesom standalone, ifsinterface etc get to
!1. there no abort actually even when model calls abort, and barrier may hang
Expand Down Expand Up @@ -580,4 +580,3 @@ subroutine status_check(partit)
call par_ex(partit%MPI_COMM_FESOM, partit%mype, 1)
endif
end subroutine status_check

13 changes: 7 additions & 6 deletions src/gen_surface_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -683,9 +683,10 @@ SUBROUTINE nc_sbc_ini(partit, mesh)
end do
! interpolate in time

if (partit%mype==0) then
write(*,*) 'sbc_do --> mstep:',mstep, ' rdate=', rdate
end if
!!PS if (partit%mype==0) then
!!PS write(*,*) 'sbc_do --> mstep:',mstep, ' rdate=', rdate
!!PS end if

call data_timeinterp(rdate, partit)
END SUBROUTINE nc_sbc_ini

Expand Down Expand Up @@ -1577,9 +1578,9 @@ SUBROUTINE sbc_do(partit, mesh)
end if
#endif

if (partit%mype==0) then
write(*,*) 'sbc_do --> mstep:',mstep, ' rdate=', rdate
end if
!!PS if (partit%mype==0) then
!!PS write(*,*) 'sbc_do --> mstep:',mstep, ' rdate=', rdate
!!PS end if

! interpolate in time
call data_timeinterp(rdate, partit)
Expand Down
3 changes: 1 addition & 2 deletions src/ifs_interface/mpp_io.F90
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
!-----------------------------------------------------

MODULE mpp_io
USE mpi
#if defined(__MULTIO)
USE iom, only : iom_enable_multio, iom_initialize, iom_init_server, iom_finalize
#endif
Expand All @@ -30,7 +31,6 @@ MODULE mpp_io

SUBROUTINE mpp_io_init( iicomm, lio, irequired, iprovided, lmpi1 )

INCLUDE "mpif.h"
INTEGER, INTENT(INOUT) :: iicomm
LOGICAL, INTENT(INOUT) :: lio
INTEGER, INTENT(INOUT) :: irequired, iprovided
Expand Down Expand Up @@ -126,7 +126,6 @@ SUBROUTINE mpp_io_init_2( iicomm )
INTEGER :: icode, ierr, icolor, iicommx, iicommm, iicommo
INTEGER :: ji,inum
LOGICAL :: lcompp
INCLUDE "mpif.h"

! Construct multio server communicator

Expand Down
35 changes: 33 additions & 2 deletions src/io_meandata.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1141,8 +1141,11 @@ subroutine ini_mean_io(ice, dynamics, tracers, partit, mesh)
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_temp_SD_tot' , 'tot. temperature DVD \n (Banerjee et al. 2023)' , 'K^2/s' , dvd_SD_tot( :,:,1), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_temp_SD_advh', 'temperature DVD horiz. adv.' , 'K^2/s' , dvd_SD_chi_adv_h( :,:,1), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_temp_SD_advv', 'temperature DVD vert. adv. ' , 'K^2/s' , dvd_SD_chi_adv_v( :,:,1), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_temp_SD_difh', 'temperature DVD horiz. diff. expl.' , 'K^2/s' , dvd_SD_chi_dif_he( :,:,1), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
if (Redi .eqv. .False. .and. K_hor /= 0.0_WP) then
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_temp_SD_difh', 'temperature DVD horiz. diff. expl.' , 'K^2/s' , dvd_SD_chi_dif_he( :,:,1), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
end if
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_temp_SD_difvi', 'temperature DVD vert. diff. impl.' , 'K^2/s' , dvd_SD_chi_dif_vi( :,:,1), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_temp_SD_difsbc', 'temperature DVD sbc.' , 'K^2/s' , dvd_SD_chi_dif_sbc(:,:,1), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
if (.not. tracers%data(1)%i_vert_diff) then
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_temp_SD_difve', 'temperature DVD vert. diff. expl.' , 'K^2/s' , dvd_SD_chi_dif_ve( :,:,1), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
end if
Expand All @@ -1151,6 +1154,7 @@ subroutine ini_mean_io(ice, dynamics, tracers, partit, mesh)
end if
if (Redi) then
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_temp_SD_difheR', 'temperature DVD horiz. redi diff. expl.' , 'K^2/s' , dvd_SD_chi_dif_heR(:,:,1), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)

call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_temp_SD_difveR', 'temperature DVD vert. redi diff. expl.' , 'K^2/s' , dvd_SD_chi_dif_veR(:,:,1), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_temp_SD_difviR', 'temperature DVD vert. redi diff. impl.' , 'K^2/s' , dvd_SD_chi_dif_viR(:,:,1), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
end if
Expand All @@ -1160,8 +1164,11 @@ subroutine ini_mean_io(ice, dynamics, tracers, partit, mesh)
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_salt_SD_tot' , 'tot. salinity DVD \n (Banerjee et al. 2023)' , 'K^2/s' , dvd_SD_tot( :,:,2), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_salt_SD_advh', 'salinity DVD horiz. adv.' , 'K^2/s' , dvd_SD_chi_adv_h( :,:,2), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_salt_SD_advv', 'salinity DVD vert. adv. ' , 'K^2/s' , dvd_SD_chi_adv_v( :,:,2), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_salt_SD_difh', 'salinity DVD horiz. diff. expl.' , 'K^2/s' , dvd_SD_chi_dif_he( :,:,2), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
if (Redi .eqv. .False. .and. K_hor /= 0.0_WP) then
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_salt_SD_difh', 'salinity DVD horiz. diff. expl.' , 'K^2/s' , dvd_SD_chi_dif_he( :,:,2), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
end if
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_salt_SD_difvi', 'salinity DVD vert. diff. impl.' , 'K^2/s' , dvd_SD_chi_dif_vi( :,:,2), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_salt_SD_difsbc','salinity DVD sbc.' , 'K^2/s' , dvd_SD_chi_dif_sbc(:,:,2), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
if (.not. tracers%data(1)%i_vert_diff) then
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_salt_SD_difve', 'salinity DVD vert. diff. expl.' , 'K^2/s' , dvd_SD_chi_dif_ve( :,:,2), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
end if
Expand All @@ -1170,6 +1177,7 @@ subroutine ini_mean_io(ice, dynamics, tracers, partit, mesh)
end if
if (Redi) then
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_salt_SD_difheR', 'salinity DVD horiz. redi diff. expl.' , 'K^2/s' , dvd_SD_chi_dif_heR(:,:,2), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)

call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_salt_SD_difveR', 'salinity DVD vert. redi diff. expl.' , 'K^2/s' , dvd_SD_chi_dif_veR(:,:,2), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D/), 'dvd_salt_SD_difviR', 'salinity DVD vert. redi diff. impl.' , 'K^2/s' , dvd_SD_chi_dif_viR(:,:,2), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
end if
Expand Down Expand Up @@ -1200,6 +1208,29 @@ subroutine ini_mean_io(ice, dynamics, tracers, partit, mesh)
end if
end if

!_______________________________________________________________________________
! compute squared velocities of u, v, w
CASE ('UVW_SQR ')
if (ldiag_uvw_sqr) then
!___temperature DVD_____________________________________________________
call def_stream((/nl-1, elem2D/), (/nl-1, myDim_elem2D/), 'u2' , 'squared zonal velocity' , 'm^2/s^2' , uv2(1,:,:), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
call def_stream((/nl-1, elem2D/), (/nl-1, myDim_elem2D/), 'v2' , 'squared meridional velocity', 'm^2/s^2' , uv2(2,:,:), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
call def_stream((/nl-1, nod2D/) , (/nl-1, myDim_nod2D/) , 'w2' , 'squared vertical velocity' , 'm^2/s^2' , wvel2(:,:), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
end if !--> if (ldiag_DVD) then

!_______________________________________________________________________________
! compute horizontal and vertical tracer gradients
CASE ('TRGRD_XYZ ')
if (ldiag_trgrd_xyz) then
call def_stream((/nl-1, elem2D/), (/nl-1, myDim_elem2D/), 'temp_grdx', 'zonal temperature gradient', 'K/m', trgrd_x(1,:,:), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
call def_stream((/nl-1, elem2D/), (/nl-1, myDim_elem2D/), 'temp_grdy', 'meridional temperature gradient', 'K/m', trgrd_y(1,:,:), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D /), 'temp_grdz', 'vertical temperature gradient', 'K/m', trgrd_z(1,:,:), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)

call def_stream((/nl-1, elem2D/), (/nl-1, myDim_elem2D/), 'salt_grdx', 'zonal salinity gradient', 'psu/m', trgrd_x(2,:,:), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
call def_stream((/nl-1, elem2D/), (/nl-1, myDim_elem2D/), 'salt_grdy', 'meridional salinity gradient', 'psu/m', trgrd_y(2,:,:), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
call def_stream((/nl-1, nod2D/), (/nl-1, myDim_nod2D /), 'salt_grdz', 'vertical salinity gradient', 'psu/m', trgrd_z(2,:,:), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, partit, mesh)
end if !--> if (ldiag_DVD) then

!_______________________________________________________________________________
CASE DEFAULT
if (mype==0) write(*,*) 'stream ', io_list(i)%id, ' is not defined !'
Expand Down
6 changes: 2 additions & 4 deletions src/io_restart.F90
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ MODULE io_RESTART
use MOD_PARTIT
use MOD_PARSUP
use fortran_utils
use mpi
#if defined(__recom)
use recom_glovar
use recom_config
Expand Down Expand Up @@ -771,7 +772,6 @@ subroutine read_all_raw_restarts(mpicomm, mype)
integer fileunit
integer status
integer mpierr
include 'mpif.h'

if(mype == RAW_RESTART_METADATA_RANK) then
! read metadata info for the raw restart
Expand Down Expand Up @@ -860,7 +860,6 @@ subroutine finalize_restart()
!
!_______________________________________________________________________________
subroutine read_restart(path, filegroup, mpicomm, mype)
include 'mpif.h'
character(len=*), intent(in) :: path
type(restart_file_group), intent(inout) :: filegroup
integer, intent(in) :: mpicomm
Expand Down Expand Up @@ -1004,12 +1003,11 @@ function is_due(unit, frequency, istep) result(d)
! integer mype
! integer npes
! integer mpierr
! include 'mpif.h'
!
! call MPI_Comm_Rank(mpicomm, mype, mpierr)
! call MPI_Comm_Size(mpicomm, npes, mpierr)
! txt = int_to_txt_pad(mype,int(log10(real(npes)))+1) ! pad to the width of the number of processes
! end function
!!PS --> move this function also to fortran_utils.F90

end module
end module
4 changes: 2 additions & 2 deletions src/temp/MOD_PARTIT.F90
Original file line number Diff line number Diff line change
Expand Up @@ -5,9 +5,9 @@ module MOD_PARTIT
USE, intrinsic :: ISO_FORTRAN_ENV
USE MOD_WRITE_BINARY_ARRAYS
USE MOD_READ_BINARY_ARRAYS
USE mpi
IMPLICIT NONE
SAVE
include 'mpif.h'
integer, parameter :: MAX_LAENDERECK=16
integer, parameter :: MAX_NEIGHBOR_PARTITIONS=32

Expand Down Expand Up @@ -186,4 +186,4 @@ subroutine READ_T_PARTIT(partit, unit, iostat, iomsg)
read(unit, iostat=iostat, iomsg=iomsg) partit%pe_status
end subroutine READ_T_PARTIT

end module MOD_PARTIT
end module MOD_PARTIT
43 changes: 21 additions & 22 deletions work/job_albedo_chain
Original file line number Diff line number Diff line change
Expand Up @@ -97,25 +97,6 @@ cp -n ../config/namelist.ice .
cp -n ../config/namelist.io .
cp -n ../config/namelist.icepack .

#___SET CHAIN_ID________________________________________________________________
if [ -f "file_chain_id" ]; then
chain_id=$(<file_chain_id)
else
chain_id=${chain_s}
echo $chain_id > file_chain_id
fi

#___PRINT INPUT INFO____________________________________________________________
echo -e "\033[1;7;33m_____JOB CHAIN INFO_____________________________________\033[0m"
echo -e "\033[1;33m --> actual chain cycle: $chain_id \033[0m"
echo -e "\033[1;33m --> max. number of chain cycles: $chain_n \033[0m"
echo -e "\033[1;33m --> simulated time range: [ $year_s $year_e] \033[0m"
echo -e "\033[1;33m --> slurm: wall-clock-time = $wcl \033[0m"
echo -e "\033[1;33m --> slurm: ntasks = $ntasks \033[0m"
echo -e "\033[1;33m --> slurm: nnodes = $nnodes \033[0m"
if [ $prescribe_rlen -ne 0 ]; then
echo -e "\033[1;33m -->change run_length = $prescribe_rlen \033[0m"
fi

#___CREATE SAVE DIR INFRASTRUCTURE______________________________________________
# extract resultpath from namelist.config
Expand Down Expand Up @@ -148,6 +129,25 @@ fi
# identify real path in case a link is used
dname_result="$(realpath "$dname_result")/"

#___SET CHAIN_ID________________________________________________________________
if [ -f "${dname_result}/file_chain_id" ]; then
chain_id=$(<${dname_result}/file_chain_id)
else
chain_id=${chain_s}
echo $chain_id > ${dname_result}/file_chain_id
fi
#___PRINT INPUT INFO____________________________________________________________
echo -e "\033[1;7;33m_____JOB CHAIN INFO_____________________________________\033[0m"
echo -e "\033[1;33m --> actual chain cycle: $chain_id \033[0m"
echo -e "\033[1;33m --> max. number of chain cycles: $chain_n \033[0m"
echo -e "\033[1;33m --> simulated time range: [ $year_s $year_e] \033[0m"
echo -e "\033[1;33m --> slurm: wall-clock-time = $wcl \033[0m"
echo -e "\033[1;33m --> slurm: ntasks = $ntasks \033[0m"
echo -e "\033[1;33m --> slurm: nnodes = $nnodes \033[0m"
if [ $prescribe_rlen -ne 0 ]; then
echo -e "\033[1;33m -->change run_length = $prescribe_rlen \033[0m"
fi

# if directory for chain_id doesn't exist --> create it
if [ ! -d "${dname_result}/${chain_id}" ]; then
echo -e "\033[33m --> chain_id directory does not exist --> will create it \033[0m"
Expand Down Expand Up @@ -234,8 +234,7 @@ if [ $is_newsimul -eq 1 ] ; then

#___BACKUP NAMELIST.* FILES INTO RESULT DIRECTORY_______________________

cp namelist.config namelist.oce namelist.ice namelist.forcing namelist.io \
namelist.dyn namelist.tra namelist.cvmix ${dname_result}/.
cp namelist.* ${dname_result}/.
cp fesom.x ${dname_result}/.

#___BACKUP SRC FILES INTO RESULT DIRECTORY__________________________________
Expand Down Expand Up @@ -335,6 +334,6 @@ fi
# check if complete cycle is finished only than increase chain_id
if [ $aux_yr_clock -gt $year_e ] && [ ${chain_id} -lt ${chain_n} ] ; then
chain_id=$(( $chain_id + 1 ))
echo $chain_id > file_chain_id
echo $chain_id > ${dname_result}/file_chain_id
fi

0 comments on commit a6a0ba4

Please sign in to comment.