From 7952a000c9210dd24af752eed591f686b342e11d Mon Sep 17 00:00:00 2001
From: Philippe WAUTELET <philippe.wautelet@aero.obs-mip.fr>
Date: Mon, 28 May 2018 10:16:32 +0200
Subject: [PATCH] Philippe 28/05/2018: bug corrections: truncated integer
 divisions

(cherry picked from commit ce5c854c3d9aa9684022a485878d68a1a4b6470a)
---
 src/MNH/aer_effic.f90              | 5 +++--
 src/MNH/aer_effic3D.f90            | 5 +++--
 src/MNH/aero_effic3D.f90           | 5 +++--
 src/MNH/lima_precip_scavenging.f90 | 3 ++-
 src/MNH/mnh2lpdm_ech.f90           | 4 +++-
 src/MNH/shallow_mf.f90             | 7 ++++---
 6 files changed, 18 insertions(+), 11 deletions(-)

diff --git a/src/MNH/aer_effic.f90 b/src/MNH/aer_effic.f90
index e183009da..27064451b 100644
--- a/src/MNH/aer_effic.f90
+++ b/src/MNH/aer_effic.f90
@@ -1,4 +1,4 @@
-!ORILAM_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
+!ORILAM_LIC Copyright 1994-2018 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.
@@ -72,6 +72,7 @@ SUBROUTINE AER_EFFIC(PRG,PVGG,      & !aerosol radius/fall speed (m/s)
 !!
 !!   MODIFICATIONS
 !!    -------------
+!!  Philippe Wautelet 28/05/2018: corrected truncated integer division (1/12 -> 1./12.)
 !!
 !-----------------------------------------------------------------
 !       
@@ -162,7 +163,7 @@ ZREY(:)=ZRR(:)*ZVR(:)*PRHODREF(:)/PMU(:)
 ZREY(:)= MAX(ZREY(:), 1E-2)
 
 !S Star
-ZSTA(:)=(1.2+1/12*LOG(1+ZREY(:)))/(1+LOG(1+ZREY(:)))
+ZSTA(:)=(1.2+1./12.*LOG(1.+ZREY(:)))/(1.+LOG(1.+ZREY(:)))
 PEFC(:,:)=0.0
 DO JI=1,KMODE
 !
diff --git a/src/MNH/aer_effic3D.f90 b/src/MNH/aer_effic3D.f90
index 1478f014e..c55a51929 100644
--- a/src/MNH/aer_effic3D.f90
+++ b/src/MNH/aer_effic3D.f90
@@ -1,4 +1,4 @@
-!ORILAM_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
+!ORILAM_LIC Copyright 1994-2018 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.
@@ -76,6 +76,7 @@ SUBROUTINE AER_EFFIC3D(PRG,PVGG,    & !aerosol radius/fall speed (m/s)
 !!
 !!   MODIFICATIONS
 !!    -------------
+!!  Philippe Wautelet 28/05/2018: corrected truncated integer division (1/12 -> 1./12.)
 !!
 !-----------------------------------------------------------------
 !       
@@ -176,7 +177,7 @@ ZREY(:,:,:)= MAX(ZREY(:,:,:), 1E-2)
 
 
 !S Star
-ZSTA(:,:,:)=(1.2+(1/12)*LOG(1+ZREY(:,:,:)))/(1+LOG(1+ZREY(:,:,:)))
+ZSTA(:,:,:)=(1.2+(1./12.)*LOG(1.+ZREY(:,:,:)))/(1.+LOG(1.+ZREY(:,:,:)))
 PEFFIC(:,:,:,:)=0.0
 DO JI=1,NMODE_DST
 !
diff --git a/src/MNH/aero_effic3D.f90 b/src/MNH/aero_effic3D.f90
index 8a5d19b86..7dc28b471 100644
--- a/src/MNH/aero_effic3D.f90
+++ b/src/MNH/aero_effic3D.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1994-2018 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.
@@ -76,6 +76,7 @@ SUBROUTINE AERO_EFFIC3D(PRG,PVGG,    & !aerosol radius/fall speed (m/s)
 !!
 !!   MODIFICATIONS
 !!    -------------
+!!  Philippe Wautelet 28/05/2018: corrected truncated integer division (1/12 -> 1./12.)
 !!
 !-----------------------------------------------------------------
 !       
@@ -179,7 +180,7 @@ ZREY(:,:,:)= MAX(ZREY(:,:,:), 1E-2)
 
 
 !S Star
-ZSTA(:,:,:)=(1.2+(1/12)*LOG(1+ZREY(:,:,:)))/(1+LOG(1+ZREY(:,:,:)))
+ZSTA(:,:,:)=(1.2+(1./12.)*LOG(1.+ZREY(:,:,:)))/(1.+LOG(1.+ZREY(:,:,:)))
 
 PEFFIC_AER(:,:,:,:)=0.0
 
diff --git a/src/MNH/lima_precip_scavenging.f90 b/src/MNH/lima_precip_scavenging.f90
index 4daf15b8a..ec318f4c8 100644
--- a/src/MNH/lima_precip_scavenging.f90
+++ b/src/MNH/lima_precip_scavenging.f90
@@ -90,6 +90,7 @@ END MODULE MODI_LIMA_PRECIP_SCAVENGING
 !!    -------------
 !!      Original             ??/??/13 
 !!
+!!  Philippe Wautelet 28/05/2018: corrected truncated integer division (3/2 -> 1.5)
 !-------------------------------------------------------------------------------
 !
 !*                  0.DECLARATIONS          
@@ -289,7 +290,7 @@ WHERE ( GRAIN(:,:,:) )
    ZT_3D(:,:,:)      = PTHT(:,:,:) * ( PPABST(:,:,:)/XP00 )**(XRD/XCPD)
    ZCONCR_3D(:,:,:)  = PCRT(:,:,:) * PRHODREF(:,:,:)                    ![/m3]
    ! Sutherland law for viscosity of air
-   ZVISCA_3D(:,:,:)  = XMUA0*(ZT_3D(:,:,:)/XTREF)**(3/2)*(XTREF+XT_SUTH_A) &
+   ZVISCA_3D(:,:,:)  = XMUA0*(ZT_3D(:,:,:)/XTREF)**1.5*(XTREF+XT_SUTH_A) &
                                                         /(XT_SUTH_A+ZT_3D(:,:,:))
    ! Air mean free path
    ZMFPA_3D(:,:,:)   = XMFPA0*(XP00*ZT_3D(:,:,:))/(PPABST(:,:,:)*XT0SCAV)           
diff --git a/src/MNH/mnh2lpdm_ech.f90 b/src/MNH/mnh2lpdm_ech.f90
index 6655be622..317168168 100644
--- a/src/MNH/mnh2lpdm_ech.f90
+++ b/src/MNH/mnh2lpdm_ech.f90
@@ -10,6 +10,8 @@
 !
 !	Auteur   : Francois Bonnardot, DP/SERV/ENV
 !	Creation : 07.01.2009
+! Modifications:
+!  Philippe Wautelet 28/05/2018: corrected truncated integer division (1/3 -> 1./3.)
 !-----------------------------------------------------------------------
 !
 !*	0.  DECLARATIONS.
@@ -263,7 +265,7 @@ XSSFV(:,:) = XSFV(NSIB:NSIE,NSJB:NSJE)
              DO JK=1,NKMAX
              IF (XSHAUT(JK).LE.XSHMIX(JI,JJ)) THEN
              XSSIGU(JI,JJ,JK)=XSUSTAR(JI,JJ)         &
-                        * (12+0.5*XSHMIX(JI,JJ)/ABS(XSLMO(JI,JJ)))**(1/3)
+                        * (12+0.5*XSHMIX(JI,JJ)/ABS(XSLMO(JI,JJ)))**(1./3.)
              ELSE
              XSSIGU(JI,JJ,JK)=0.001
              ENDIF
diff --git a/src/MNH/shallow_mf.f90 b/src/MNH/shallow_mf.f90
index a294f5859..de563579c 100644
--- a/src/MNH/shallow_mf.f90
+++ b/src/MNH/shallow_mf.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1994-2018 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.
@@ -164,6 +164,7 @@ END MODULE MODI_SHALLOW_MF
 !!      R.Honnert 07/2012 : MF gray zone 
 !!      R.Honnert 10/2016 : SURF=gray zone initilisation + EDKF  
 !!      R.Honnert 10/2016 : Update with Arome
+!!      Philippe Wautelet 28/05/2018: corrected truncated integer division (2/3 -> 2./3.)
 !! --------------------------------------------------------------------------
 !
 !*      0. DECLARATIONS
@@ -463,8 +464,8 @@ ENDIF
       ENDDO
       ZRESOL_NORM=ZRESOL_GRID/ZLUP
       !! P=loi pour MF, on utilise la même loi à chaque fois
-      ZPLAW=(ZRESOL_NORM*ZRESOL_NORM+0.19*ZRESOL_NORM**(2/3))/ &
-      (ZRESOL_NORM*ZRESOL_NORM+0.15*ZRESOL_NORM**(2/3)+0.33)
+      ZPLAW=(ZRESOL_NORM*ZRESOL_NORM+0.19*ZRESOL_NORM**(2./3.))/ &
+      (ZRESOL_NORM*ZRESOL_NORM+0.15*ZRESOL_NORM**(2./3.)+0.33)
       !! reduction des flux a posteriori
       !! MF=P*MF en première approximation, on oublie w'f' (Kgrad) et w'f'resol (nul avec ce flux)
       !  
-- 
GitLab