From 47004fb1d2e62b521266d0c9687b3bd4f5a66c47 Mon Sep 17 00:00:00 2001
From: Philippe WAUTELET <philippe.wautelet@aero.obs-mip.fr>
Date: Mon, 17 Aug 2020 13:07:28 +0200
Subject: [PATCH] Philippe 17/08/2020: minor: correction of typo
 (splitted->split)

---
 LIBTOOLS/tools/lfi2cdf/src/lfi2cdf.f90         |  2 +-
 src/LIB/SURCOUCHE/src/modd_io.f90              |  6 +++---
 .../SURCOUCHE/src/mode_io_manage_struct.f90    |  2 +-
 src/LIB/SURCOUCHE/src/mode_io_write_lfi.f90    |  4 ++--
 src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90    |  4 ++--
 src/LIB/SURCOUCHE/src/mode_tools_ll.f90        |  4 ++--
 src/LIB/SURCOUCHE/src/mode_toolsz_ll.f90       |  4 ++--
 src/MNH/calcsound.f90                          | 11 +++--------
 src/MNH/default_desfmn.f90                     |  4 ++--
 src/MNH/extend_grid_parameter_mnh.f90          | 10 +++++-----
 src/MNH/lima_inst_procs.f90                    |  4 ++--
 src/MNH/lima_nucleation_procs.f90              |  2 +-
 src/MNH/lima_phillips_ifn_nucleation.f90       |  2 +-
 src/MNH/lima_tendencies.f90                    |  4 ++--
 src/MNH/ls_coupling.f90                        |  4 ++--
 src/MNH/modd_budget.f90                        |  2 +-
 src/MNH/modeln.f90                             |  2 +-
 src/MNH/modn_budget.f90                        |  2 +-
 src/MNH/radiations.f90                         | 16 ++++++++--------
 src/MNH/radtr_satel.f90                        | 18 +++++++++---------
 src/MNH/rain_c2r2_khko.f90                     |  2 +-
 src/MNH/split_grid_parameter_mnh.f90           | 10 +++++-----
 src/MNH/turb_ver.f90                           |  4 ++--
 src/MNH/turb_ver_dyn_flux.f90                  |  8 ++++----
 src/MNH/turb_ver_sv_flux.f90                   |  6 +++---
 src/MNH/turb_ver_thermo_corr.f90               |  4 ++--
 src/MNH/turb_ver_thermo_flux.f90               |  8 ++++----
 27 files changed, 72 insertions(+), 77 deletions(-)

diff --git a/LIBTOOLS/tools/lfi2cdf/src/lfi2cdf.f90 b/LIBTOOLS/tools/lfi2cdf/src/lfi2cdf.f90
index 4bf5549a1..39bb56a69 100644
--- a/LIBTOOLS/tools/lfi2cdf/src/lfi2cdf.f90
+++ b/LIBTOOLS/tools/lfi2cdf/src/lfi2cdf.f90
@@ -96,7 +96,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 45afb9732..ecd430177 100644
--- a/src/LIB/SURCOUCHE/src/modd_io.f90
+++ b/src/LIB/SURCOUCHE/src/modd_io.f90
@@ -68,7 +68,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
 
@@ -89,10 +89,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 ad3d23d18..aefe98738 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_manage_struct.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_manage_struct.f90
@@ -593,7 +593,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
           TPBAKOUTN(IPOS)%TFILE%NSUBFILES_IOZ = NB_PROCIO_W
           ALLOCATE(TPBAKOUTN(IPOS)%TFILE%TFILES_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 bb455523b..7f5f2ce22 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_write_lfi.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_write_lfi.f90
@@ -138,8 +138,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 da63ebcb9..754cebb90 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90
@@ -475,8 +475,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=CDFINT)                            :: STATUS
diff --git a/src/LIB/SURCOUCHE/src/mode_tools_ll.f90 b/src/LIB/SURCOUCHE/src/mode_tools_ll.f90
index b5fbe7198..6736a75bd 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 1998-2019 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.
@@ -2486,7 +2486,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 e76d24d1d..ac917b492 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 1998-2019 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.
@@ -1124,7 +1124,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 a0b1c5fa1..03acbaba2 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 27d39a9ca..15a627d2e 100644
--- a/src/MNH/default_desfmn.f90
+++ b/src/MNH/default_desfmn.f90
@@ -145,7 +145,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
@@ -187,7 +187,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 f83fc564f..7b54a15d5 100644
--- a/src/MNH/extend_grid_parameter_mnh.f90
+++ b/src/MNH/extend_grid_parameter_mnh.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2015-2019 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.
@@ -7,7 +7,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 
@@ -37,7 +37,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
 !
@@ -154,7 +154,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
 !
 !
 !
@@ -169,7 +169,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 a03eed7e3..ff8dc1f04 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 a31888d49..a7d11b098 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 14733bb6d..a1103f50b 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 b66b19c3d..02bf151fc 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 9af87a483..3f8c43e1e 100644
--- a/src/MNH/ls_coupling.f90
+++ b/src/MNH/ls_coupling.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1996-2019 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 045f94a15..486a6af78 100644
--- a/src/MNH/modd_budget.f90
+++ b/src/MNH/modd_budget.f90
@@ -37,7 +37,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 d1bd8dbf3..158ba786c 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 8f7488e84..f5761a3aa 100644
--- a/src/MNH/modn_budget.f90
+++ b/src/MNH/modn_budget.f90
@@ -220,7 +220,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 b8a1c3424..11e377c90 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
@@ -204,7 +204,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 ! 
@@ -418,7 +418,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
@@ -514,7 +514,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
@@ -2181,7 +2181,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
@@ -2218,7 +2218,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
@@ -2320,7 +2320,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(:,:) 
@@ -2372,7 +2372,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 357b7941c..851030cd8 100644
--- a/src/MNH/radtr_satel.f90
+++ b/src/MNH/radtr_satel.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2000-2019 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.
@@ -25,7 +25,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
@@ -136,7 +136,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
@@ -226,7 +226,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
@@ -241,7 +241,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
@@ -642,7 +642,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
@@ -658,7 +658,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, &
@@ -668,14 +668,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 582717631..bda25362d 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 e859565f1..e04ff2ea5 100644
--- a/src/MNH/split_grid_parameter_mnh.f90
+++ b/src/MNH/split_grid_parameter_mnh.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2011-2019 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.
@@ -11,7 +11,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
@@ -39,7 +39,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
 !
@@ -143,7 +143,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
 !
 !
 !
@@ -164,7 +164,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 37b7bcfd9..f41ffc697 100644
--- a/src/MNH/turb_ver.f90
+++ b/src/MNH/turb_ver.f90
@@ -226,10 +226,10 @@ END MODULE MODI_TURB_VER
 !!                               _(M,UW,...) represent the localization of the 
 !!                               field	derivated
 !!
-!!      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 96b5b1f48..dad39fdb5 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 ed660517d..d97819307 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 445020794..d9b9507b7 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 25c9d06f4..84a997a82 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)
   !
-- 
GitLab