diff --git a/LIBTOOLS/tools/lfi2cdf/src/lfi2cdf.f90 b/LIBTOOLS/tools/lfi2cdf/src/lfi2cdf.f90 index b76d3ce23ec63b22b700e02498d2bbb17e84e34a..3148788174a6b3c2680a20190e242206c8fe5fcd 100644 --- a/LIBTOOLS/tools/lfi2cdf/src/lfi2cdf.f90 +++ b/LIBTOOLS/tools/lfi2cdf/src/lfi2cdf.f90 @@ -94,7 +94,7 @@ program LFI2CDF CALL OPEN_FILES(infiles, outfiles, nfiles_out, hinfile, houtfile, nbvar_infile, options, runmode) IF (options(OPTLIST)%set) STOP - !Set and initialize parallel variables (necessary to read splitted files) + !Set and initialize parallel variables (necessary to read split files) CALL SET_JP_ll(1,JPHEXT,JPVEXT,JPHEXT) CALL SET_DAD0_ll() CALL SET_DIM_ll(NIMAX_ll, NJMAX_ll, NKMAX) diff --git a/src/LIB/SURCOUCHE/src/modd_io.f90 b/src/LIB/SURCOUCHE/src/modd_io.f90 index 0970816a79d818c1150ed40ec0e0a9bbe20e5db2..45e24dad1fd9eb35accad4ec3be5fa07879e3706 100644 --- a/src/LIB/SURCOUCHE/src/modd_io.f90 +++ b/src/LIB/SURCOUCHE/src/modd_io.f90 @@ -63,7 +63,7 @@ TYPE TOUTBAK REAL :: XTIME !Time from start of the segment (in seconds and rounded to a timestep) INTEGER :: NOUTDAD = -1 !Index of the corresponding dad file (file with same time) TYPE(TFILEDATA),POINTER :: TFILE => NULL() !Corresponding file - TYPE(TFILE_ELT),DIMENSION(:),ALLOCATABLE :: TFILE_IOZ !Corresponding Z-splitted files + TYPE(TFILE_ELT),DIMENSION(:),ALLOCATABLE :: TFILE_IOZ !Corresponding Z-split files INTEGER,DIMENSION(:),POINTER :: NFIELDLIST => NULL() !List of the fields to read or write END TYPE TOUTBAK @@ -84,10 +84,10 @@ TYPE TFILEDATA LOGICAL :: LMASTER = .FALSE. !True if process is master of the file (process that open/read/write/close) LOGICAL :: LMULTIMASTERS = .FALSE. !True if several processes may access the file ! - INTEGER :: NSUBFILES_IOZ = 0 !Number of sub-files (Z-splitted files based on this file) + INTEGER :: NSUBFILES_IOZ = 0 !Number of sub-files (Z-split files based on this file) !For example if 2 sub-files and this file is abcd, !the 2 sub-files are abcd.Z001 and abcd.Z002 - TYPE(TFILE_ELT),DIMENSION(:),ALLOCATABLE :: TFILES_IOZ !Corresponding Z-splitted files + TYPE(TFILE_ELT),DIMENSION(:),ALLOCATABLE :: TFILES_IOZ !Corresponding Z-split files ! INTEGER :: NMODEL = 0 !Model number corresponding to the file (field not always set) INTEGER,DIMENSION(3) :: NMNHVERSION = (/0,0,0/) !MesoNH version used to create the file diff --git a/src/LIB/SURCOUCHE/src/mode_io_manage_struct.f90 b/src/LIB/SURCOUCHE/src/mode_io_manage_struct.f90 index 048674922b786b9df234490873d068edc6ce311c..5a16d2be23830f8c094e1b0f1fa77221f626fcec 100644 --- a/src/LIB/SURCOUCHE/src/mode_io_manage_struct.f90 +++ b/src/LIB/SURCOUCHE/src/mode_io_manage_struct.f90 @@ -575,7 +575,7 @@ SUBROUTINE POPULATE_STRUCT(TPFILE_FIRST,TPFILE_LAST,KSTEPS,HFILETYPE,TPBAKOUTN) CALL PRINT_MSG(NVERB_FATAL,'IO','POPULATE_STRUCT','unknown backup/output fileformat') ENDIF ! - !Create file structures if Z-splitted files + !Create file structures if Z-split files IF (NB_PROCIO_W>1) THEN ALLOCATE(TPBAKOUTN(IPOS)%TFILE%TFILES_IOZ(NB_PROCIO_W)) ! ALLOCATE(TPBAKOUTN(IPOS)%TFILE_IOZ(NB_PROCIO_W)) diff --git a/src/LIB/SURCOUCHE/src/mode_io_write_lfi.f90 b/src/LIB/SURCOUCHE/src/mode_io_write_lfi.f90 index 0ec7744765e80f6213d09536da78c95a03946679..ad371a956cdb549ce923756990f053a498d200b8 100644 --- a/src/LIB/SURCOUCHE/src/mode_io_write_lfi.f90 +++ b/src/LIB/SURCOUCHE/src/mode_io_write_lfi.f90 @@ -134,8 +134,8 @@ TYPE(TFILEDATA),TARGET,INTENT(IN) :: TPFILE TYPE(TFIELDDATA), INTENT(IN) :: TPFIELD REAL,DIMENSION(:,:), INTENT(IN) :: PFIELD ! array containing the data field INTEGER, INTENT(OUT):: KRESP ! return-code if problems araised -INTEGER,OPTIONAL, INTENT(IN) :: KVERTLEVEL ! Number of the vertical level (needed for Z-level splitted files) -INTEGER,OPTIONAL, INTENT(IN) :: KZFILE ! Number of the Z-level splitted file +INTEGER,OPTIONAL, INTENT(IN) :: KVERTLEVEL ! Number of the vertical level (needed for Z-level split files) +INTEGER,OPTIONAL, INTENT(IN) :: KZFILE ! Number of the Z-level split file ! !* 0.2 Declarations of local variables ! diff --git a/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 b/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 index 5441ca49543948a8d8e31a74dd16c201bffc894c..e63dc8f88349bee2c1dd6237f2f85ded0f4f0226 100644 --- a/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 +++ b/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 @@ -488,8 +488,8 @@ TYPE(TFILEDATA),TARGET,INTENT(IN) :: TPFILE TYPE(TFIELDDATA), INTENT(IN) :: TPFIELD REAL,DIMENSION(:,:), INTENT(IN) :: PFIELD ! array containing the data field INTEGER, INTENT(OUT):: KRESP -INTEGER,OPTIONAL, INTENT(IN) :: KVERTLEVEL ! Number of the vertical level (needed for Z-level splitted files) -INTEGER,OPTIONAL, INTENT(IN) :: KZFILE ! Number of the Z-level splitted file +INTEGER,OPTIONAL, INTENT(IN) :: KVERTLEVEL ! Number of the vertical level (needed for Z-level split files) +INTEGER,OPTIONAL, INTENT(IN) :: KZFILE ! Number of the Z-level split file LOGICAL,OPTIONAL, INTENT(IN) :: OISCOORD ! Is a coordinate variable (->do not write coordinates attribute) ! INTEGER(KIND=IDCDF_KIND) :: STATUS diff --git a/src/LIB/SURCOUCHE/src/mode_tools_ll.f90 b/src/LIB/SURCOUCHE/src/mode_tools_ll.f90 index 158d5313622d2681529fa70baeb453fce1d293af..da50aae6edd0844bf119a329a0cab9c80544f22d 100644 --- a/src/LIB/SURCOUCHE/src/mode_tools_ll.f90 +++ b/src/LIB/SURCOUCHE/src/mode_tools_ll.f90 @@ -1,4 +1,4 @@ -!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier +!MNH_LIC Copyright 1998-2020 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !MNH_LIC for details. version 1. @@ -2500,7 +2500,7 @@ ENDIF ! INTEGER, INTENT(IN) :: K ! Number of elements of TPSPLIT ! - TYPE(ZONE_ll), INTENT(IN) :: TPZONE ! Zone to be splitted + TYPE(ZONE_ll), INTENT(IN) :: TPZONE ! Zone to be split ! TYPE(ZONE_ll), DIMENSION(:), INTENT(OUT) :: TPRES ! Splitting of the zone ! diff --git a/src/LIB/SURCOUCHE/src/mode_toolsz_ll.f90 b/src/LIB/SURCOUCHE/src/mode_toolsz_ll.f90 index 882201462ac00002f452f7088936eaa8a67453a0..329f75eadbe5e96b7271123af025bbd2d83bdd47 100644 --- a/src/LIB/SURCOUCHE/src/mode_toolsz_ll.f90 +++ b/src/LIB/SURCOUCHE/src/mode_toolsz_ll.f90 @@ -1,4 +1,4 @@ -!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier +!MNH_LIC Copyright 1998-2020 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !MNH_LIC for details. version 1. @@ -1122,7 +1122,7 @@ ! INTEGER, INTENT(IN) :: K ! Number of elements of TPSPLIT ! - TYPE(ZONE_ll), INTENT(IN) :: TPZONE ! Zone to be splitted + TYPE(ZONE_ll), INTENT(IN) :: TPZONE ! Zone to be split ! TYPE(ZONE_ll), DIMENSION(:), INTENT(OUT) :: TPRES ! Splitting of the zone ! diff --git a/src/MNH/calcsound.f90 b/src/MNH/calcsound.f90 index a0b1c5fa1e0deb61f7723d6ac1fba400a2b49707..03acbaba22fb11a10921e2f67dafe4474c8137c0 100644 --- a/src/MNH/calcsound.f90 +++ b/src/MNH/calcsound.f90 @@ -1,13 +1,8 @@ -!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier +!MNH_LIC Copyright 1994-2020 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence -!MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt +!MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !MNH_LIC for details. version 1. !----------------------------------------------------------------- -!--------------- special set of characters for RCS information -!----------------------------------------------------------------- -! $Source$ $Revision$ -! masdev4_7 BUG1 2007/06/15 17:47:17 -!----------------------------------------------------------------- ! ##################### MODULE MODI_CALCSOUND ! ##################### @@ -43,7 +38,7 @@ END MODULE MODI_CALCSOUND !! !!** METHOD !! ------ -!! The horizontal dimensions of model arrays are splitted in arrays of +!! The horizontal dimensions of model arrays are split in arrays of !! 1000 columns. If there is at least 1000 elements, computation is !! made in a static way, otherwise in a dynamical way. !! diff --git a/src/MNH/default_desfmn.f90 b/src/MNH/default_desfmn.f90 index a554e967f003a65d25b075efa39da3ead31f85cc..0beee5be3b761142bdaae5892ec17e894354ddf6 100644 --- a/src/MNH/default_desfmn.f90 +++ b/src/MNH/default_desfmn.f90 @@ -168,7 +168,7 @@ END MODULE MODI_DEFAULT_DESFM_n !! Modifications 25/04/96 (Suhre) add the blank module !! Modifications 29/07/96 (Pinty&Suhre) add module MODD_FRC !! Modifications 11/04/96 (Pinty) add the rain-ice scheme and modify -!! the splitted arrays in MODD_PARAM_RAD_n +!! the split arrays in MODD_PARAM_RAD_n !! Modifications 11/01/97 (Pinty) add the deep convection scheme !! Modifications 24/11/96 (Masson) add LREFRESH_ALL in deep convection !! Modifications 12/02/96 (Lafore) transformation to DEFAULT_DESFM_n for spawning @@ -210,7 +210,7 @@ END MODULE MODI_DEFAULT_DESFM_n !! Modification 24/03/16 (Leriche) remove LCH_SURFACE_FLUX !! put NCH_VEC_LENGTH = 50 instead of 1000 !! -!! 04/2016 (C.LAC) negative contribution to the budget splitted between advection, turbulence and microphysics for KHKO/C2R2 +!! 04/2016 (C.LAC) negative contribution to the budget split between advection, turbulence and microphysics for KHKO/C2R2 !! Modification 01/2016 (JP Pinty) Add LIMA !! Modification 24/03/16 (Leriche) remove LCH_SURFACE_FLUX !! put NCH_VEC_LENGTH = 50 instead of 1000 diff --git a/src/MNH/extend_grid_parameter_mnh.f90 b/src/MNH/extend_grid_parameter_mnh.f90 index 09d06299039e54a684cf25c7ef023918ebc132f2..bf9d369d1fc6faae5410ed4804937b88f58d0e2b 100644 --- a/src/MNH/extend_grid_parameter_mnh.f90 +++ b/src/MNH/extend_grid_parameter_mnh.f90 @@ -1,4 +1,4 @@ -!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier +!MNH_LIC Copyright 2015-2020 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !MNH_LIC for details. version 1. @@ -6,7 +6,7 @@ SUBROUTINE EXTEND_GRID_PARAMETERX1_MNH(HGRID,HREC,KDIM,KSIZE,KIMAX,KJMAX,PFIELD,PFIELD_EXTEND) ! ############################################################# ! -!!**** * - routine to extend a real splitted array on SURFEX halo +!!**** * - routine to extend a real split array on SURFEX halo ! ! Author ! M.Moge 01/03/2015 @@ -33,7 +33,7 @@ INTEGER, INTENT(IN) :: KSIZE ! size of PFIELD_EXTEND INTEGER, INTENT(IN) :: KIMAX !(local) dimension of the domain - X direction INTEGER, INTENT(IN) :: KJMAX !(local) dimension of the domain - Y direction REAL, DIMENSION(KDIM ), INTENT(IN) :: PFIELD ! real field for complete grid -REAL, DIMENSION(KSIZE), INTENT(OUT):: PFIELD_EXTEND! real field for splitted grid +REAL, DIMENSION(KSIZE), INTENT(OUT):: PFIELD_EXTEND! real field for split grid ! !* 0.2 Declarations of local variables ! @@ -150,7 +150,7 @@ END SUBROUTINE EXTEND_GRID_PARAMETERX1_MNH SUBROUTINE EXTEND_GRID_PARAMETERN0_MNH(HGRID,HREC,KFIELD,KFIELD_EXTEND) ! ############################################################# ! -!!**** * - routine to "extend" an integer related to splitted grid on SURFEX halo +!!**** * - routine to "extend" an integer related to split grid on SURFEX halo ! ! ! @@ -165,7 +165,7 @@ IMPLICIT NONE CHARACTER(LEN=10), INTENT(IN) :: HGRID ! grid type CHARACTER(LEN=6), INTENT(IN) :: HREC ! name of the parameter INTEGER, INTENT(IN) :: KFIELD ! integer scalar for complete grid -INTEGER, INTENT(OUT):: KFIELD_EXTEND ! integer scalar for splitted grid +INTEGER, INTENT(OUT):: KFIELD_EXTEND ! integer scalar for split grid !* 0.2 Declarations of local variables ! INTEGER :: IIB, IIE, IJB, IJE diff --git a/src/MNH/lima_inst_procs.f90 b/src/MNH/lima_inst_procs.f90 index a03eed7e3af5aa42c376955b9d8094bde1204feb..ff8dc1f04df51daa9018d3cf8a1778ce4bde2294 100644 --- a/src/MNH/lima_inst_procs.f90 +++ b/src/MNH/lima_inst_procs.f90 @@ -1,4 +1,4 @@ -!MNH_LIC Copyright 2013-2018 CNRS, Meteo-France and Universite Paul Sabatier +!MNH_LIC Copyright 2013-2020 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !MNH_LIC for details. version 1. @@ -82,7 +82,7 @@ SUBROUTINE LIMA_INST_PROCS (PTSTEP, LDCOMPUTE, !! PURPOSE !! ------- !! Compute sources of instantaneous microphysical processes for the -!! time-splitted version of LIMA +!! time-split version of LIMA !! !! AUTHOR !! ------ diff --git a/src/MNH/lima_nucleation_procs.f90 b/src/MNH/lima_nucleation_procs.f90 index 04f4f90095015487c266d562c5ecc9bc77602a3b..6d4af712daf4d934169002088b374588f480091a 100644 --- a/src/MNH/lima_nucleation_procs.f90 +++ b/src/MNH/lima_nucleation_procs.f90 @@ -60,7 +60,7 @@ SUBROUTINE LIMA_NUCLEATION_PROCS (PTSTEP, TPFILE, OCLOSE_OUT, PRHODJ, ! !! PURPOSE !! ------- -!! Compute nucleation processes for the time-splitted version of LIMA +!! Compute nucleation processes for the time-split version of LIMA !! !! AUTHOR !! ------ diff --git a/src/MNH/lima_phillips_ifn_nucleation.f90 b/src/MNH/lima_phillips_ifn_nucleation.f90 index f16a52c5f6b7712d3a48eceacb421deb6bbaea03..cfa3e6420220b5fc66c3739f168cabe37c12961a 100644 --- a/src/MNH/lima_phillips_ifn_nucleation.f90 +++ b/src/MNH/lima_phillips_ifn_nucleation.f90 @@ -59,7 +59,7 @@ END MODULE MODI_LIMA_PHILLIPS_IFN_NUCLEATION !! PURPOSE !! ------- !! The purpose of this routine is to compute the heterogeneous nucleation -!! following Phillips (2008) for the time-splitted version of LIMA +!! following Phillips (2008) for the time-split version of LIMA !! !! !!** METHOD diff --git a/src/MNH/lima_tendencies.f90 b/src/MNH/lima_tendencies.f90 index b66b19c3d56f807c7378db7f8a85bcc003584c39..02bf151fce8c8ec637810ab26ae2682d13520e0b 100644 --- a/src/MNH/lima_tendencies.f90 +++ b/src/MNH/lima_tendencies.f90 @@ -1,4 +1,4 @@ -!MNH_LIC Copyright 2013-2018 CNRS, Meteo-France and Universite Paul Sabatier +!MNH_LIC Copyright 2013-2020 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !MNH_LIC for details. version 1. @@ -209,7 +209,7 @@ SUBROUTINE LIMA_TENDENCIES (PTSTEP, LDCOMPUTE, !! PURPOSE !! ------- !! Compute sources of non-instantaneous microphysical processes for the -!! time-splitted version of LIMA +!! time-split version of LIMA !! !! AUTHOR !! ------ diff --git a/src/MNH/ls_coupling.f90 b/src/MNH/ls_coupling.f90 index 24238e398d3ac9b80170747fbeb47cb5ab41deb6..7b94aadad92bcdf0a42b173a37c08affd0898e05 100644 --- a/src/MNH/ls_coupling.f90 +++ b/src/MNH/ls_coupling.f90 @@ -1,4 +1,4 @@ -!MNH_LIC Copyright 1994-2018 CNRS, Meteo-France and Universite Paul Sabatier +!MNH_LIC Copyright 1996-2020 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !MNH_LIC for details. version 1. @@ -159,7 +159,7 @@ END MODULE MODI_LS_COUPLING !! !! MODIFICATIONS !! ------------- -!! Original 03/09/96 The previous routine SET_COUPLING have been splitted +!! Original 03/09/96 The previous routine SET_COUPLING have been split !! in 2 routines (UVW_LS_COUPLING and LS_COUPLING), !! and the temporal advance have been removed. !! Correction of the LS sources names (removing of R). diff --git a/src/MNH/modd_budget.f90 b/src/MNH/modd_budget.f90 index 6d0fe284b5547afc95e41824b4048567acbbcb7f..40cb7c46c644a954bea2c4235d0cacfab014f9df 100644 --- a/src/MNH/modd_budget.f90 +++ b/src/MNH/modd_budget.f90 @@ -38,7 +38,7 @@ !! V. Masson 27/11/02 add 2way nesting effect !! P. Jabouille 07/07/04 add budget terms for microphysics !! C. Barthe 19/11/09 add budget terms for electricity -!! C.Lac 04/2016 negative contribution to the budget splitted between advection, turbulence and microphysics for KHKO/C2R2 +!! C.Lac 04/2016 negative contribution to the budget split between advection, turbulence and microphysics for KHKO/C2R2 !! C. Barthe /16 add budget terms for LIMA !! C. LAc 10/2016 add droplets deposition !! S. Riette 11/2016 New budgets for ICE3/ICE4 diff --git a/src/MNH/modeln.f90 b/src/MNH/modeln.f90 index f6862bb176bc07509bfe9b1bb91bb20a31902cfc..d443ea46ab004ade4e733235ddebd10087e3f8ea 100644 --- a/src/MNH/modeln.f90 +++ b/src/MNH/modeln.f90 @@ -168,7 +168,7 @@ END MODULE MODI_MODEL_n !! July 29,1996 (Lafore) nesting introduction !! Aug. 1,1996 (Lafore) synchronization between models !! Sept. 4,1996 (Lafore) modification of call to routine SET_COUPLING -!! now splitted in 2 routines +!! now split in 2 routines !! (UVW_LS_COUPLING and SCALAR_LS_COUPLING) !! Sept 5,1996 (V.Masson) print of loop index for debugging !! purposes diff --git a/src/MNH/modn_budget.f90 b/src/MNH/modn_budget.f90 index 257e023032c00b2e1bf54986b3845ff225422455..52bc31721e72572a8efae724e3159f561ae41a17 100644 --- a/src/MNH/modn_budget.f90 +++ b/src/MNH/modn_budget.f90 @@ -221,7 +221,7 @@ !! J.-P. Pinty 18/02/97 add forcing and ice !! J.-P. Pinty 25/09/00 add budget terms for C2R2 !! D. Gazen 22/01/01 add NCHEMSV -!! C.Lac 04/2016 negative contribution to the budget splitted between advection, turbulence and microphysics for KHKO/C2R2 +!! C.Lac 04/2016 negative contribution to the budget split between advection, turbulence and microphysics for KHKO/C2R2 !! C. Barthe /16 add budget terms for LIMA !! C.Lac 10/2016 Add droplet deposition !! S. Riette 11/2016 New budgets for ICE3/ICE4 diff --git a/src/MNH/radiations.f90 b/src/MNH/radiations.f90 index 807b5e1c604aeac9724ff37c7bda41f30de547bf..dc7f79e0be0ca05a827143dadb0a5db3ea4c0795 100644 --- a/src/MNH/radiations.f90 +++ b/src/MNH/radiations.f90 @@ -84,7 +84,7 @@ CONTAINS !! ------------- !! Original 26/02/95 !! J.Stein 20/12/95 add the array splitting in order to save memory -!! J.-P. Pinty 19/11/96 change the splitted arrays, specific humidity +!! J.-P. Pinty 19/11/96 change the split arrays, specific humidity !! and add the ice phase !! J.Stein 22/06/97 use of the absolute pressure !! P.Jabouille 31/07/97 impose a zero humidity for dry simulation @@ -200,7 +200,7 @@ INTEGER, INTENT(IN) :: KSTATM ! index of the standard ! atmosphere level just above ! the model top INTEGER, INTENT(IN) :: KRAD_COLNBR ! factor by which the memory - ! is splitted + ! is split ! !Choice of : CHARACTER (LEN=*), INTENT (IN) :: HEFRADL ! @@ -414,7 +414,7 @@ REAL, DIMENSION(:), ALLOCATABLE :: ZWORK1, ZWORK2, ZWORK3, ZWORK REAL, DIMENSION(:,:), ALLOCATABLE :: ZWORK4, ZWORK1AER, ZWORK2AER, ZWORK_GRID LOGICAL, DIMENSION(SIZE(PTHT,1),SIZE(PTHT,2)) :: ZWORKL ! -! splitted arrays used to split the memory required by the ECMWF_radiation +! split arrays used to split the memory required by the ECMWF_radiation ! subroutine, the fields have the same meaning as their complete counterpart ! REAL(KIND=JPRB), DIMENSION(:,:), ALLOCATABLE :: ZALBP_SPLIT, ZALBD_SPLIT @@ -510,7 +510,7 @@ REAL, DIMENSION(KFLEV,KSWB_OLD) :: ZTAUREL_EQ_CLEAR !tau/tau_{550} INTEGER :: WVL_IDX !Counter for wavelength ! -INTEGER :: JI_SPLIT ! loop on the splitted array +INTEGER :: JI_SPLIT ! loop on the split array INTEGER :: INUM_CALL ! number of CALL of the radiation scheme INTEGER :: IDIM_EFF ! effective number of air-columns to compute INTEGER :: IDIM_RESIDUE ! number of remaining air-columns to compute @@ -2176,7 +2176,7 @@ ELSE END IF END IF ! -! fill the splitted arrays with their values taken from the full arrays +! fill the split arrays with their values taken from the full arrays ! IBEG = IDIM-IDIM_RESIDUE+1 IEND = IBEG+IDIM_EFF-1 @@ -2213,7 +2213,7 @@ ELSE ZQSAVE_SPLIT (:,:) = ZQSAVE (IBEG:IEND ,:) ZTS_SPLIT (:) = ZTS (IBEG:IEND) ! -! CALL the ECMWF radiation with the splitted array +! CALL the ECMWF radiation with the split array ! IF (CCLOUD == 'LIMA') THEN ! LIMA concentrations @@ -2315,7 +2315,7 @@ ELSE END IF END IF ! -! fill the full output arrays with the splitted arrays +! fill the full output arrays with the split arrays ! ZDTLW( IBEG:IEND ,:) = ZDTLW_SPLIT(:,:) ZDTSW( IBEG:IEND ,:) = ZDTSW_SPLIT(:,:) @@ -2367,7 +2367,7 @@ ELSE ! IDIM_RESIDUE = IDIM_RESIDUE - IDIM_EFF ! -! desallocation of the splitted arrays +! desallocation of the split arrays ! IF( JI_SPLIT >= INUM_CALL-1 ) THEN DEALLOCATE( ZALBP_SPLIT ) diff --git a/src/MNH/radtr_satel.f90 b/src/MNH/radtr_satel.f90 index 394f11794c5c952137967648016492cab7b9a1e3..554244aa4c0ed7178d64f8609528fde3abd5a6d7 100644 --- a/src/MNH/radtr_satel.f90 +++ b/src/MNH/radtr_satel.f90 @@ -1,4 +1,4 @@ -!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier +!MNH_LIC Copyright 2000-2020 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !MNH_LIC for details. version 1. @@ -29,7 +29,7 @@ INTEGER, INTENT(IN) :: KFLEV !number of vertical levels where the !radiation calculations are performed INTEGER, INTENT(IN) :: KSTATM !index of the standard atmosphere level !just above the model top -INTEGER, INTENT(IN) :: KRAD_COLNBR !factor by which the memory is splitted +INTEGER, INTENT(IN) :: KRAD_COLNBR !factor by which the memory is split ! REAL, DIMENSION(:,:), INTENT(IN) :: PEMIS !Surface IR EMISsivity REAL, INTENT(IN) :: PCCO2 !CO2 content @@ -139,7 +139,7 @@ INTEGER, INTENT(IN) :: KFLEV !number of vertical levels where the ! radiation calculations are performed INTEGER, INTENT(IN) :: KSTATM !index of the standard atmosphere level !just above the model top -INTEGER, INTENT(IN) :: KRAD_COLNBR !factor by which the memory is splitted +INTEGER, INTENT(IN) :: KRAD_COLNBR !factor by which the memory is split ! REAL, DIMENSION(:,:), INTENT(IN) :: PEMIS !Surface IR EMISsivity REAL, INTENT(IN) :: PCCO2 !CO2 content @@ -229,7 +229,7 @@ REAL, DIMENSION(:,:), ALLOCATABLE :: ZZRADFT ! REAL, DIMENSION(:), ALLOCATABLE :: ZWORK1, ZWORK3 ! -! splitted arrays used to split the memory required by the ECMWF_radiation +! split arrays used to split the memory required by the ECMWF_radiation ! subroutine, the fields have the same meaning as their complete counterpart REAL, DIMENSION(:), ALLOCATABLE :: ZREMIS_SPLIT REAL, DIMENSION(:,:), ALLOCATABLE :: ZO3AVE_SPLIT @@ -244,7 +244,7 @@ REAL, DIMENSION(:), ALLOCATABLE :: ZDT0_SPLIT REAL, DIMENSION(:,:), ALLOCATABLE :: ZRADBT_SPLIT REAL, DIMENSION(:,:), ALLOCATABLE :: ZRADBC_SPLIT ! -INTEGER :: JI_SPLIT ! loop on the splitted array +INTEGER :: JI_SPLIT ! loop on the split array INTEGER :: INUM_CALL ! number of CALL of the radiation scheme INTEGER :: IDIM_EFF ! effective number of air-columns to compute INTEGER :: IDIM_RESIDUE ! number of remaining air-columns to compute @@ -645,7 +645,7 @@ ELSE ALLOCATE( ZRADBC_SPLIT(IDIM_EFF,JPWVINT)) END IF ! - ! fill the splitted arrays with their values + ! fill the split arrays with their values ! taken from the full arrays ! IBEG = IDIM-IDIM_RESIDUE+1 @@ -661,7 +661,7 @@ ELSE ZVIEW_SPLIT(:) = ZVIEW ( IBEG:IEND ) ZDT0_SPLIT(:) = ZDT0 ( IBEG:IEND ) ! - ! call ECMWF_radiation with the splitted arrays + ! call ECMWF_radiation with the split arrays ! CALL NBMVEC( 1, IDIM_EFF, IDIM_EFF, KFLEV, IGL, ICABS, ING1, IUABS,& IH2O, ICO2, IO3, ICNT, IN2O, ICH4, ICO, IC11, IC12, ICFC, & @@ -671,14 +671,14 @@ ELSE ZVIEW_SPLIT, ZCLDLD_SPLIT, ZCLDLU_SPLIT, ZDT0_SPLIT, & ZREMIS_SPLIT, ZRADBC_SPLIT, ZRADBT_SPLIT) ! - ! fill the full output arrays with the splitted arrays + ! fill the full output arrays with the split arrays ! ZRADBT( IBEG:IEND ,:) = ZRADBT_SPLIT(:,:) ZRADBC( IBEG:IEND ,:) = ZRADBC_SPLIT(:,:) ! IDIM_RESIDUE = IDIM_RESIDUE - IDIM_EFF ! - ! desallocation of the splitted arrays + ! desallocation of the split arrays ! IF( JI_SPLIT >= INUM_CALL-1 ) THEN DEALLOCATE(ZREMIS_SPLIT) diff --git a/src/MNH/rain_c2r2_khko.f90 b/src/MNH/rain_c2r2_khko.f90 index 9f190775b27000b4506f5d8b475aa47c7916dce0..e842e10ff6eb8a98efc980c52040b3fc745abf16 100644 --- a/src/MNH/rain_c2r2_khko.f90 +++ b/src/MNH/rain_c2r2_khko.f90 @@ -367,7 +367,7 @@ REAL, DIMENSION(SIZE(PRHODREF,1),SIZE(PRHODREF,2),SIZE(PRHODREF,3)) & :: ZMVRR,ZVRR,ZVCR REAL, DIMENSION(SIZE(PRHODREF,1),SIZE(PRHODREF,2),SIZE(PRHODREF,3)) & :: ZPRCT, ZPCCT, ZPRRT, ZPCRT - ! For splitted sedimentation + ! For split sedimentation REAL, DIMENSION(SIZE(PRHODREF,1),SIZE(PRHODREF,2),SIZE(PRHODREF,3)) & :: ZMVRC !Cloud water mean volumic radius REAL, DIMENSION(SIZE(PEXNREF,1),SIZE(PEXNREF,2),SIZE(PEXNREF,3)) & diff --git a/src/MNH/split_grid_parameter_mnh.f90 b/src/MNH/split_grid_parameter_mnh.f90 index fed28c271c66c42b89e5a22370edd23e29884dda..17fb0fbd09cc16b07ee148322b87b53b3d4be202 100644 --- a/src/MNH/split_grid_parameter_mnh.f90 +++ b/src/MNH/split_grid_parameter_mnh.f90 @@ -1,4 +1,4 @@ -!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier +!MNH_LIC Copyright 2011-2020 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !MNH_LIC for details. version 1. @@ -10,7 +10,7 @@ #endif ! ############################################################# ! -!!**** * - routine to split a real array on the splitted grid +!!**** * - routine to split a real array on the split grid ! ! Modifications ! M.Moge 10/02/2015 Using local subdomain for parallel execution @@ -36,7 +36,7 @@ INTEGER, INTENT(IN) :: KJMAX_ll !(global) dimension of the dom INTEGER, INTENT(IN) :: KHALO ! size of the Halo #endif REAL, DIMENSION(KDIM ), INTENT(IN) :: PFIELD ! real field for complete grid -REAL, DIMENSION(KSIZE), INTENT(OUT):: PFIELD_SPLIT! real field for splitted grid +REAL, DIMENSION(KSIZE), INTENT(OUT):: PFIELD_SPLIT! real field for split grid ! !* 0.2 Declarations of local variables ! @@ -140,7 +140,7 @@ END SUBROUTINE SPLIT_GRID_PARAMETERX1_MNH #endif ! ############################################################# ! -!!**** * - routine to define an integer related to splitted grid +!!**** * - routine to define an integer related to split grid ! ! ! @@ -161,7 +161,7 @@ CHARACTER(LEN=6), INTENT(IN) :: HREC ! name of the parameter INTEGER, INTENT(IN) :: KHALO ! size of the Halo #endif INTEGER, INTENT(IN) :: KFIELD ! integer scalar for complete grid -INTEGER, INTENT(OUT):: KFIELD_SPLIT ! integer scalar for splitted grid +INTEGER, INTENT(OUT):: KFIELD_SPLIT ! integer scalar for split grid !* 0.2 Declarations of local variables ! INTEGER :: IIB, IIE, IJB, IJE diff --git a/src/MNH/turb_ver.f90 b/src/MNH/turb_ver.f90 index ecf077cbb6c7070894387c00b8521ad2d30aed06..a3e16ee549a2e9dfc77e2208934ecd479bcce57b 100644 --- a/src/MNH/turb_ver.f90 +++ b/src/MNH/turb_ver.f90 @@ -227,15 +227,10 @@ END MODULE MODI_TURB_VER !! field derivated !! !! -!! MXM,MXF,MYM,MYF,MZM,MZF -!! : Shuman functions (mean operators) -!! DXF,DYF,DZF,DZM -!! : Shuman functions (difference operators) -!! -!! SUBROUTINE TRIDIAG : to compute the splitted implicit evolution +!! SUBROUTINE TRIDIAG : to compute the split implicit evolution !! of a variable located at a mass point !! -!! SUBROUTINE TRIDIAG_WIND: to compute the splitted implicit evolution +!! SUBROUTINE TRIDIAG_WIND: to compute the split implicit evolution !! of a variable located at a wind point !! !! FUNCTIONs ETHETA and EMOIST : diff --git a/src/MNH/turb_ver_dyn_flux.f90 b/src/MNH/turb_ver_dyn_flux.f90 index 93b7f9016bf9013a6398afb8293c49ee7757d98f..d3192e7b1a4c8b6915987fc2741ec689e299cc2d 100644 --- a/src/MNH/turb_ver_dyn_flux.f90 +++ b/src/MNH/turb_ver_dyn_flux.f90 @@ -198,10 +198,10 @@ END MODULE MODI_TURB_VER_DYN_FLUX !! DXF,DYF,DZF,DZM !! : Shuman functions (difference operators) !! -!! SUBROUTINE TRIDIAG : to compute the splitted implicit evolution +!! SUBROUTINE TRIDIAG : to compute the split implicit evolution !! of a variable located at a mass point !! -!! SUBROUTINE TRIDIAG_WIND: to compute the splitted implicit evolution +!! SUBROUTINE TRIDIAG_WIND: to compute the split implicit evolution !! of a variable located at a wind point !! !! FUNCTIONs ETHETA and EMOIST : @@ -483,7 +483,7 @@ ZSOURCE(:,:,IKB:IKB) = & ZSOURCE(:,:,IKTB+1:IKTE-1) = 0. ZSOURCE(:,:,IKE) = 0. ! -! Obtention of the splitted U at t+ deltat +! Obtention of the split U at t+ deltat ! CALL TRIDIAG_WIND(KKA,KKU,KKL,PUM,ZA,ZCOEFS(:,:,1),PTSTEP,PEXPL,PIMPL, & MXM(PRHODJ),ZSOURCE,ZRES) @@ -659,7 +659,7 @@ ZSOURCE(:,:,IKB:IKB) = & ZSOURCE(:,:,IKTB+1:IKTE-1) = 0. ZSOURCE(:,:,IKE) = 0. ! -! Obtention of the splitted V at t+ deltat +! Obtention of the split V at t+ deltat CALL TRIDIAG_WIND(KKA,KKU,KKL,PVM,ZA,ZCOEFS(:,:,1),PTSTEP,PEXPL,PIMPL, & MYM(PRHODJ),ZSOURCE,ZRES) ! diff --git a/src/MNH/turb_ver_sv_flux.f90 b/src/MNH/turb_ver_sv_flux.f90 index 26b102f73916c8461fece32d3455abd03aa56198..8d6479df6d4803871348005b5753b88e6b7375e3 100644 --- a/src/MNH/turb_ver_sv_flux.f90 +++ b/src/MNH/turb_ver_sv_flux.f90 @@ -177,10 +177,10 @@ END MODULE MODI_TURB_VER_SV_FLUX !! DXF,DYF,DZF,DZM !! : Shuman functions (difference operators) !! -!! SUBROUTINE TRIDIAG : to compute the splitted implicit evolution +!! SUBROUTINE TRIDIAG : to compute the split implicit evolution !! of a variable located at a mass point !! -!! SUBROUTINE TRIDIAG_WIND: to compute the splitted implicit evolution +!! SUBROUTINE TRIDIAG_WIND: to compute the split implicit evolution !! of a variable located at a wind point !! !! FUNCTIONs ETHETA and EMOIST : @@ -419,7 +419,7 @@ DO JSV=1,ISV ZSOURCE(:,:,IKTB+1:IKTE-1) = 0. ZSOURCE(:,:,IKE) = 0. ! -! Obtention of the splitted JSV scalar variable at t+ deltat +! Obtention of the split JSV scalar variable at t+ deltat CALL TRIDIAG(KKA,KKU,KKL,PSVM(:,:,:,JSV),ZA,PTSTEP,PEXPL,PIMPL,PRHODJ,ZSOURCE,ZRES) ! ! Compute the equivalent tendency for the JSV scalar variable diff --git a/src/MNH/turb_ver_thermo_corr.f90 b/src/MNH/turb_ver_thermo_corr.f90 index e9dcb3f1c2ae6b416fd5632a31bc6d3ed236a956..3e7544f91cac2442656b0073595e5267ce776001 100644 --- a/src/MNH/turb_ver_thermo_corr.f90 +++ b/src/MNH/turb_ver_thermo_corr.f90 @@ -222,10 +222,10 @@ END MODULE MODI_TURB_VER_THERMO_CORR !! DXF,DYF,DZF,DZM !! : Shuman functions (difference operators) !! -!! SUBROUTINE TRIDIAG : to compute the splitted implicit evolution +!! SUBROUTINE TRIDIAG : to compute the split implicit evolution !! of a variable located at a mass point !! -!! SUBROUTINE TRIDIAG_WIND: to compute the splitted implicit evolution +!! SUBROUTINE TRIDIAG_WIND: to compute the split implicit evolution !! of a variable located at a wind point !! !! FUNCTIONs ETHETA and EMOIST : diff --git a/src/MNH/turb_ver_thermo_flux.f90 b/src/MNH/turb_ver_thermo_flux.f90 index 0915d2544a1d22876940acadc3a7705dc74ce1ad..4a660f36fb8cc0bea819a0b7e1a8dd1af6155cda 100644 --- a/src/MNH/turb_ver_thermo_flux.f90 +++ b/src/MNH/turb_ver_thermo_flux.f90 @@ -234,10 +234,10 @@ END MODULE MODI_TURB_VER_THERMO_FLUX !! DXF,DYF,DZF,DZM !! : Shuman functions (difference operators) !! -!! SUBROUTINE TRIDIAG : to compute the splitted implicit evolution +!! SUBROUTINE TRIDIAG : to compute the split implicit evolution !! of a variable located at a mass point !! -!! SUBROUTINE TRIDIAG_WIND: to compute the splitted implicit evolution +!! SUBROUTINE TRIDIAG_WIND: to compute the split implicit evolution !! of a variable located at a wind point !! !! FUNCTIONs ETHETA and EMOIST : @@ -580,7 +580,7 @@ ELSE * 0.5 * (1. + PRHODJ(:,:,KKA) / PRHODJ(:,:,IKB)) END IF ! -! Compute the splitted conservative potential temperature at t+deltat +! Compute the split conservative potential temperature at t+deltat CALL TRIDIAG_THERMO(KKA,KKU,KKL,PTHLM,ZF,ZDFDDTDZ,PTSTEP,PIMPL,PDZZ,& PRHODJ,PTHLP) ! @@ -758,7 +758,7 @@ IF (KRR /= 0) THEN * 0.5 * (1. + PRHODJ(:,:,KKA) / PRHODJ(:,:,IKB)) END IF ! - ! Compute the splitted conservative potential temperature at t+deltat + ! Compute the split conservative potential temperature at t+deltat CALL TRIDIAG_THERMO(KKA,KKU,KKL,PRM(:,:,:,1),ZF,ZDFDDRDZ,PTSTEP,PIMPL,& PDZZ,PRHODJ,PRP) !