From 34076db93350ef3b3a14cd5960c34947363d001a Mon Sep 17 00:00:00 2001
From: Philippe WAUTELET <philippe.wautelet@aero.obs-mip.fr>
Date: Wed, 5 Jan 2022 11:38:52 +0100
Subject: [PATCH] Philippe 05/01/2022: replace ppp by ppv (ppp is not a valid
 unit)

---
 src/MNH/aer_monitorn.f90               |  6 +++---
 src/MNH/ch_aer_reallfin.f90            | 13 ++++---------
 src/MNH/ch_convect_scavenging.f90      |  7 ++++---
 src/MNH/ch_emission_flux0d.f90         | 16 ++++++++--------
 src/MNH/ch_field_valuen.f90            |  4 ++--
 src/MNH/ch_model0d.f90                 | 16 ++++++++--------
 src/MNH/ch_monitorn.f90                |  6 +++---
 src/MNH/ch_read_chem.f90               |  6 +++---
 src/MNH/ch_surface0d.f90               |  8 ++++----
 src/MNH/ch_write_chem.f90              |  6 +++---
 src/MNH/effic_aero.f90                 | 12 ++++--------
 src/MNH/effic_dust.f90                 | 10 +++-------
 src/MNH/effic_salt.f90                 | 10 +++-------
 src/MNH/ground_paramn.f90              | 14 +++++++-------
 src/MNH/ini_lb.f90                     | 16 ++++++++--------
 src/MNH/ini_nsv.f90                    | 22 +++++++++++-----------
 src/MNH/modd_ch_flxn.f90               | 11 +++--------
 src/MNH/mode_aero_psd.f90              | 23 +++++++++--------------
 src/MNH/mode_blowsnow_psd.f90          |  6 +++---
 src/MNH/mode_dust_psd.f90              | 24 ++++++++++--------------
 src/MNH/mode_salt_psd.f90              | 24 ++++++++++--------------
 src/MNH/mode_salt_psd_wet.f90          | 24 ++++++++++--------------
 src/MNH/radiations.f90                 |  8 ++++----
 src/MNH/read_all_data_grib_case.f90    |  4 ++--
 src/MNH/read_chem_data_netcdf_case.f90 |  4 ++--
 src/MNH/read_field.f90                 | 18 +++++++++---------
 src/MNH/sedim_blowsnow.f90             |  4 ++--
 src/MNH/sedim_dust.f90                 |  6 +++---
 src/MNH/sedim_salt.f90                 |  6 +++---
 src/MNH/spawn_field2.f90               | 14 +++++++-------
 src/MNH/write_lbn.f90                  |  8 ++++----
 src/MNH/write_lfifm1_for_diag_supp.f90 |  6 +++---
 src/MNH/write_lfin.f90                 | 20 ++++++++++----------
 src/MNH/write_ts1d.f90                 |  4 ++--
 34 files changed, 174 insertions(+), 212 deletions(-)

diff --git a/src/MNH/aer_monitorn.f90 b/src/MNH/aer_monitorn.f90
index 97faca64c..22d5f69a9 100644
--- a/src/MNH/aer_monitorn.f90
+++ b/src/MNH/aer_monitorn.f90
@@ -1,4 +1,4 @@
-!ORILAM_LIC Copyright 2008-2019 CNRS, Meteo-France and Universite Paul Sabatier
+!ORILAM_LIC Copyright 2008-2022 CNRS, Meteo-France and Universite Paul Sabatier
 !ORILAM_LIC This is part of the ORILAM software governed by the CeCILL-C licence
 !ORILAM_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !ORILAM_LIC for details.
@@ -214,7 +214,7 @@ IF (LDUST.AND.LSEDIMDUST) THEN
                   XRHODREF(IIB:IIE,IJB:IJE,IKB:IKE), &
                   XPABST(IIB:IIE,IJB:IJE,IKB:IKE), &
                   XZZ(IIB:IIE,IJB:IJE,IKB:IKE+1),    &
-                  ZSVT(IIB:IIE,IJB:IJE,IKB:IKE,:)) !ppp (concentration)
+                  ZSVT(IIB:IIE,IJB:IJE,IKB:IKE,:)) !ppv (concentration)
 !
 DO JSV = NSV_DSTBEG, NSV_DSTEND
     XRSVS(IIB:IIE,IJB:IJE,IKB:IKE,JSV) = ZSVT(IIB:IIE,IJB:IJE,IKB:IKE,JSV-NSV_DSTBEG+1)  *&
@@ -240,7 +240,7 @@ IF ((LSALT).AND.(LSEDIMSALT)) THEN
                   XRHODREF(IIB:IIE,IJB:IJE,IKB:IKE), &
                   XPABST(IIB:IIE,IJB:IJE,IKB:IKE), &
                   XZZ(IIB:IIE,IJB:IJE,IKB:IKE+1),    &
-                  ZSVT(IIB:IIE,IJB:IJE,IKB:IKE,:))  !ppp (concentration)
+                  ZSVT(IIB:IIE,IJB:IJE,IKB:IKE,:))  !ppv (concentration)
 ! -- JORIS DEBUG --
 
 DO JSV = NSV_SLTBEG, NSV_SLTEND
diff --git a/src/MNH/ch_aer_reallfin.f90 b/src/MNH/ch_aer_reallfin.f90
index 99b0f8766..505f3acfa 100644
--- a/src/MNH/ch_aer_reallfin.f90
+++ b/src/MNH/ch_aer_reallfin.f90
@@ -1,13 +1,8 @@
-!ORILAM_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
+!ORILAM_LIC Copyright 1994-2022 CNRS, Meteo-France and Universite Paul Sabatier
 !ORILAM_LIC This is part of the ORILAM software governed by the CeCILL-C licence
 !ORILAM_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !ORILAM_LIC for details.
 !-----------------------------------------------------------------
-!--------------- special set of characters for RCS information
-!-----------------------------------------------------------------
-! $Source$ $Revision$
-! MASDEV4_7 chimie 2006/06/16 13:28:57
-!-----------------------------------------------------------------
 !!   ########################
      MODULE MODI_CH_AER_REALLFI_n
 !!   ########################
@@ -155,8 +150,8 @@ IF (LINITPM) THEN
 !ZVALOC=2.304978E-9 ! value in kg/m3 (escompte values)
 !ZVALBC=1.E-9  ! value in kg/m3 (default values)
 !ZVALOC=2.E-9 ! value in kg/m3  (default values)
-!ZVALBC= ZVALBC *24.47 / 12. ! conversion into ppp 
-!ZVALOC= ZVALOC *24.47 / 12. ! conversion into ppp
+!ZVALBC= ZVALBC *24.47 / 12. ! conversion into ppv
+!ZVALOC= ZVALOC *24.47 / 12. ! conversion into ppv
 !ZCOEFAEROBC=ZVALBC/ZSUMAEROCO
 !ZCOEFAEROOC=ZVALOC/ZSUMAEROCO
 
@@ -317,7 +312,7 @@ DO JN=1,JPMODE
 !
 ENDDO
 !
-!conversion into ppp
+!conversion into ppv
 DO JJ=1,NSV_AER
   PSV(:,:,:,JJ) =  PSV(:,:,:,JJ) /  (ZDEN2MOL*PRHODREF(:,:,:)) 
 ENDDO
diff --git a/src/MNH/ch_convect_scavenging.f90 b/src/MNH/ch_convect_scavenging.f90
index a0bfccfd6..dd8a55917 100644
--- a/src/MNH/ch_convect_scavenging.f90
+++ b/src/MNH/ch_convect_scavenging.f90
@@ -1,7 +1,8 @@
-!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1994-2022 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.
+!-----------------------------------------------------------------
 !     ######################
       MODULE MODI_CH_CONVECT_SCAVENGING
 !     ######################
@@ -340,7 +341,7 @@ ENDDO
 !
 GCHFIRSTCALL = .FALSE.
 !
-!               Convert KH from mol/l/atm in ppp/ppp
+!               Convert KH from mol/l/atm in ppv/ppv
 !               ------------------------------------
 DO JKAQ = NSV_CHEMBEG, NSV_CHEMEND
  ZKHC(:,:,JKAQ) = ZKH(:,:,JKAQ)*0.08205*ZT(:,:)*ZLWCC(:,:)
@@ -368,7 +369,7 @@ DO JKAQ = NSV_CHEMBEG, NSV_CHEMEND
 ENDDO
 !
 !
-!          Convert KHI from cm3(air)/cm3(ice) in ppp/ppp
+!          Convert KHI from cm3(air)/cm3(ice) in ppv/ppv
 !          ---------------------------------------------    
 DO JKAQ = NSV_CHEMBEG, NSV_CHEMEND
  IF (CNAMES(JKAQ-NSV_CHEMBEG+1)=='HNO3') THEN 
diff --git a/src/MNH/ch_emission_flux0d.f90 b/src/MNH/ch_emission_flux0d.f90
index 540a03306..74b84f6d4 100644
--- a/src/MNH/ch_emission_flux0d.f90
+++ b/src/MNH/ch_emission_flux0d.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1999-2019 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1999-2022 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.
@@ -13,7 +13,7 @@ USE MODD_CH_M9_n,      ONLY: NEQ
 IMPLICIT NONE
 REAL,                 INTENT(IN)  :: PTIME      ! time of simulation in sec UTC
                                                 ! (counting from midnight)
-REAL, DIMENSION(NEQ), INTENT(OUT) :: PFLUX      ! emission flux in ppp*m/s
+REAL, DIMENSION(NEQ), INTENT(OUT) :: PFLUX      ! emission flux in ppv*m/s
 CHARACTER(len=*),     INTENT(IN)  :: HINPUTFILE ! name of the input file
 INTEGER,              INTENT(IN)  :: KLUOUT     ! output listing channel
 INTEGER,              INTENT(IN)  :: KVERB      ! verbosity level
@@ -55,10 +55,10 @@ END MODULE MODI_CH_EMISSION_FLUX0D
 !!    where the unit identifier [MIX|CON|MOL] indicates whether
 !!    the flux is given as 
 !!    CON: molecules/cm2/s 
-!!    MIX: ppp*m/s
+!!    MIX: ppv*m/s
 !!    MOL: microMol/m2/day
 !!    (assuming standard pressure and temperature in the conversion)
-!!    The returned flux is given in ppp*m/s, that is standard MesoNH
+!!    The returned flux is given in ppv*m/s, that is standard MesoNH
 !!    units so that no conversion is to be applied when introducing 
 !!    the emission flux in the 3-D model.
 !!
@@ -96,7 +96,7 @@ IMPLICIT NONE
 
 REAL,                 INTENT(IN)  :: PTIME      ! time of simulation in sec UTC
                                                 ! (counting from midnight)
-REAL, DIMENSION(NEQ), INTENT(OUT) :: PFLUX      ! emission flux in ppp*m/s
+REAL, DIMENSION(NEQ), INTENT(OUT) :: PFLUX      ! emission flux in ppv*m/s
 CHARACTER(len=*),     INTENT(IN)  :: HINPUTFILE ! name of the input file
 INTEGER,              INTENT(IN)  :: KLUOUT     ! output listing channel
 INTEGER,              INTENT(IN)  :: KVERB      ! verbosity level
