From bff915a58472b9ad7d65def980c81c6c6f4c7325 Mon Sep 17 00:00:00 2001 From: Philippe WAUTELET <philippe.wautelet@aero.obs-mip.fr> Date: Wed, 10 Apr 2024 15:42:53 +0200 Subject: [PATCH] Philippe 10/04/2024: outputs: add LOUT_PHYSICAL_SIMPLIFIED in NAM_OUTPUT to allow to write all fields with the same number of points even if not on same Arakawa grid position --- src/LIB/SURCOUCHE/src/mode_io_field_write.f90 | 7 ++--- src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90 | 26 ++++++++++++++----- src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 | 25 +++++++++++++++--- src/MNH/modd_bakout.f90 | 6 +++++ src/MNH/modn_output.f90 | 1 + 5 files changed, 53 insertions(+), 12 deletions(-) diff --git a/src/LIB/SURCOUCHE/src/mode_io_field_write.f90 b/src/LIB/SURCOUCHE/src/mode_io_field_write.f90 index b0a8dda19..bab51c4c1 100644 --- a/src/LIB/SURCOUCHE/src/mode_io_field_write.f90 +++ b/src/LIB/SURCOUCHE/src/mode_io_field_write.f90 @@ -3961,6 +3961,7 @@ END SUBROUTINE IO_Fieldlist_write SUBROUTINE IO_Fieldlist_1field_write( TPOUTPUT, KMI, TPFIELD, TPBOX ) +USE MODD_BAKOUT, ONLY: LOUT_PHYSICAL_SIMPLIFIED USE MODD_DIM_n, ONLY: NIMAX_ll, NJMAX_ll, NKMAX USE MODD_FIELD, ONLY: NMNHDIM_BOX_NI, NMNHDIM_BOX_NJ, NMNHDIM_BOX_NI_U, NMNHDIM_BOX_NJ_U, NMNHDIM_BOX_NI_V, & NMNHDIM_BOX_NJ_V, NMNHDIM_BOX_LEVEL, NMNHDIM_BOX_LEVEL_W, NMNHDIM_NOTLISTED, & @@ -4286,19 +4287,19 @@ NDIMS: SELECT CASE (TPFIELD%NDIMS) TZFIELDMD%NDIMLIST(3) = NMNHDIM_BOX_LEVEL_W END SELECT END IF - IF ( TPBOX%CNAME == CMAINDOMAINNAME .AND. TZFIELDMD%NGRID == 2 ) THEN + IF ( TPBOX%CNAME == CMAINDOMAINNAME .AND. TZFIELDMD%NGRID == 2 .AND. .NOT.LOUT_PHYSICAL_SIMPLIFIED ) THEN ! There is one more PHYSICAL horizontal layer for u points (but the same number for physical + unphysical borders) IISUP = MIN( JPHEXT + TPBOX%NISUP + 1, NIMAX_ll + 2*JPHEXT ) ELSE IISUP = JPHEXT + TPBOX%NISUP END IF - IF ( TPBOX%CNAME == CMAINDOMAINNAME .AND. TZFIELDMD%NGRID == 3 ) THEN + IF ( TPBOX%CNAME == CMAINDOMAINNAME .AND. TZFIELDMD%NGRID == 3 .AND. .NOT.LOUT_PHYSICAL_SIMPLIFIED ) THEN ! There is one more PHYSICAL horizontal layer for v points (but the same number for physical + unphysical borders) IJSUP = MIN( JPHEXT + TPBOX%NJSUP + 1, NJMAX_ll + 2*JPHEXT ) ELSE IJSUP = JPHEXT + TPBOX%NJSUP END IF - IF ( TPBOX%CNAME == CMAINDOMAINNAME .AND. TZFIELDMD%NGRID == 4 ) THEN + IF ( TPBOX%CNAME == CMAINDOMAINNAME .AND. TZFIELDMD%NGRID == 4 .AND. .NOT.LOUT_PHYSICAL_SIMPLIFIED ) THEN ! There is one more PHYSICAL vertical layer for w points (but the same number for physical + unphysical borders) IKSUP = MIN( JPVEXT + TPBOX%NKSUP + 1, NKMAX + 2*JPVEXT ) ELSE diff --git a/src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90 b/src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90 index 438a3218c..d60ce3f8a 100644 --- a/src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90 +++ b/src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90 @@ -248,6 +248,7 @@ END SUBROUTINE IO_Dimids_guess_nc4 SUBROUTINE IO_Knowndims_set_nc4(TPFILE,HPROGRAM_ORIG) +use modd_bakout, only: lout_physical_simplified use modd_budget, only: cbutype, lbu_icp, lbu_jcp, lbu_kcp, nbuimax_ll, nbujmax_ll, nbukmax, nbumask, nbutotwrite use modd_lbc_n, only: clbcx, clbcy USE MODD_CONF, ONLY: CPROGRAM, l2d, lpack @@ -341,17 +342,30 @@ end if call IO_Add_dim_nc4( tpfile, NMNHDIM_NI, 'ni', IIU_ll ) call IO_Add_dim_nc4( tpfile, NMNHDIM_NJ, 'nj', IJU_ll ) -! There is one more PHYSICAL horizontal layer for u points (but the same number for physical + unphysical borders) -call IO_Add_dim_nc4( tpfile, NMNHDIM_NI_U, 'ni_u', MIN( IIU_ll+1, IIU_MAX ) ) +if ( tpfile%ctype == 'MNHOUTPUT' .and. lout_physical_simplified ) then + call IO_Add_dim_nc4( tpfile, NMNHDIM_NI_U, 'ni_u', IIU_ll ) +else + ! There is one more PHYSICAL horizontal layer for u points (but the same number for physical + unphysical borders) + call IO_Add_dim_nc4( tpfile, NMNHDIM_NI_U, 'ni_u', MIN( IIU_ll+1, IIU_MAX ) ) +end if call IO_Add_dim_nc4( tpfile, NMNHDIM_NJ_U, 'nj_u', IJU_ll ) call IO_Add_dim_nc4( tpfile, NMNHDIM_NI_V, 'ni_v', IIU_ll ) -! There is one more PHYSICAL horizontal layer for v points (but the same number for physical + unphysical borders) -call IO_Add_dim_nc4( tpfile, NMNHDIM_NJ_V, 'nj_v', MIN( IJU_ll+1, IJU_MAX ) ) +if ( tpfile%ctype == 'MNHOUTPUT' .and. lout_physical_simplified ) then + call IO_Add_dim_nc4( tpfile, NMNHDIM_NJ_V, 'nj_v', IJU_ll ) +else + ! There is one more PHYSICAL horizontal layer for v points (but the same number for physical + unphysical borders) + call IO_Add_dim_nc4( tpfile, NMNHDIM_NJ_V, 'nj_v', MIN( IJU_ll+1, IJU_MAX ) ) +end if + if ( Trim( yprogram ) /= 'PGD' .and. Trim( yprogram ) /= 'NESPGD' .and. Trim( yprogram ) /= 'ZOOMPG' & .and. .not. ( Trim( yprogram ) == 'REAL' .and. cstorage_type == 'SU' ) ) then !condition to detect PREP_SURFEX call IO_Add_dim_nc4( tpfile, NMNHDIM_LEVEL, 'level', IKU ) - ! There is one more PHYSICAL vertical layer for w points (but the same number for physical + unphysical borders) - call IO_Add_dim_nc4( tpfile, NMNHDIM_LEVEL_W, 'level_w', MIN( IKU+1, IKU_MAX ) ) + if ( tpfile%ctype == 'MNHOUTPUT' .and. lout_physical_simplified ) then + call IO_Add_dim_nc4( tpfile, NMNHDIM_LEVEL_W, 'level_w', IKU ) + else + ! There is one more PHYSICAL vertical layer for w points (but the same number for physical + unphysical borders) + call IO_Add_dim_nc4( tpfile, NMNHDIM_LEVEL_W, 'level_w', MIN( IKU+1, IKU_MAX ) ) + end if if ( tpfile%ctype /= 'MNHDIACHRONIC' ) & call IO_Add_dim_nc4( tpfile, NMNHDIM_TIME, 'time', Int( NF90_UNLIMITED, kind = Kind(1) ) ) end if diff --git a/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 b/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 index 8bdbea5ae..b6707b7ca 100644 --- a/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 +++ b/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 @@ -1439,6 +1439,7 @@ end subroutine IO_Field_partial_write_nc4_N4 subroutine IO_Coordvar_write_nc4( tpfile, hprogram_orig, tpdtmodeln ) use modd_aircraft_balloon +use modd_bakout, only: lout_physical_simplified use modd_budget, only: cbutype, lbu_icp, lbu_jcp, lbu_kcp, nbuih, nbuil, nbujh, nbujl, nbukh, nbukl, nbukmax, & nbustep, nbutotwrite use modd_conf, only: cprogram, l2d, lcartesian @@ -1610,20 +1611,38 @@ else ijm_max = tout_boxes(0)%njsup + jphext iiu_min = iim_min - iiu_max = min( iim_max + 1, nimax_ll + 2 * jphext ) + if ( lout_physical_simplified ) then + ! Take the same number of points for the ni and ni_u dimensions + ! And therefore, drop the last physical point of ni_u if the unphysical borders are removed + iiu_max = iim_max + else + iiu_max = min( iim_max + 1, nimax_ll + 2 * jphext ) + end if iju_min = ijm_min iju_max = ijm_max iiv_min = iim_min iiv_max = iim_max ijv_min = ijm_min - ijv_max = min( ijm_max + 1, njmax_ll + 2 * jphext ) + if ( lout_physical_simplified ) then + ! Take the same number of points for the nj and nj_v dimensions + ! And therefore, drop the last physical point of nj_v if the unphysical borders are removed + ijv_max = ijm_max + else + ijv_max = min( ijm_max + 1, njmax_ll + 2 * jphext ) + end if ikm_min = tout_boxes(0)%nkinf + JPVEXT ikm_max = tout_boxes(0)%nksup + JPVEXT ikw_min = ikm_min - ikw_max = min( ikm_max + 1, nkmax + 2 * JPVEXT ) + if ( lout_physical_simplified ) then + ! Take the same number of points for the level and level_w dimensions + ! And therefore, drop the upper physical point of level_w if the unphysical borders are removed + ikw_max = ikm_max + else + ikw_max = min( ikm_max + 1, nkmax + 2 * JPVEXT ) + end if ! Coordinates: number of unphysical values on boundaries iim_bdmin = max( 0, jphext - iim_min + 1 ) diff --git a/src/MNH/modd_bakout.f90 b/src/MNH/modd_bakout.f90 index 30d1f432f..8048bb601 100644 --- a/src/MNH/modd_bakout.f90 +++ b/src/MNH/modd_bakout.f90 @@ -104,6 +104,12 @@ LOGICAL, DIMENSION(JPMODELMAX) :: LOUT_TOP_ABSORBING_LAYER_REMOVE = .TRUE. ! LOGICAL, DIMENSION(JPMODELMAX) :: LOUT_UNPHYSICAL_HOR_CELLS_REMOVE = .TRUE. ! Remove the JPHEXT horizontal external points LOGICAL, DIMENSION(JPMODELMAX) :: LOUT_UNPHYSICAL_VER_CELLS_REMOVE = .TRUE. ! Remove the JPVEXT vertical external points +! If LOUT_PHYSICAL_SIMPLIFIED=.TRUE., simplify the box boundaries by removing some physical points at end of domain depending +! on the position on the Arakawa grid to get the same dimensions for all coordinates +! If .FALSE., variables at different point locations in the Arakawa grids can have different dimensions (ie u-points have 1 more +! physical position in the X direction) +LOGICAL :: LOUT_PHYSICAL_SIMPLIFIED = .FALSE. + INTEGER, DIMENSION(:,:), ALLOCATABLE :: NOUT_BOX_IINF ! Box coordinates in physical domain (for each model and for each box) INTEGER, DIMENSION(:,:), ALLOCATABLE :: NOUT_BOX_ISUP INTEGER, DIMENSION(:,:), ALLOCATABLE :: NOUT_BOX_JINF diff --git a/src/MNH/modn_output.f90 b/src/MNH/modn_output.f90 index 8bf8f2e89..c76dd2372 100644 --- a/src/MNH/modn_output.f90 +++ b/src/MNH/modn_output.f90 @@ -58,6 +58,7 @@ NAMELIST/NAM_OUTPUT/LOUT_BEG,LOUT_END,& LOUT_MAINDOMAIN_WRITE, & LOUT_BOTTOM_ABSORBING_LAYER_REMOVE, LOUT_TOP_ABSORBING_LAYER_REMOVE, & LOUT_UNPHYSICAL_HOR_CELLS_REMOVE, LOUT_UNPHYSICAL_VER_CELLS_REMOVE, & + LOUT_PHYSICAL_SIMPLIFIED, & NOUT_BOX_IINF, NOUT_BOX_ISUP, NOUT_BOX_JINF, NOUT_BOX_JSUP, NOUT_BOX_KINF, NOUT_BOX_KSUP LOGICAL, SAVE, PRIVATE :: LOUTPUT_NML_ALLOCATED = .FALSE. -- GitLab