@@ -207,13 +207,13 @@ IF (LSFIRSTCALL) THEN
 !
 ! determine the conversion factor
   SELECT CASE (YUNIT)
-  CASE ('MIX') ! flux given ppp*m/s, no conversion required
+  CASE ('MIX') ! flux given ppv*m/s, no conversion required
     ZCONVERSION = 1.0
   CASE ('CON') ! flux given in molecules/cm2/s
-               ! where 1 molecule/cm2/s = (224.14/6.022136E23) ppp*m/s
+               ! where 1 molecule/cm2/s = (224.14/6.022136E23) ppv*m/s
     ZCONVERSION = (224.14/6.022136E23)
   CASE ('MOL') ! flux given in microMol/m2/day
-               ! where 1 microMol/m2/day = (22.414/86.400)*1E-12 ppp*m/s
+               ! where 1 microMol/m2/day = (22.414/86.400)*1E-12 ppv*m/s
     ZCONVERSION = (22.414/86.400)*1E-12
   CASE DEFAULT
     call Print_msg( NVERB_FATAL, 'GEN', 'CH_EMISSION_FLUX0D', 'unknow conversion factor: '//trim(YUNIT) )
diff --git a/src/MNH/ch_field_valuen.f90 b/src/MNH/ch_field_valuen.f90
index 0693c28a2..0dcd5670a 100644
--- a/src/MNH/ch_field_valuen.f90
+++ b/src/MNH/ch_field_valuen.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1995-2019 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1995-2022 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.
@@ -228,7 +228,7 @@ firstcall: IF (GSFIRSTCALL) THEN
   CALL CH_OPEN_INPUT(CCHEM_INPUT_FILE, "NORMINIT", TZFILE, KLUOUT, KVERB)
   ICHANNEL = TZFILE%NLU
 !
-! read units for initial data (may be "CON" for molec./cm3 or "MIX" for ppp)
+! read units for initial data (may be "CON" for molec./cm3 or "MIX" for ppv)
   READ(ICHANNEL,"(A)") HUNIT
   IF (HUNIT .EQ. "CON") THEN
     IF (KVERB >= 5) THEN
diff --git a/src/MNH/ch_model0d.f90 b/src/MNH/ch_model0d.f90
index c2b4fb457..26ff9fe18 100644
--- a/src/MNH/ch_model0d.f90
+++ b/src/MNH/ch_model0d.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1995-2019 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1995-2022 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.
@@ -309,10 +309,10 @@ IF (NVERB >= 5) THEN
   END IF
 END IF
 ! 
-ZCONC(1,:) = ZCONC(1,:) * ZDEN2MOL * ZRHODREF(1,1,1) ! convert ppp to molec.cm-3
+ZCONC(1,:) = ZCONC(1,:) * ZDEN2MOL * ZRHODREF(1,1,1) ! convert ppv to molec.cm-3
 ZNEWCONC(1,:) = ZCONC(1,:)
 IF (LORILAM) THEN
-ZAERO(1,:) = ZAERO(1,:) * ZDEN2MOL * ZRHODREF(1,1,1) ! convert ppp to molec.cm-3
+ZAERO(1,:) = ZAERO(1,:) * ZDEN2MOL * ZRHODREF(1,1,1) ! convert ppv to molec.cm-3
 ZNEWAERO(1,:) = ZAERO(1,:)  
 END IF
 !*       1.5  initialize data for jvalues
@@ -468,7 +468,7 @@ IF (LORILAM) THEN
    XDP(:,:) = 2.E-6 * ZRG0(:,:)
 END IF
 
-  ! ZCONC(1,:) = ZCONC(1,:) * ZDEN2MOL * ZRHODREF(1,1,1) !convert ppp to  molec.cm-3
+  ! ZCONC(1,:) = ZCONC(1,:) * ZDEN2MOL * ZRHODREF(1,1,1) !convert ppv to  molec.cm-3
 
    CALL CH_SET_RATES(XTSIMUL,ZCONC,TZM,1,6,NVERB,1,NEQ)
    TZK%MODELLEVEL = 1
@@ -501,10 +501,10 @@ CALL CH_UPDATE_JVALUES(6, ZZENITH, ZRT,              &
   write_to_disk : IF (XTSIMUL >= XTNEXTOUT) THEN
 
     ZCONC(1,:) = ZCONC(1,:)*1.E9 / (ZDEN2MOL * ZRHODREF(1,1,1)) ! convert molec.cm-3 to ppb
-    IF (LORILAM) ZAERO(1,:) = ZAERO(1,:) / (ZDEN2MOL * ZRHODREF(1,1,1)) ! convert molec.cm-3 to ppp
+    IF (LORILAM) ZAERO(1,:) = ZAERO(1,:) / (ZDEN2MOL * ZRHODREF(1,1,1)) ! convert molec.cm-3 to ppv
     CALL CH_OUTPUT(ZCONC,ZAERO, ZMI, TZM, 1, 1)
     ZCONC(1,:) = ZCONC(1,:)*1.E-9 * (ZDEN2MOL * ZRHODREF(1,1,1)) ! convert  ppb to molec.cm-3
-    IF (LORILAM) ZAERO(1,:) = ZAERO(1,:) * (ZDEN2MOL * ZRHODREF(1,1,1)) ! convert  ppp to molec.cm-3
+    IF (LORILAM) ZAERO(1,:) = ZAERO(1,:) * (ZDEN2MOL * ZRHODREF(1,1,1)) ! convert  ppv to molec.cm-3
 
     XTNEXTOUT = XTSIMUL + XDTOUT
   ENDIF write_to_disk
@@ -559,8 +559,8 @@ ENDDO time_loop
 !*       4.1  write final result to disk (restart file)
 !
 ! convert molec.cm-3 to ppb
-ZCONC(1,:) = ZCONC(1,:) / (ZDEN2MOL * ZRHODREF(1,1,1)) ! convert molec.cm-3 to ppp
-IF (LORILAM) ZAERO(1,:) = ZAERO(1,:) / (ZDEN2MOL * ZRHODREF(1,1,1)) ! convert molec.cm-3 to ppp
+ZCONC(1,:) = ZCONC(1,:) / (ZDEN2MOL * ZRHODREF(1,1,1)) ! convert molec.cm-3 to ppv
+IF (LORILAM) ZAERO(1,:) = ZAERO(1,:) / (ZDEN2MOL * ZRHODREF(1,1,1)) ! convert molec.cm-3 to ppv
 CALL CH_WRITE_CHEM(ZCONC(1,:), ZAERO(1,:), ZRHODREF(:,1,1), COUTFILE)
 !
 !*       4.2  finish
diff --git a/src/MNH/ch_monitorn.f90 b/src/MNH/ch_monitorn.f90
index eee756dfb..5539015c3 100644
--- a/src/MNH/ch_monitorn.f90
+++ b/src/MNH/ch_monitorn.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1995-2021 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1995-2022 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.
@@ -623,7 +623,7 @@ IF (LORILAM) THEN
 !
 END IF
 !
-!*       1.4 compute conversion factor ppp/m3 --> molec/cm3
+!*       1.4 compute conversion factor ppv/m3 --> molec/cm3
 !
 ZDEN2MOL = 1E-6 * XAVOGADRO / XMD
 !
@@ -910,7 +910,7 @@ DO JL=1,ISVECNMASK
     IF (SIZE(XRT,4) .GE. 2) ZRC(JM+1) = XRT(JI, JJ, JK, 2)
     !Molar mass (kg/kg)
     ZMI(JM+1,:)     = XMI(JI, JJ, JK, :)
-    !Moments (ppp)
+    !Moments (ppv)
     ZM(JM+1,:)      = XM3D(JI,JJ,JK,:)
     ZSIG0(JM+1,:)   = LOG(XSIG3D(JI,JJ,JK,:))
     ZRG0(JM+1,:)    =  XRG3D(JI,JJ,JK,:)  
diff --git a/src/MNH/ch_read_chem.f90 b/src/MNH/ch_read_chem.f90
index bd3ed06df..29a166440 100644
--- a/src/MNH/ch_read_chem.f90
+++ b/src/MNH/ch_read_chem.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1995-2019 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1995-2022 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.
@@ -147,7 +147,7 @@ ELSE
     END IF
   END DO
 
-!Conversion ppb to ppp
+!Conversion ppb to ppv
  PCONC(:) =  PCONC(:) * 1E-9
 IF (LORILAM) THEN
   DO JI = 1, SIZE(PAERO,1)
@@ -165,7 +165,7 @@ IF (LORILAM) THEN
                       ' /= '//trim(YVARNAME) )
     END IF
   END DO
-!Conversion  microgram/m3 to ppp
+!Conversion  microgram/m3 to ppv
 ZMD    = 28.9644E-3
 ! Constants initialization
 ZMI(:) = 250.
diff --git a/src/MNH/ch_surface0d.f90 b/src/MNH/ch_surface0d.f90
index ce3bab6c4..8247ae0b7 100644
--- a/src/MNH/ch_surface0d.f90
+++ b/src/MNH/ch_surface0d.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1999-2019 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1999-2022 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.
@@ -132,8 +132,8 @@ CALL CH_EMISSION_FLUX0D(PTSIMUL, ZEMIS, "CHCONTROL1.nam", 6, NVERB)
 ! convert m2 to cm2, days to seconds and Mole to molecules
 ! ZEMIS(1:KEQ) = (6.022136E23/1E4/86400.)*ZEMIS(1:KEQ)
 !
-! convert ppp*m/s to molecules/cm2/s
-! based on 1 ppp*m/s = (Na/Vmol)*m/s = (6.022136E23/22.414E-3) molecules/m2/s
+! convert ppv*m/s to molecules/cm2/s
+! based on 1 ppv*m/s = (Na/Vmol)*m/s = (6.022136E23/22.414E-3) molecules/m2/s
 ZEMIS(1:KEQ) = (6.022136E23/224.14)*ZEMIS(1:KEQ)
 !
 !*    2.   CALCULATE DEPOSITION FLUXES WITH WESLEY 
@@ -153,7 +153,7 @@ ZSVT(1,1,1,:) = PCONC(:) ! scalar variables at t
 !                      ZHU_PATCH,ZPSN_PATCH)
 !UPG
 !
-! results in  ZSFSV(1,1,:) ! flux of scalar variables (ppp*m/s)
+! results in  ZSFSV(1,1,:) ! flux of scalar variables (ppv*m/s)
 ! but we do not use them here, we rather take the deposition velocity 
 ! directly from the module (variable XVDEPT)
 !
diff --git a/src/MNH/ch_write_chem.f90 b/src/MNH/ch_write_chem.f90
index ecc8a4b1e..a3c05fd66 100644
--- a/src/MNH/ch_write_chem.f90
+++ b/src/MNH/ch_write_chem.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1995-2019 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1995-2022 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.
@@ -93,10 +93,10 @@ OPEN(NEWUNIT =  ILU,        &
      STATUS  = 'UNKNOWN'    )
 !
 DO JI = 1, NEQ
-  WRITE(UNIT=ILU,FMT='(3A,E20.8)') "'", CNAMES(JI), "' ", PCONC(JI)*1.E9 ! convert ppp to ppb
+  WRITE(UNIT=ILU,FMT='(3A,E20.8)') "'", CNAMES(JI), "' ", PCONC(JI)*1.E9 ! convert ppv to ppb
 ENDDO
 IF (LORILAM) THEN
-!Conversion  ppp to microgram/m3
+!Conversion  ppv to microgram/m3
 ZMD    = 28.9644E-3
 ! Constants initialization
 ZMI(:) = 250.
diff --git a/src/MNH/effic_aero.f90 b/src/MNH/effic_aero.f90
index 83d653057..f3d053a49 100644
--- a/src/MNH/effic_aero.f90
+++ b/src/MNH/effic_aero.f90
@@ -1,12 +1,8 @@
-!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2013-2022 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$ $Date$
-!-----------------------------------------------------------------
 !!   ##############################
      MODULE MODI_EFFIC_AERO
 !!   ##############################
@@ -18,8 +14,8 @@ SUBROUTINE EFFIC_AERO(  &
      ,PRHODREF          & !I [kg/m3] air density
      ,PPABST            & !I [Pa] pressure
      ,PURR              & !I
-     ,PSVT              & !I [scalar variable, ppp] sea salt concentration
-     ,PEFFIC_AER            & !O [scalar variable, ppp] sea salt concentration
+     ,PSVT              & !I [scalar variable, ppv] sea salt concentration
+     ,PEFFIC_AER            & !O [scalar variable, ppv] sea salt concentration
      )
 
 IMPLICIT NONE
diff --git a/src/MNH/effic_dust.f90 b/src/MNH/effic_dust.f90
index 0f3755fcf..a3ba0109e 100644
--- a/src/MNH/effic_dust.f90
+++ b/src/MNH/effic_dust.f90
@@ -1,12 +1,8 @@
-!ORILAM_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
+!ORILAM_LIC Copyright 2011-2022 CNRS, Meteo-France and Universite Paul Sabatier
 !ORILAM_LIC This is part of the ORILAM software governed by the CeCILL-C licence
 !ORILAM_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !ORILAM_LIC for details.
 !-----------------------------------------------------------------
-!--------------- special set of characters for RCS information
-!-----------------------------------------------------------------
-! $Source$ $Revision$ $Date$
-!-----------------------------------------------------------------
 !!   ##############################
      MODULE MODI_EFFIC_DUST
 !!   ##############################
@@ -18,8 +14,8 @@ SUBROUTINE EFFIC_DUST(  &
      ,PRHODREF          & !I [kg/m3] air density
      ,PPABST            & !I [Pa] pressure
      ,PURR              & !I
-     ,PSVT              & !I [scalar variable, ppp] sea salt concentration
-     ,PEFFIC            & !O [scalar variable, ppp] sea salt concentration
+     ,PSVT              & !I [scalar variable, ppv] sea salt concentration
+     ,PEFFIC            & !O [scalar variable, ppv] sea salt concentration
      )
 
 IMPLICIT NONE
diff --git a/src/MNH/effic_salt.f90 b/src/MNH/effic_salt.f90
index a26367896..6b7f152d2 100644
--- a/src/MNH/effic_salt.f90
+++ b/src/MNH/effic_salt.f90
@@ -1,12 +1,8 @@
-!ORILAM_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
+!ORILAM_LIC Copyright 2017-2022 CNRS, Meteo-France and Universite Paul Sabatier
 !ORILAM_LIC This is part of the ORILAM software governed by the CeCILL-C licence
 !ORILAM_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !ORILAM_LIC for details.
 !-----------------------------------------------------------------
-!--------------- special set of characters for RCS information
-!-----------------------------------------------------------------
-! $Source$ $Revision$ $Date$
-!-----------------------------------------------------------------
 !!   ##############################
      MODULE MODI_EFFIC_SALT
 !!   ##############################
@@ -18,8 +14,8 @@ SUBROUTINE EFFIC_SALT(  &
      ,PRHODREF          & !I [kg/m3] air density
      ,PPABST            & !I [Pa] pressure
      ,PURR              & !I
-     ,PSVT              & !I [scalar variable, ppp] sea salt concentration
-     ,PEFFIC            & !O [scalar variable, ppp] sea salt concentration
+     ,PSVT              & !I [scalar variable, ppv] sea salt concentration
+     ,PEFFIC            & !O [scalar variable, ppv] sea salt concentration
      )
 
 IMPLICIT NONE
diff --git a/src/MNH/ground_paramn.f90 b/src/MNH/ground_paramn.f90
index b504d4b1b..795d0eb7e 100644
--- a/src/MNH/ground_paramn.f90
+++ b/src/MNH/ground_paramn.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1994-2020 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1995-2022 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.
@@ -18,7 +18,7 @@ INTERFACE
 REAL, DIMENSION(:,:), INTENT(OUT) :: PSFTH ! surface flux of potential temperature (Km/s)
 REAL, DIMENSION(:,:), INTENT(OUT) :: PSFRV ! surface flux of water vapor           (m/s*kg/kg)
 REAL, DIMENSION(:,:,:),INTENT(OUT):: PSFSV ! surface flux of scalar                (m/s*kg/kg)
-                                           ! flux of chemical var.                 (ppp.m/s)
+                                           ! flux of chemical var.                 (ppv.m/s)
 REAL, DIMENSION(:,:), INTENT(OUT) :: PSFCO2! surface flux of CO2                   (m/s*kg/kg)
 REAL, DIMENSION(:,:), INTENT(OUT) :: PSFU  ! surface fluxes of horizontal   
 REAL, DIMENSION(:,:), INTENT(OUT) :: PSFV  ! momentum in x and y directions        (m2/s2)
@@ -195,7 +195,7 @@ IMPLICIT NONE
 REAL, DIMENSION(:,:), INTENT(OUT) :: PSFTH ! surface flux of potential temperature (Km/s)
 REAL, DIMENSION(:,:), INTENT(OUT) :: PSFRV ! surface flux of water vapor           (m/s*kg/kg)
 REAL, DIMENSION(:,:,:),INTENT(OUT):: PSFSV ! surface flux of scalar                (m/s*kg/kg)
-                                           ! flux of chemical var.                 (ppp.m/s)
+                                           ! flux of chemical var.                 (ppv.m/s)
 REAL, DIMENSION(:,:), INTENT(OUT) :: PSFCO2! surface flux of CO2                   (m/s*kg/kg)
 REAL, DIMENSION(:,:), INTENT(OUT) :: PSFU  ! surface fluxes of horizontal   
 REAL, DIMENSION(:,:), INTENT(OUT) :: PSFV  ! momentum in x and y directions        (m2/s2)
@@ -679,7 +679,7 @@ IF(NSV .GT. 0) THEN
    END DO
 END IF
 !
-!* conversion from chemistry flux (molec/m2/s) to (ppp.m.s-1)
+!* conversion from chemistry flux (molec/m2/s) to (ppv.m.s-1)
 !
 IF (LUSECHEM) THEN
    DO JSV=NSV_CHEMBEG,NSV_CHEMEND
@@ -690,7 +690,7 @@ ELSE
   PSFSV(:,:,NSV_CHEMBEG:NSV_CHEMEND) = 0.
 END IF
 !
-!* conversion from dust flux (kg/m2/s) to (ppp.m.s-1)
+!* conversion from dust flux (kg/m2/s) to (ppv.m.s-1)
 !
 IF (LDUST) THEN
   DO JSV=NSV_DSTBEG,NSV_DSTEND
@@ -700,7 +700,7 @@ ELSE
   PSFSV(:,:,NSV_DSTBEG:NSV_DSTEND) = 0.
 END IF
 !
-!* conversion from sea salt flux (kg/m2/s) to (ppp.m.s-1)
+!* conversion from sea salt flux (kg/m2/s) to (ppv.m.s-1)
 !
 IF (LSALT) THEN
   DO JSV=NSV_SLTBEG,NSV_SLTEND
@@ -710,7 +710,7 @@ ELSE
   PSFSV(:,:,NSV_SLTBEG:NSV_SLTEND) = 0.
 END IF
 !
-!* conversion from aerosol flux (molec/m2/s) to (ppp.m.s-1)
+!* conversion from aerosol flux (molec/m2/s) to (ppv.m.s-1)
 !
 IF (LORILAM) THEN
   DO JSV=NSV_AERBEG,NSV_AEREND
diff --git a/src/MNH/ini_lb.f90 b/src/MNH/ini_lb.f90
index 710de1454..2d30bdde0 100644
--- a/src/MNH/ini_lb.f90
+++ b/src/MNH/ini_lb.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1998-2021 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1998-2022 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.
@@ -913,7 +913,7 @@ END IF
 ! Chemical aqueous phase scalar variables
 IF (NSV_CHACEND>=NSV_CHACBEG) THEN
   TZFIELD%CSTDNAME   = ''
-  TZFIELD%CUNITS     = 'ppp'
+  TZFIELD%CUNITS     = 'ppv'
   TZFIELD%CDIR       = ''
   TZFIELD%NGRID      = 1
   TZFIELD%NTYPE      = TYPEREAL
@@ -969,7 +969,7 @@ END IF
 ! Chemical ice phase scalar variables
 IF (NSV_CHICEND>=NSV_CHICBEG) THEN
   TZFIELD%CSTDNAME   = ''
-  TZFIELD%CUNITS     = 'ppp'
+  TZFIELD%CUNITS     = 'ppv'
   TZFIELD%CDIR       = ''
   TZFIELD%NGRID      = 1
   TZFIELD%NTYPE      = TYPEREAL
@@ -1025,7 +1025,7 @@ END IF
 ! Orilam aerosol scalar variables
 IF (NSV_AEREND>=NSV_AERBEG) THEN
   TZFIELD%CSTDNAME   = ''
-  TZFIELD%CUNITS     = 'ppp'
+  TZFIELD%CUNITS     = 'ppv'
   TZFIELD%CDIR       = ''
   TZFIELD%NGRID      = 1
   TZFIELD%NTYPE      = TYPEREAL
@@ -1081,7 +1081,7 @@ END IF
 ! Orilam aerosols moist scalar variables
 IF (NSV_AERDEPEND>=NSV_AERDEPBEG) THEN
   TZFIELD%CSTDNAME   = ''
-  TZFIELD%CUNITS     = 'ppp'
+  TZFIELD%CUNITS     = 'ppv'
   TZFIELD%CDIR       = ''
   TZFIELD%NGRID      = 1
   TZFIELD%NTYPE      = TYPEREAL
@@ -1137,7 +1137,7 @@ END IF
 ! Dust scalar variables
 IF (NSV_DSTEND>=NSV_DSTBEG) THEN
   TZFIELD%CSTDNAME   = ''
-  TZFIELD%CUNITS     = 'ppp'
+  TZFIELD%CUNITS     = 'ppv'
   TZFIELD%CDIR       = ''
   TZFIELD%NGRID      = 1
   TZFIELD%NTYPE      = TYPEREAL
@@ -1193,7 +1193,7 @@ END IF
 !
 IF (NSV_DSTDEPEND>=NSV_DSTDEPBEG) THEN
   TZFIELD%CSTDNAME   = ''
-  TZFIELD%CUNITS     = 'ppp'
+  TZFIELD%CUNITS     = 'ppv'
   TZFIELD%CDIR       = ''
   TZFIELD%NGRID      = 1
   TZFIELD%NTYPE      = TYPEREAL
@@ -1250,7 +1250,7 @@ END IF
 ! Sea salt scalar variables
 IF (NSV_SLTEND>=NSV_SLTBEG) THEN
   TZFIELD%CSTDNAME   = ''
-  TZFIELD%CUNITS     = 'ppp'
+  TZFIELD%CUNITS     = 'ppv'
   TZFIELD%CDIR       = ''
   TZFIELD%NGRID      = 1
   TZFIELD%NTYPE      = TYPEREAL
diff --git a/src/MNH/ini_nsv.f90 b/src/MNH/ini_nsv.f90
index eddddd15e..072ec322b 100644
--- a/src/MNH/ini_nsv.f90
+++ b/src/MNH/ini_nsv.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2001-2021 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2001-2022 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.
@@ -842,7 +842,7 @@ DO JSV = NSV_LIMA_BEG_A(KMI), NSV_LIMA_END_A(KMI)
     CMNHNAME   = 'SV LIMA ' // YNUM3,        &
     CSTDNAME   = '',                         &
     CLONGNAME  = '',                         &
-    CUNITS     = 'kg-1',                    &
+    CUNITS     = 'kg-1',                     &
     CDIR       = 'XY',                       &
     CCOMMENT   = 'X_Y_Z_' // 'SVT' // YNUM3, &
     NGRID      = 1,                          &
@@ -1003,7 +1003,7 @@ DO JSV = NSV_CHEMBEG_A(KMI), NSV_CHEMEND_A(KMI)
     CMNHNAME   = TRIM( CNAMES(JSV-NSV_CHEMBEG_A(KMI)+1) ), &
     CSTDNAME   = '',                                       &
     CLONGNAME  = TRIM( CNAMES(JSV-NSV_CHEMBEG_A(KMI)+1) ), &
-    CUNITS     = 'ppp',                                    &
+    CUNITS     = 'ppv',                                    &
     CDIR       = 'XY',                                     &
     CCOMMENT   = 'X_Y_Z_' // 'SVT' // YNUM3,               &
     NGRID      = 1,                                        &
@@ -1021,7 +1021,7 @@ DO JSV = NSV_CHICBEG_A(KMI), NSV_CHICEND_A(KMI)
     CMNHNAME   = TRIM( CICNAMES(JSV-NSV_CHICBEG_A(KMI)+1) ), &
     CSTDNAME   = '',                                         &
     CLONGNAME  = TRIM( CICNAMES(JSV-NSV_CHICBEG_A(KMI)+1) ), &
-    CUNITS     = 'ppp',                                      &
+    CUNITS     = 'ppv',                                      &
     CDIR       = 'XY',                                       &
     CCOMMENT   = 'X_Y_Z_' // 'SVT' // YNUM3,                 &
     NGRID      = 1,                                          &
@@ -1039,7 +1039,7 @@ DO JSV = NSV_AERBEG_A(KMI), NSV_AEREND_A(KMI)
     CMNHNAME   = TRIM( CAERONAMES(JSV-NSV_AERBEG_A(KMI)+1) ), &
     CSTDNAME   = '',                                          &
     CLONGNAME  = TRIM( CAERONAMES(JSV-NSV_AERBEG_A(KMI)+1) ), &
-    CUNITS     = 'ppp',                                       &
+    CUNITS     = 'ppv',                                       &
     CDIR       = 'XY',                                        &
     CCOMMENT   = 'X_Y_Z_' // 'SVT' // YNUM3,                  &
     NGRID      = 1,                                           &
@@ -1057,7 +1057,7 @@ DO JSV = NSV_AERDEPBEG_A(KMI), NSV_AERDEPEND_A(KMI)
     CMNHNAME   = TRIM( CDEAERNAMES(JSV-NSV_AERDEPBEG_A(KMI)+1) ), &
     CSTDNAME   = '',                                              &
     CLONGNAME  = TRIM( CDEAERNAMES(JSV-NSV_AERDEPBEG_A(KMI)+1) ), &
-    CUNITS     = 'ppp',                                           &
+    CUNITS     = 'ppv',                                           &
     CDIR       = 'XY',                                            &
     CCOMMENT   = 'X_Y_Z_' // 'SVT' // YNUM3,                      &
     NGRID      = 1,                                               &
@@ -1075,7 +1075,7 @@ DO JSV = NSV_DSTBEG_A(KMI), NSV_DSTEND_A(KMI)
     CMNHNAME   = TRIM( CDUSTNAMES(JSV-NSV_DSTBEG_A(KMI)+1) ), &
     CSTDNAME   = '',                                          &
     CLONGNAME  = TRIM( CDUSTNAMES(JSV-NSV_DSTBEG_A(KMI)+1) ), &
-    CUNITS     = 'ppp',                                       &
+    CUNITS     = 'ppv',                                       &
     CDIR       = 'XY',                                        &
     CCOMMENT   = 'X_Y_Z_' // 'SVT' // YNUM3,                  &
     NGRID      = 1,                                           &
@@ -1093,7 +1093,7 @@ DO JSV = NSV_DSTDEPBEG_A(KMI), NSV_DSTDEPEND_A(KMI)
     CMNHNAME   = TRIM( CDEDSTNAMES(JSV-NSV_DSTDEPBEG_A(KMI)+1) ), &
     CSTDNAME   = '',                                              &
     CLONGNAME  = TRIM( CDEDSTNAMES(JSV-NSV_DSTDEPBEG_A(KMI)+1) ), &
-    CUNITS     = 'ppp',                                           &
+    CUNITS     = 'ppv',                                           &
     CDIR       = 'XY',                                            &
     CCOMMENT   = 'X_Y_Z_' // 'SVT' // YNUM3,                      &
     NGRID      = 1,                                               &
@@ -1111,7 +1111,7 @@ DO JSV = NSV_SLTBEG_A(KMI), NSV_SLTEND_A(KMI)
     CMNHNAME   = TRIM( CSALTNAMES(JSV-NSV_SLTBEG_A(KMI)+1) ), &
     CSTDNAME   = '',                                          &
     CLONGNAME  = TRIM( CSALTNAMES(JSV-NSV_SLTBEG_A(KMI)+1) ), &
-    CUNITS     = 'ppp',                                       &
+    CUNITS     = 'ppv',                                       &
     CDIR       = 'XY',                                        &
     CCOMMENT   = 'X_Y_Z_' // 'SVT' // YNUM3,                  &
     NGRID      = 1,                                           &
@@ -1129,7 +1129,7 @@ DO JSV = NSV_SLTDEPBEG_A(KMI), NSV_SLTDEPEND_A(KMI)
     CMNHNAME   = TRIM( CDESLTNAMES(JSV-NSV_SLTDEPBEG_A(KMI)+1) ), &
     CSTDNAME   = '',                                              &
     CLONGNAME  = TRIM( CDESLTNAMES(JSV-NSV_SLTDEPBEG_A(KMI)+1) ), &
-    CUNITS     = 'ppp',                                           &
+    CUNITS     = 'ppv',                                           &
     CDIR       = 'XY',                                            &
     CCOMMENT   = 'X_Y_Z_' // 'SVT' // YNUM3,                      &
     NGRID      = 1,                                               &
@@ -1165,7 +1165,7 @@ DO JSV = NSV_LNOXBEG_A(KMI), NSV_LNOXEND_A(KMI)
     CMNHNAME   = 'SVLNOX' // YNUM3,          &
     CSTDNAME   = '',                         &
     CLONGNAME  = 'SVLNOX' // YNUM3,          &
-    CUNITS     = 'ppp',                      &
+    CUNITS     = 'ppv',                      &
     CDIR       = 'XY',                       &
     CCOMMENT   = 'X_Y_Z_' // 'SVT' // YNUM3, &
     NGRID      = 1,                          &
diff --git a/src/MNH/modd_ch_flxn.f90 b/src/MNH/modd_ch_flxn.f90
index 47c729a93..4a1e9930f 100644
--- a/src/MNH/modd_ch_flxn.f90
+++ b/src/MNH/modd_ch_flxn.f90
@@ -1,13 +1,8 @@
-!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2016-2022 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: /home/cvsroot/MNH-VX-Y-Z/src/MNH/modd_ch_flxn.f90,v $ $Revision: 1.1 $
-! MASDEV5_2 modd 2016/06/27 14:05:40
-!-----------------------------------------------------------------
 !     #####################
       MODULE MODD_CH_FLX_n
 !     ######################
@@ -42,7 +37,7 @@ IMPLICIT NONE
 
 TYPE CH_FLX_t
 !
-  REAL, DIMENSION(:,:,:), POINTER :: XCHFLX=>NULL() ! chemical fluxes ppp.m/s at t
+  REAL, DIMENSION(:,:,:), POINTER :: XCHFLX=>NULL() ! chemical fluxes ppv.m/s at t
 !
 END TYPE CH_FLX_t
 
diff --git a/src/MNH/mode_aero_psd.f90 b/src/MNH/mode_aero_psd.f90
index cb09f5461..9eedf4e47 100644
--- a/src/MNH/mode_aero_psd.f90
+++ b/src/MNH/mode_aero_psd.f90
@@ -1,19 +1,14 @@
-!ORILAM_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
+!ORILAM_LIC Copyright 2006-2022 CNRS, Meteo-France and Universite Paul Sabatier
 !ORILAM_LIC This is part of the ORILAM software governed by the CeCILL-C licence
 !ORILAM_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !ORILAM_LIC for details.
 !-----------------------------------------------------------------
-!-----------------------------------------------------------------
-!--------------- special set of characters for RCS information
-!-----------------------------------------------------------------
-! $Source$ $Revision$ $Date$
-!-----------------------------------------------------------------
 !!   ########################
 MODULE MODE_AERO_PSD
 !!   ########################
 !!
 !! MODULE DUST PSD (Particle Size Distribution)
-!! Purpose: Contains subroutines to convert from transported variables (ppp)
+!! Purpose: Contains subroutines to convert from transported variables (ppv)
 !! to understandable aerosol variables, e.g. #/m3, kg/m3, sigma, R_{n}
 
 USE MODD_CH_AEROSOL
@@ -29,7 +24,7 @@ CONTAINS
 ! 
 !    ############################################################
   SUBROUTINE PPP2AERO(             &
-       PSVT                         & !I [ppp] input scalar variables (moment of distribution)
+       PSVT                         & !I [ppv] input scalar variables (moment of distribution)
        , PRHODREF                   & !I [kg/m3] density of air       
        , PSIG3D                     & !O [-] standard deviation of aerosol distribution
        , PRG3D                      & !O [um] number median diameter of aerosol distribution
@@ -43,7 +38,7 @@ CONTAINS
 !!
 !!    PURPOSE
 !!    -------
-!!    Translate the three moments M0, M3 and M6 given in ppp into
+!!    Translate the three moments M0, M3 and M6 given in ppv into
 !!    Values which can be understood more easily (R, sigma, N, M)
 !! 
 !!    CALLING STRUCTURE NOTE: OPTIONAL VARIABLES
@@ -317,7 +312,7 @@ END SUBROUTINE PPP2AERO
 !
 !   ############################################################
   SUBROUTINE AERO2PPP(             &
-       PSVT                         & !IO [ppp] input scalar variables (moment of distribution)
+       PSVT                         & !IO [ppv] input scalar variables (moment of distribution)
        , PRHODREF                   & !I [kg/m3] density of air       
        , PSIG3D                     & !I [-] standard deviation of aerosol distribution
        , PRG3D                      & !I [um] number median diameter of aerosol distribution
@@ -328,7 +323,7 @@ END SUBROUTINE PPP2AERO
 !!
 !!    PURPOSE
 !!    -------
-!!    Translate the aerosol Mass, RG and SIGMA in the  three moments M0, M3 and M6 given in ppp 
+!!    Translate the aerosol Mass, RG and SIGMA in the  three moments M0, M3 and M6 given in ppv 
 !!
 !!    REFERENCE
 !!    ---------
@@ -519,7 +514,7 @@ ZCTOTA(:,:,:,:,:) = 0.
  ZM(:,:,:,6) = ZM(:,:,:,4)*(PRG3D(:,:,:,2)**6) * &
                EXP(18 *(LOG(PSIG3D(:,:,:,2)))**2)
 
-!*       6    return to ppp
+!*       6    return to ppv
 !
 PSVT(:,:,:,JP_CH_M0i) = ZM(:,:,:,1) * 1E-6 
 PSVT(:,:,:,JP_CH_M0j) = ZM(:,:,:,4) * 1E-6
@@ -537,7 +532,7 @@ END SUBROUTINE AERO2PPP
 !
 !    ############################################################
   SUBROUTINE PPP2AERO1D(            &
-       PSVT                         & !I [ppp] input scalar variables (moment of distribution)
+       PSVT                         & !I [ppv] input scalar variables (moment of distribution)
        , PRHODREF                   & !I [kg/m3] density of air       
        , PMI                        & !O molecular weight
        , PSIG1D                     & !O [-] standard deviation of aerosol distribution
@@ -551,7 +546,7 @@ END SUBROUTINE AERO2PPP
 !!
 !!    PURPOSE
 !!    -------
-!!    Translate the three moments M0, M3 and M6 given in ppp into
+!!    Translate the three moments M0, M3 and M6 given in ppv into
 !!    Values which can be understood more easily (R, sigma, N, M)
 !! 
 !!    CALLING STRUCTURE NOTE: OPTIONAL VARIABLES
diff --git a/src/MNH/mode_blowsnow_psd.f90 b/src/MNH/mode_blowsnow_psd.f90
index 71298e331..6e741809b 100644
--- a/src/MNH/mode_blowsnow_psd.f90
+++ b/src/MNH/mode_blowsnow_psd.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1994-2018 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2018-2022 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.
@@ -32,7 +32,7 @@ CONTAINS
 !
 !!   ############################################################
   SUBROUTINE PPP2SNOW(             &
-       PSVT                         & !I [ppp] input scalar variables (moment of distribution)
+       PSVT                         & !I [ppv] input scalar variables (moment of distribution)
        , PRHODREF                   & !I [kg/m3] density of air       
        , PBET3D                     & !O [m] scale parameter of snow distribution
        , PRG3D                      & !O [um] mean radius of snow  distribution
@@ -72,7 +72,7 @@ CONTAINS
 !
 !*      0.1    declarations of arguments
 !
-REAL,       DIMENSION(:,:,:,:),  INTENT(INOUT)  :: PSVT      !I [ppp] first moment
+REAL,       DIMENSION(:,:,:,:),  INTENT(INOUT)  :: PSVT      !I [ppv] first moment
 REAL,       DIMENSION(:,:,:),    INTENT(IN)     :: PRHODREF !I [kg/m3] density of air
 
 REAL,       DIMENSION(:,:,:),  OPTIONAL, INTENT(OUT)     :: PBET3D   !O [-] scale parameter
diff --git a/src/MNH/mode_dust_psd.f90 b/src/MNH/mode_dust_psd.f90
index 70e078f5e..3fdff9eb7 100644
--- a/src/MNH/mode_dust_psd.f90
+++ b/src/MNH/mode_dust_psd.f90
@@ -1,12 +1,8 @@
-!ORILAM_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
+!ORILAM_LIC Copyright 2005-2022 CNRS, Meteo-France and Universite Paul Sabatier
 !ORILAM_LIC This is part of the ORILAM software governed by the CeCILL-C licence
 !ORILAM_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !ORILAM_LIC for details.
 !-----------------------------------------------------------------
-!--------------- special set of characters for RCS information
-!-----------------------------------------------------------------
-! $Source$ $Revision$ $Date$
-!-----------------------------------------------------------------
 !!   ########################
      MODULE MODE_DUST_PSD
 !!   ########################
@@ -14,7 +10,7 @@
 !!    PURPOSE
 !!    -------
 !! MODULE DUST PSD (Particle Size Distribution)
-!! Purpose: Contains subroutines to convert from transported variables (ppp)
+!! Purpose: Contains subroutines to convert from transported variables (ppv)
 !! to understandable aerosol variables, e.g. #/m3, kg/m3, sigma, R_{n}
 !!
 !!    AUTHOR
@@ -45,7 +41,7 @@ CONTAINS
 !
 !!   ############################################################
   SUBROUTINE PPP2DUST(             &
-       PSVT                         & !I [ppp] input scalar variables (moment of distribution)
+       PSVT                         & !I [ppv] input scalar variables (moment of distribution)
        , PRHODREF                   & !I [kg/m3] density of air       
        , PSIG3D                     & !O [-] standard deviation of aerosol distribution
        , PRG3D                      & !O [um] number median diameter of aerosol distribution
@@ -58,7 +54,7 @@ CONTAINS
 !!
 !!    PURPOSE
 !!    -------
-!!    Translate the three moments M0, M3 and M6 given in ppp into
+!!    Translate the three moments M0, M3 and M6 given in ppv into
 !!    Values which can be understood more easily (R, sigma, N, M)
 !! 
 !!    CALLING STRUCTURE NOTE: OPTIONAL VARIABLES
@@ -92,7 +88,7 @@ CONTAINS
 !
 !*      0.1    declarations of arguments
 !
-REAL,       DIMENSION(:,:,:,:),  INTENT(INOUT)  :: PSVT      !I [ppp] first moment
+REAL,       DIMENSION(:,:,:,:),  INTENT(INOUT)  :: PSVT      !I [ppv] first moment
 REAL,       DIMENSION(:,:,:),    INTENT(IN)     :: PRHODREF !I [kg/m3] density of air
 
 REAL,       DIMENSION(:,:,:,:),  OPTIONAL, INTENT(OUT)     :: PSIG3D   !O [-] standard deviation
@@ -324,7 +320,7 @@ END SUBROUTINE PPP2DUST
 
 !!   ############################################################
   SUBROUTINE DUST2PPP(             &
-       PSVT                         & !IO [ppp] input scalar variables (moment of distribution)
+       PSVT                         & !IO [ppv] input scalar variables (moment of distribution)
        , PRHODREF                   & !I [kg/m3] density of air       
        , PSIG3D                     & !I [-] standard deviation of aerosol distribution
        , PRG3D                      & !I [um] number median diameter of aerosol distribution
@@ -334,7 +330,7 @@ END SUBROUTINE PPP2DUST
 !!
 !!    PURPOSE
 !!    -------
-!!    Translate the dust Mass, RG and SIGMA in the  three moments M0, M3 and M6 given in ppp 
+!!    Translate the dust Mass, RG and SIGMA in the  three moments M0, M3 and M6 given in ppv 
 !! 
 !!    CALLING STRUCTURE NOTE: OPTIONAL VARIABLES
 !!    -------
@@ -539,7 +535,7 @@ DEALLOCATE(NM0)
 END SUBROUTINE DUST2PPP
 !!   ############################################################
   SUBROUTINE PPP2DUST1D(             &
-       PSVT                         & !I [ppp] input scalar variables (moment of distribution)
+       PSVT                         & !I [ppv] input scalar variables (moment of distribution)
        , PRHODREF                   & !I [kg/m3] density of air       
        , PSIG1D                     & !O [-] standard deviation of aerosol distribution
        , PRG1D                      & !O [um] number median diameter of aerosol distribution
@@ -552,7 +548,7 @@ END SUBROUTINE DUST2PPP
 !!
 !!    PURPOSE
 !!    -------
-!!    Translate the three moments M0, M3 and M6 given in ppp into
+!!    Translate the three moments M0, M3 and M6 given in ppv into
 !!    Values which can be understood more easily (R, sigma, N, M)
 !! 
 !!    CALLING STRUCTURE NOTE: OPTIONAL VARIABLES
@@ -586,7 +582,7 @@ END SUBROUTINE DUST2PPP
 !
 !*      0.1    declarations of arguments
 !
-REAL,       DIMENSION(:,:),  INTENT(INOUT)  :: PSVT      !I [ppp] first moment
+REAL,       DIMENSION(:,:),  INTENT(INOUT)  :: PSVT      !I [ppv] first moment
 REAL,       DIMENSION(:),    INTENT(IN)     :: PRHODREF !I [kg/m3] density of air
 
 REAL,       DIMENSION(:,:),  OPTIONAL, INTENT(OUT)     :: PSIG1D   !O [-] standard deviation
diff --git a/src/MNH/mode_salt_psd.f90 b/src/MNH/mode_salt_psd.f90
index dc5a8611e..c014096a8 100644
--- a/src/MNH/mode_salt_psd.f90
+++ b/src/MNH/mode_salt_psd.f90
@@ -1,12 +1,8 @@
-!ORILAM_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
+!ORILAM_LIC Copyright 2005-2022 CNRS, Meteo-France and Universite Paul Sabatier
 !ORILAM_LIC This is part of the ORILAM software governed by the CeCILL-C licence
 !ORILAM_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !ORILAM_LIC for details.
 !-----------------------------------------------------------------
-!--------------- special set of characters for RCS information
-!-----------------------------------------------------------------
-! $Source$ $Revision$ $Date$
-!-----------------------------------------------------------------
 !!   ########################
      MODULE MODE_SALT_PSD
 !!   ########################
@@ -14,7 +10,7 @@
 !!    PURPOSE
 !!    -------
 !! MODULE SALT PSD (Particle Size Distribution)
-!! Purpose: Contains subroutines to convert from transported variables (ppp)
+!! Purpose: Contains subroutines to convert from transported variables (ppv)
 !! to understandable aerosol variables, e.g. #/m3, kg/m3, sigma, R_{n}
 !!
 !!    AUTHOR
@@ -50,7 +46,7 @@ CONTAINS
 !
 !!   ############################################################
   SUBROUTINE PPP2SALT(             &
-       PSVT                         & !I [ppp] input scalar variables (moment of distribution)
+       PSVT                         & !I [ppv] input scalar variables (moment of distribution)
        , PRHODREF                   & !I [kg/m3] density of air       
        , PSIG3D                     & !O [-] standard deviation of aerosol distribution
        , PRG3D                      & !O [um] number median diameter of aerosol distribution
@@ -63,7 +59,7 @@ CONTAINS
 !!
 !!    PURPOSE
 !!    -------
-!!    Translate the three moments M0, M3 and M6 given in ppp into
+!!    Translate the three moments M0, M3 and M6 given in ppv into
 !!    Values which can be understood more easily (R, sigma, N, M)
 !! 
 !!    CALLING STRUCTURE NOTE: OPTIONAL VARIABLES
@@ -97,7 +93,7 @@ CONTAINS
 !
 !*      0.1    declarations of arguments
 !
-REAL,       DIMENSION(:,:,:,:),  INTENT(INOUT)  :: PSVT      !I [ppp] first moment
+REAL,       DIMENSION(:,:,:,:),  INTENT(INOUT)  :: PSVT      !I [ppv] first moment
 REAL,       DIMENSION(:,:,:),    INTENT(IN)     :: PRHODREF !I [kg/m3] density of air
 
 REAL,       DIMENSION(:,:,:,:),  OPTIONAL, INTENT(OUT)     :: PSIG3D   !O [-] standard deviation
@@ -354,7 +350,7 @@ END SUBROUTINE PPP2SALT
 
 !!   ############################################################
   SUBROUTINE SALT2PPP(             &
-       PSVT                         & !IO [ppp] input scalar variables (moment of distribution)
+       PSVT                         & !IO [ppv] input scalar variables (moment of distribution)
        , PRHODREF                   & !I [kg/m3] density of air       
        , PSIG3D                     & !I [-] standard deviation of aerosol distribution
        , PRG3D                      & !I [um] number median diameter of aerosol distribution
@@ -364,7 +360,7 @@ END SUBROUTINE PPP2SALT
 !!
 !!    PURPOSE
 !!    -------
-!!    Translate the sea salt Mass, RG and SIGMA in the  three moments M0, M3 and M6 given in ppp 
+!!    Translate the sea salt Mass, RG and SIGMA in the  three moments M0, M3 and M6 given in ppv 
 !! 
 !!    CALLING STRUCTURE NOTE: OPTIONAL VARIABLES
 !!    -------
@@ -571,7 +567,7 @@ END SUBROUTINE SALT2PPP
 !
 !!   ############################################################
   SUBROUTINE PPP2SALT1D(             &
-       PSVT                         & !I [ppp] input scalar variables (moment of distribution)
+       PSVT                         & !I [ppv] input scalar variables (moment of distribution)
        , PRHODREF                   & !I [kg/m3] density of air       
        , PSIG1D                     & !O [-] standard deviation of aerosol distribution
        , PRG1D                      & !O [um] number median diameter of aerosol distribution
@@ -584,7 +580,7 @@ END SUBROUTINE SALT2PPP
 !!
 !!    PURPOSE
 !!    -------
-!!    Translate the three moments M0, M3 and M6 given in ppp into
+!!    Translate the three moments M0, M3 and M6 given in ppv into
 !!    Values which can be understood more easily (R, sigma, N, M)
 !! 
 !!    CALLING STRUCTURE NOTE: OPTIONAL VARIABLES
@@ -618,7 +614,7 @@ END SUBROUTINE SALT2PPP
 !
 !*      0.1    declarations of arguments
 !
-REAL,       DIMENSION(:,:),  INTENT(INOUT)  :: PSVT      !I [ppp] first moment
+REAL,       DIMENSION(:,:),  INTENT(INOUT)  :: PSVT      !I [ppv] first moment
 REAL,       DIMENSION(:),    INTENT(IN)     :: PRHODREF !I [kg/m3] density of air
 
 REAL,       DIMENSION(:,:),  OPTIONAL, INTENT(OUT)     :: PSIG1D   !O [-] standard deviation
diff --git a/src/MNH/mode_salt_psd_wet.f90 b/src/MNH/mode_salt_psd_wet.f90
index cb5af52f8..2a679f193 100644
--- a/src/MNH/mode_salt_psd_wet.f90
+++ b/src/MNH/mode_salt_psd_wet.f90
@@ -1,12 +1,8 @@
-!ORILAM_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
+!ORILAM_LIC Copyright 2005-2022 CNRS, Meteo-France and Universite Paul Sabatier
 !ORILAM_LIC This is part of the ORILAM software governed by the CeCILL-C licence
 !ORILAM_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !ORILAM_LIC for details.
 !-----------------------------------------------------------------
-!--------------- special set of characters for RCS information
-!-----------------------------------------------------------------
-! $Source: /home/cvsroot/MNH-VX-Y-Z/src/MNH/Attic/mode_salt_psd.f90,v $ $Revision: 1.1.2.1.2.1.2.1.2.1 $ $Date: 2013/07/12 13:55:08 $
-!-----------------------------------------------------------------
 !!   ########################
      MODULE MODE_SALT_PSD_WET
 !!   ########################
@@ -14,7 +10,7 @@
 !!    PURPOSE
 !!    -------
 !! MODULE SALT PSD (Particle Size Distribution)
-!! Purpose: Contains subroutines to convert from transported variables (ppp)
+!! Purpose: Contains subroutines to convert from transported variables (ppv)
 !! to understandable aerosol variables, e.g. #/m3, kg/m3, sigma, R_{n}
 !!
 !!    AUTHOR
@@ -56,7 +52,7 @@ CONTAINS
 !
 !!   ############################################################
   SUBROUTINE PPP2SALT_WET(          &
-       PSVT                         & !I [ppp] input scalar variables (moment of distribution)
+       PSVT                         & !I [ppv] input scalar variables (moment of distribution)
        , PRHODREF                   & !I [kg/m3] density of air       
        , PPABST                     & !I Pression
        , PTHT                       & !I Potential temperature
@@ -73,7 +69,7 @@ CONTAINS
 !!
 !!    PURPOSE
 !!    -------
-!!    Translate the three moments M0, M3 and M6 given in ppp into
+!!    Translate the three moments M0, M3 and M6 given in ppv into
 !!    Values which can be understood more easily (R, sigma, N, M)
 !!    
 !!    Calcul the wet radius of the particles, using RH and Gerber (1985) relation
@@ -111,7 +107,7 @@ CONTAINS
 !
 !*      0.1    declarations of arguments
 !
-REAL, DIMENSION(:,:,:,:),           INTENT(INOUT) :: PSVT      !I [ppp] first moment
+REAL, DIMENSION(:,:,:,:),           INTENT(INOUT) :: PSVT      !I [ppv] first moment
 REAL, DIMENSION(:,:,:),             INTENT(IN)    :: PRHODREF  !I [kg/m3] density of air
 REAL, DIMENSION(:,:,:),             INTENT(IN)    :: PPABST    !I Pression
 REAL, DIMENSION(:,:,:),             INTENT(IN)    :: PTHT      !I Potential temperature
@@ -432,7 +428,7 @@ END SUBROUTINE PPP2SALT_WET
 
 !!   ############################################################
   SUBROUTINE SALT2PPP(             &
-       PSVT                         & !IO [ppp] input scalar variables (moment of distribution)
+       PSVT                         & !IO [ppv] input scalar variables (moment of distribution)
        , PRHODREF                   & !I [kg/m3] density of air       
        , PSIG3D                     & !I [-] standard deviation of aerosol distribution
        , PRG3D                      & !I [um] number median diameter of aerosol distribution
@@ -442,7 +438,7 @@ END SUBROUTINE PPP2SALT_WET
 !!
 !!    PURPOSE
 !!    -------
-!!    Translate the sea salt Mass, RG and SIGMA in the  three moments M0, M3 and M6 given in ppp 
+!!    Translate the sea salt Mass, RG and SIGMA in the  three moments M0, M3 and M6 given in ppv 
 !! 
 !!    CALLING STRUCTURE NOTE: OPTIONAL VARIABLES
 !!    -------
@@ -645,7 +641,7 @@ END SUBROUTINE SALT2PPP
 !
 !!   ############################################################
   SUBROUTINE PPP2SALT1D(             &
-       PSVT                         & !I [ppp] input scalar variables (moment of distribution)
+       PSVT                         & !I [ppv] input scalar variables (moment of distribution)
        , PRHODREF                   & !I [kg/m3] density of air       
        , PSIG1D                     & !O [-] standard deviation of aerosol distribution
        , PRG1D                      & !O [um] number median diameter of aerosol distribution
@@ -658,7 +654,7 @@ END SUBROUTINE SALT2PPP
 !!
 !!    PURPOSE
 !!    -------
-!!    Translate the three moments M0, M3 and M6 given in ppp into
+!!    Translate the three moments M0, M3 and M6 given in ppv into
 !!    Values which can be understood more easily (R, sigma, N, M)
 !! 
 !!    CALLING STRUCTURE NOTE: OPTIONAL VARIABLES
@@ -692,7 +688,7 @@ END SUBROUTINE SALT2PPP
 !
 !*      0.1    declarations of arguments
 !
-REAL,       DIMENSION(:,:),  INTENT(INOUT)  :: PSVT      !I [ppp] first moment
+REAL,       DIMENSION(:,:),  INTENT(INOUT)  :: PSVT      !I [ppv] first moment
 REAL,       DIMENSION(:),    INTENT(IN)     :: PRHODREF !I [kg/m3] density of air
 
 REAL,       DIMENSION(:,:),  OPTIONAL, INTENT(OUT)     :: PSIG1D   !O [-] standard deviation
diff --git a/src/MNH/radiations.f90 b/src/MNH/radiations.f90
index 809d0d6f0..3778dd245 100644
--- a/src/MNH/radiations.f90
+++ b/src/MNH/radiations.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1995-2021 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1995-2022 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.
@@ -897,7 +897,7 @@ IF (CAOP=='EXPL') THEN
   
  IF (LORILAM) THEN
    CALL AEROOPT_GET(                             &
-        PSVT(IIB:IIE,IJB:IJE,:,NSV_AERBEG:NSV_AEREND)        &  !I [ppp]  aerosols concentration
+        PSVT(IIB:IIE,IJB:IJE,:,NSV_AERBEG:NSV_AEREND)        &  !I [ppv]  aerosols concentration
         ,PZZ(IIB:IIE,IJB:IJE,:)                   &  !I [m] height of layers
         ,PRHODREF(IIB:IIE,IJB:IJE,:)              &  !I [kg/m3] density of air
         ,ZPIZA_AER_TMP(IIB:IIE,IJB:IJE,IKB-JPVEXT:IKE-JPVEXT,:)   &  !O [-] single scattering albedo of aerosols
@@ -911,7 +911,7 @@ IF (CAOP=='EXPL') THEN
  ENDIF
  IF(LDUST) THEN
    CALL DUSTOPT_GET(                             &
-        PSVT(IIB:IIE,IJB:IJE,:,NSV_DSTBEG:NSV_DSTEND)        &  !I [ppp] Dust scalar concentration
+        PSVT(IIB:IIE,IJB:IJE,:,NSV_DSTBEG:NSV_DSTEND)        &  !I [ppv] Dust scalar concentration
         ,PZZ(IIB:IIE,IJB:IJE,:)                   &  !I [m] height of layers
         ,PRHODREF(IIB:IIE,IJB:IJE,:)              &  !I [kg/m3] density of air
         ,ZPIZA_DST_TMP(IIB:IIE,IJB:IJE,IKB-JPVEXT:IKE-JPVEXT,:)   &  !O [-] single scattering albedo of dust
@@ -926,7 +926,7 @@ IF (CAOP=='EXPL') THEN
  ENDIF
  IF(LSALT) THEN
    CALL SALTOPT_GET(                             &
-        PSVT(IIB:IIE,IJB:IJE,:,NSV_SLTBEG:NSV_SLTEND)        &  !I [ppp] sea salt scalar concentration
+        PSVT(IIB:IIE,IJB:IJE,:,NSV_SLTBEG:NSV_SLTEND)        &  !I [ppv] sea salt scalar concentration
         ,PZZ(IIB:IIE,IJB:IJE,:)                   &  !I [m] height of layers
         ,PRHODREF(IIB:IIE,IJB:IJE,:)              &  !I [kg/m3] density of air
         ,PTHT(IIB:IIE,IJB:IJE,:)                  &  !I [K] potential temperature
diff --git a/src/MNH/read_all_data_grib_case.f90 b/src/MNH/read_all_data_grib_case.f90
index 841ae62b0..18ac78eda 100644
--- a/src/MNH/read_all_data_grib_case.f90
+++ b/src/MNH/read_all_data_grib_case.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1998-2021 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1998-2022 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.
@@ -1362,7 +1362,7 @@ IF (IMODEL==5) THEN
   XSV_LS(:,:,:,:) = 0.
   ILEV1=-1
 !
-  WRITE (ILUOUT0,'(A,A4,A)') ' | Reading Mocage species (ppp) from ',HFILE,' file'
+  WRITE (ILUOUT0,'(A,A4,A)') ' | Reading Mocage species (ppv) from ',HFILE,' file'
 !
 !*       2.6.1  read mocage species
 !
diff --git a/src/MNH/read_chem_data_netcdf_case.f90 b/src/MNH/read_chem_data_netcdf_case.f90
index 547a55b53..d779c372a 100644
--- a/src/MNH/read_chem_data_netcdf_case.f90
+++ b/src/MNH/read_chem_data_netcdf_case.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2012-2021 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2012-2022 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.
@@ -439,7 +439,7 @@ enddo
     ALLOCATE (XSV_LS(IIU,IJU,ilevlen,NSV))
    XSV_LS(:,:,:,:) = 0.
 !
-  WRITE (ILUOUT0,'(A,A4,A)') ' | Reading MOZART species (ppp) from ',HFILE,' file'
+  WRITE (ILUOUT0,'(A,A4,A)') ' | Reading MOZART species (ppv) from ',HFILE,' file'
 
 where (ZLONOUT(:) < 0.) ZLONOUT(:) = ZLONOUT(:) + 360.
 !
diff --git a/src/MNH/read_field.f90 b/src/MNH/read_field.f90
index a21ac5b41..0264f75c6 100644
--- a/src/MNH/read_field.f90
+++ b/src/MNH/read_field.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1994-2021 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1994-2022 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.
@@ -977,7 +977,7 @@ END IF
 !
 IF (NSV_CHICEND>=NSV_CHICBEG) THEN
   TZFIELD%CSTDNAME   = ''
-  TZFIELD%CUNITS     = 'ppp'
+  TZFIELD%CUNITS     = 'ppv'
   TZFIELD%CDIR       = 'XY'
   TZFIELD%NGRID      = 1
   TZFIELD%NTYPE      = TYPEREAL
@@ -1000,7 +1000,7 @@ END IF
 !
 IF (NSV_SLTEND>=NSV_SLTBEG) THEN
   TZFIELD%CSTDNAME   = ''
-  TZFIELD%CUNITS     = 'ppp'
+  TZFIELD%CUNITS     = 'ppv'
   TZFIELD%CDIR       = 'XY'
   TZFIELD%NGRID      = 1
   TZFIELD%NTYPE      = TYPEREAL
@@ -1022,7 +1022,7 @@ END IF
 !
 IF (NSV_SLTDEPEND>=NSV_SLTDEPBEG) THEN
   TZFIELD%CSTDNAME   = ''
-  TZFIELD%CUNITS     = 'ppp'
+  TZFIELD%CUNITS     = 'ppv'
   TZFIELD%CDIR       = 'XY'
   TZFIELD%NGRID      = 1
   TZFIELD%NTYPE      = TYPEREAL
@@ -1044,7 +1044,7 @@ END IF
 !
 IF (NSV_DSTEND>=NSV_DSTBEG) THEN
   TZFIELD%CSTDNAME   = ''
-  TZFIELD%CUNITS     = 'ppp'
+  TZFIELD%CUNITS     = 'ppv'
   TZFIELD%CDIR       = 'XY'
   TZFIELD%NGRID      = 1
   TZFIELD%NTYPE      = TYPEREAL
@@ -1066,7 +1066,7 @@ END IF
 !
 IF (NSV_DSTDEPEND>=NSV_DSTDEPBEG) THEN
   TZFIELD%CSTDNAME   = ''
-  TZFIELD%CUNITS     = 'ppp'
+  TZFIELD%CUNITS     = 'ppv'
   TZFIELD%CDIR       = 'XY'
   TZFIELD%NGRID      = 1
   TZFIELD%NTYPE      = TYPEREAL
@@ -1088,7 +1088,7 @@ END IF
 !
 IF (NSV_AEREND>=NSV_AERBEG) THEN
   TZFIELD%CSTDNAME   = ''
-  TZFIELD%CUNITS     = 'ppp'
+  TZFIELD%CUNITS     = 'ppv'
   TZFIELD%CDIR       = 'XY'
   TZFIELD%NGRID      = 1
   TZFIELD%NTYPE      = TYPEREAL
@@ -1110,7 +1110,7 @@ END IF
 !
 IF (NSV_AERDEPEND>=NSV_AERDEPBEG) THEN
   TZFIELD%CSTDNAME   = ''
-  TZFIELD%CUNITS     = 'ppp'
+  TZFIELD%CUNITS     = 'ppv'
   TZFIELD%CDIR       = 'XY'
   TZFIELD%NGRID      = 1
   TZFIELD%NTYPE      = TYPEREAL
@@ -1241,7 +1241,7 @@ END IF
 !
 IF (NSV_LNOXEND>=NSV_LNOXBEG) THEN
   TZFIELD%CSTDNAME   = ''
-  TZFIELD%CUNITS     = 'ppp'
+  TZFIELD%CUNITS     = 'ppv'
   TZFIELD%CDIR       = 'XY'
   TZFIELD%NGRID      = 1
   TZFIELD%NTYPE      = TYPEREAL
diff --git a/src/MNH/sedim_blowsnow.f90 b/src/MNH/sedim_blowsnow.f90
index 2cb0f8264..75985a3dc 100644
--- a/src/MNH/sedim_blowsnow.f90
+++ b/src/MNH/sedim_blowsnow.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2018-2021 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2018-2022 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.
@@ -17,7 +17,7 @@ SUBROUTINE SEDIM_BLOWSNOW(  &
      ,PDTMONITOR        & !I Time step
      ,PRHODREF          & !I [kg/m3] air density
      ,PZZ               & !I [m] height of layers
-     ,PSVT              & !IO [scalar variable, ppp] Blowing snow concentration
+     ,PSVT              & !IO [scalar variable, ppv] Blowing snow concentration
      ,PSVS              & !IO ! Blowing snow variable source
      ,PVGK              &  !I [m/s] Blowing snow variable settling velocity 
      )
diff --git a/src/MNH/sedim_dust.f90 b/src/MNH/sedim_dust.f90
index 145939e1f..339f4cfa7 100644
--- a/src/MNH/sedim_dust.f90
+++ b/src/MNH/sedim_dust.f90
@@ -1,4 +1,4 @@
-!ORILAM_LIC Copyright 2006-2019 CNRS, Meteo-France and Universite Paul Sabatier
+!ORILAM_LIC Copyright 2006-2022 CNRS, Meteo-France and Universite Paul Sabatier
 !ORILAM_LIC This is part of the ORILAM software governed by the CeCILL-C licence
 !ORILAM_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !ORILAM_LIC for details.
@@ -15,7 +15,7 @@ SUBROUTINE SEDIM_DUST(  &
      ,PRHODREF          & !I [kg/m3] air density
      ,PPABST            & !I [Pa] pressure
      ,PZZ               & !I [m] height of layers
-     ,PSVT              & !IO [scalar variable, ppp] sea salt concentration
+     ,PSVT              & !IO [scalar variable, ppv] sea salt concentration
      )
 
 IMPLICIT NONE
@@ -241,7 +241,7 @@ ELSE
   LSEDFIX = .TRUE.
 END IF
 !
-!*       5.   Return to concentration in ppp (#/molec_{air})
+!*       5.   Return to concentration in ppv (#/molec_{air})
 !
 DO JN=1,NMODE_DST
 IF (LVARSIG) THEN
diff --git a/src/MNH/sedim_salt.f90 b/src/MNH/sedim_salt.f90
index 43e407a88..702737741 100644
--- a/src/MNH/sedim_salt.f90
+++ b/src/MNH/sedim_salt.f90
@@ -1,4 +1,4 @@
-!ORILAM_LIC Copyright 2006-2019 CNRS, Meteo-France and Universite Paul Sabatier
+!ORILAM_LIC Copyright 2006-2022 CNRS, Meteo-France and Universite Paul Sabatier
 !ORILAM_LIC This is part of the ORILAM software governed by the CeCILL-C licence
 !ORILAM_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !ORILAM_LIC for details.
@@ -15,7 +15,7 @@ SUBROUTINE SEDIM_SALT(  &
      ,PRHODREF          & !I [kg/m3] air density
      ,PPABST            & !I [Pa] pressure
      ,PZZ               & !I [m] height of layers
-     ,PSVT              & !IO [scalar variable, ppp] sea salt concentration
+     ,PSVT              & !IO [scalar variable, ppv] sea salt concentration
      )
 
 IMPLICIT NONE
@@ -241,7 +241,7 @@ ELSE
   LSEDFIX = .TRUE.
 END IF
 !
-!*       5.   Return to concentration in ppp (#/molec_{air})
+!*       5.   Return to concentration in ppv (#/molec_{air})
 !
 DO JN=1,NMODE_SLT
 IF (LVARSIG_SLT) THEN
diff --git a/src/MNH/spawn_field2.f90 b/src/MNH/spawn_field2.f90
index e774f4c61..a36f75467 100644
--- a/src/MNH/spawn_field2.f90
+++ b/src/MNH/spawn_field2.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1995-2021 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1995-2022 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.
@@ -912,7 +912,7 @@ IF (PRESENT(TPSONFILE)) THEN
     !
     IF (NSV_CHEMEND>=NSV_CHEMBEG) THEN
       TZFIELD%CSTDNAME   = ''
-      TZFIELD%CUNITS     = 'ppp'
+      TZFIELD%CUNITS     = 'ppv'
       TZFIELD%CDIR       = 'XY'
       TZFIELD%NGRID      = 1
       TZFIELD%NTYPE      = TYPEREAL
@@ -932,7 +932,7 @@ IF (PRESENT(TPSONFILE)) THEN
     !
     IF (NSV_CHICEND>=NSV_CHICBEG) THEN
       TZFIELD%CSTDNAME   = ''
-      TZFIELD%CUNITS     = 'ppp'
+      TZFIELD%CUNITS     = 'ppv'
       TZFIELD%CDIR       = 'XY'
       TZFIELD%NGRID      = 1
       TZFIELD%NTYPE      = TYPEREAL
@@ -953,7 +953,7 @@ IF (PRESENT(TPSONFILE)) THEN
     !
     IF (NSV_AEREND>=NSV_AERBEG) THEN
       TZFIELD%CSTDNAME   = ''
-      TZFIELD%CUNITS     = 'ppp'
+      TZFIELD%CUNITS     = 'ppv'
       TZFIELD%CDIR       = 'XY'
       TZFIELD%NGRID      = 1
       TZFIELD%NTYPE      = TYPEREAL
@@ -973,7 +973,7 @@ IF (PRESENT(TPSONFILE)) THEN
     !
     IF (NSV_DSTEND>=NSV_DSTBEG) THEN
       TZFIELD%CSTDNAME   = ''
-      TZFIELD%CUNITS     = 'ppp'
+      TZFIELD%CUNITS     = 'ppv'
       TZFIELD%CDIR       = 'XY'
       TZFIELD%NGRID      = 1
       TZFIELD%NTYPE      = TYPEREAL
@@ -993,7 +993,7 @@ IF (PRESENT(TPSONFILE)) THEN
     !
     IF (NSV_SLTEND>=NSV_SLTBEG) THEN
       TZFIELD%CSTDNAME   = ''
-      TZFIELD%CUNITS     = 'ppp'
+      TZFIELD%CUNITS     = 'ppv'
       TZFIELD%CDIR       = 'XY'
       TZFIELD%NGRID      = 1
       TZFIELD%NTYPE      = TYPEREAL
@@ -1035,7 +1035,7 @@ IF (PRESENT(TPSONFILE)) THEN
 !PW:TODO/bug2?: Same name of variable in a loop!
     IF (NSV_LNOXEND>=NSV_LNOXBEG) THEN
       TZFIELD%CSTDNAME   = ''
-      TZFIELD%CUNITS     = 'ppp' !PW: TODO: not sure (depends if LINOX or LINOXT)
+      TZFIELD%CUNITS     = 'ppv' !PW: TODO: not sure (depends if LINOX or LINOXT)
       TZFIELD%CDIR       = 'XY'
       TZFIELD%NGRID      = 1
       TZFIELD%NTYPE      = TYPEREAL
diff --git a/src/MNH/write_lbn.f90 b/src/MNH/write_lbn.f90
index 4b612a21e..1051579a1 100644
--- a/src/MNH/write_lbn.f90
+++ b/src/MNH/write_lbn.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1998-2021 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1998-2022 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.
@@ -473,7 +473,7 @@ IF (NSV >=1) THEN
     END IF
     !
     TZFIELD%CSTDNAME   = ''
-    TZFIELD%CUNITS     = 'ppp'
+    TZFIELD%CUNITS     = 'ppv'
     TZFIELD%CDIR       = ''
     TZFIELD%NGRID      = 1
     TZFIELD%NTYPE      = TYPEREAL
@@ -610,7 +610,7 @@ IF (NSV >=1) THEN
     END IF
     !
     TZFIELD%CSTDNAME   = ''
-    TZFIELD%CUNITS     = 'ppp'
+    TZFIELD%CUNITS     = 'ppv'
     TZFIELD%CDIR       = ''
     TZFIELD%NGRID      = 1
     TZFIELD%NTYPE      = TYPEREAL
@@ -699,7 +699,7 @@ IF (NSV >=1) THEN
     END IF
     !
     TZFIELD%CSTDNAME   = ''
-    TZFIELD%CUNITS     = 'ppp'
+    TZFIELD%CUNITS     = 'ppv'
     TZFIELD%CDIR       = ''
     TZFIELD%NGRID      = 1
     TZFIELD%NTYPE      = TYPEREAL
diff --git a/src/MNH/write_lfifm1_for_diag_supp.f90 b/src/MNH/write_lfifm1_for_diag_supp.f90
index f24f10f5b..72c472fc4 100644
--- a/src/MNH/write_lfifm1_for_diag_supp.f90
+++ b/src/MNH/write_lfifm1_for_diag_supp.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2000-2021 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2000-2022 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.
@@ -1579,7 +1579,7 @@ IF (NEQ_BUDGET>0) THEN
   TZFIELD%CDIR       = 'XY'
   TZFIELD%NGRID      = 1
   !
-  TZFIELD%CUNITS     = 'ppp s-1'
+  TZFIELD%CUNITS     = 'ppv s-1'
   TZFIELD%NTYPE      = TYPEREAL
   TZFIELD%NDIMS      = 4
   TZFIELD%LTIMEDEP   = .TRUE.
@@ -1607,7 +1607,7 @@ END IF
 ! chemical prod/loss terms
 IF (NEQ_PLT>0) THEN
   TZFIELD%CSTDNAME   = ''
-  TZFIELD%CUNITS     = 'ppp s-1'
+  TZFIELD%CUNITS     = 'ppv s-1'
   TZFIELD%CDIR       = 'XY'
   TZFIELD%NGRID      = 1
   TZFIELD%NTYPE      = TYPEREAL
diff --git a/src/MNH/write_lfin.f90 b/src/MNH/write_lfin.f90
index 3324cac3b..cd875dd96 100644
--- a/src/MNH/write_lfin.f90
+++ b/src/MNH/write_lfin.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1994-2021 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1994-2022 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.
@@ -1225,7 +1225,7 @@ IF (NSV >=1) THEN
     DO JSV = NSV_CHEMBEG,NSV_CHEMEND
       TZFIELD%CMNHNAME   = TRIM(UPCASE(CNAMES(JSV-NSV_CHEMBEG+1)))//'T'
       TZFIELD%CLONGNAME  = TRIM(TZFIELD%CMNHNAME)
-      TZFIELD%CUNITS     = 'ppp'
+      TZFIELD%CUNITS     = 'ppv'
       WRITE(TZFIELD%CCOMMENT,'(A6,A3,I3.3)')'X_Y_Z_','SVT',JSV
       CALL IO_Field_write(TPFILE,TZFIELD,XSVT(:,:,:,JSV))
       !
@@ -1236,7 +1236,7 @@ IF (NSV >=1) THEN
       DO JSV = NSV_CHICBEG,NSV_CHICEND
         TZFIELD%CMNHNAME   = TRIM(UPCASE(CICNAMES(JSV-NSV_CHICBEG+1)))//'T'
         TZFIELD%CLONGNAME  = TRIM(TZFIELD%CMNHNAME)
-        TZFIELD%CUNITS     = 'ppp'
+        TZFIELD%CUNITS     = 'ppv'
         WRITE(TZFIELD%CCOMMENT,'(A6,A3,I3.3)')'X_Y_Z_','SVT',JSV
         CALL IO_Field_write(TPFILE,TZFIELD,XSVT(:,:,:,JSV))
         !
@@ -1283,7 +1283,7 @@ IF (NSV >=1) THEN
     ENDIF
   ELSE IF (LCH_CONV_LINOX) THEN
     TZFIELD%CSTDNAME   = ''
-    TZFIELD%CUNITS     = 'ppp'
+    TZFIELD%CUNITS     = 'ppv'
     TZFIELD%CDIR       = 'XY'
     TZFIELD%NGRID      = 1
     TZFIELD%NTYPE      = TYPEREAL
@@ -1306,7 +1306,7 @@ IF (NSV >=1) THEN
       CALL CH_AER_REALLFI_n(XSVT(:,:,:,NSV_AERBEG:NSV_AEREND),XSVT(:,:,:,NSV_CHEMBEG-1+JP_CH_CO),  XRHODREF)
     IF (NSV_AEREND>=NSV_AERBEG) THEN
       TZFIELD%CSTDNAME   = ''
-      TZFIELD%CUNITS     = 'ppp'
+      TZFIELD%CUNITS     = 'ppv'
       TZFIELD%CDIR       = 'XY'
       TZFIELD%NGRID      = 1
       TZFIELD%NTYPE      = TYPEREAL
@@ -1325,7 +1325,7 @@ IF (NSV >=1) THEN
     END IF
     IF (LDEPOS_AER(IMI)) THEN
       TZFIELD%CSTDNAME   = ''
-      TZFIELD%CUNITS     = 'ppp'
+      TZFIELD%CUNITS     = 'ppv'
       TZFIELD%CDIR       = 'XY'
       TZFIELD%NGRID      = 1
       TZFIELD%NTYPE      = TYPEREAL
@@ -1352,7 +1352,7 @@ IF (NSV >=1) THEN
     !At this point, we have the tracer array in order of importance, i.e.
     !if mode 2 is most important it will occupy place 1-3 of XSVT  
     TZFIELD%CSTDNAME   = ''
-    TZFIELD%CUNITS     = 'ppp'
+    TZFIELD%CUNITS     = 'ppv'
     TZFIELD%CDIR       = 'XY'
     TZFIELD%NGRID      = 1
     TZFIELD%NTYPE      = TYPEREAL
@@ -1372,7 +1372,7 @@ IF (NSV >=1) THEN
 
     IF (LDEPOS_DST(IMI)) THEN
       TZFIELD%CSTDNAME   = ''
-      TZFIELD%CUNITS     = 'ppp'
+      TZFIELD%CUNITS     = 'ppv'
       TZFIELD%CDIR       = 'XY'
       TZFIELD%NGRID      = 1
       TZFIELD%NTYPE      = TYPEREAL
@@ -1399,7 +1399,7 @@ IF (NSV >=1) THEN
     !At this point, we have the tracer array in order of importance, i.e.
     !if mode 2 is most important it will occupy place 1-3 of XSVT  
     TZFIELD%CSTDNAME   = ''
-    TZFIELD%CUNITS     = 'ppp'
+    TZFIELD%CUNITS     = 'ppv'
     TZFIELD%CDIR       = 'XY'
     TZFIELD%NGRID      = 1
     TZFIELD%NTYPE      = TYPEREAL
@@ -1419,7 +1419,7 @@ IF (NSV >=1) THEN
 
     IF (LDEPOS_SLT(IMI)) THEN        
       TZFIELD%CSTDNAME   = ''
-      TZFIELD%CUNITS     = 'ppp'
+      TZFIELD%CUNITS     = 'ppv'
       TZFIELD%CDIR       = 'XY'
       TZFIELD%NGRID      = 1
       TZFIELD%NTYPE      = TYPEREAL
diff --git a/src/MNH/write_ts1d.f90 b/src/MNH/write_ts1d.f90
index 440d7303f..4ffad8b5f 100644
--- a/src/MNH/write_ts1d.f90
+++ b/src/MNH/write_ts1d.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1995-2020 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1995-2022 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.
@@ -375,7 +375,7 @@ DO JN=1,NBPROF
     DO JL = 1, NSV
       IF (JL>=NSV_CHEMBEG .AND. JL<=NSV_CHEMEND) THEN
         DO JK = NKMAX + JPVEXT , JPVEXT + 1, -1
-        ! convert ppp to ppt
+        ! convert ppv to ppt
           CALL WRITECLIP ( XSVT(IINDEX,JINDEX,JK,JL) * 1E12 )
         ENDDO
       ELSE
-- 
GitLab