From ce5c854c3d9aa9684022a485878d68a1a4b6470a Mon Sep 17 00:00:00 2001 From: Philippe WAUTELET <philippe.wautelet@aero.obs-mip.fr> Date: Mon, 28 May 2018 10:11:37 +0200 Subject: [PATCH] Philippe 28/05/2018: bug corrections: truncated integer divisions --- src/MNH/aer_effic.f90 | 5 +++-- src/MNH/aer_effic3D.f90 | 5 +++-- src/MNH/aero_effic3D.f90 | 5 +++-- src/MNH/blowsnow_velgrav.f90 | 3 ++- src/MNH/lima_precip_scavenging.f90 | 3 ++- src/MNH/mnh2lpdm_ech.f90 | 3 ++- src/MNH/shallow_mf.f90 | 7 ++++--- src/MNH/subl_blowsnow.f90 | 5 ++++- src/SURFEX/blowsnw_velgrav1d.f90 | 11 ++++++++++- 9 files changed, 33 insertions(+), 14 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/blowsnow_velgrav.f90 b/src/MNH/blowsnow_velgrav.f90 index 7909543a6..7c4d84637 100644 --- a/src/MNH/blowsnow_velgrav.f90 +++ b/src/MNH/blowsnow_velgrav.f90 @@ -52,6 +52,7 @@ END MODULE MODI_BLOWSNOW_VELGRAV !! !! MODIFICATIONS !! ------------- +!! Philippe Wautelet 28/05/2018: corrected truncated integer division (1*10**(-6) -> 1E-6) !! !! !----------------------------------------------------------------- @@ -249,7 +250,7 @@ DO JI=1,SIZE(PSVT,1) ZSUM_VEL_M0=0. ZSUM_VEL_M3=0. DO II=1,NMAX(JI,JJ,JK) - ZR = 1*10**(-6)+(II-0.5)*ZDELTAR + ZR = 1E-6+(II-0.5)*ZDELTAR ZVEL_CARRIER = - ZAA(JI,JJ,JK)/ZR+((ZAA(JI,JJ,JK)/ZR)**2.+ZBB(JI,JJ,JK)*ZR)**0.5 ZW_M0=ZR**(XALPHA_SNOW-1)*exp(-ZR/ZBETA(JI,JJ,JK))/(ZBETA(JI,JJ,JK))**XALPHA_SNOW*ZGAM 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 4c5c24ae3..e7b334e84 100644 --- a/src/MNH/mnh2lpdm_ech.f90 +++ b/src/MNH/mnh2lpdm_ech.f90 @@ -13,6 +13,7 @@ ! Creation : 07.01.2009 ! Modifications: ! Philippe Wautelet: 05/2016-04/2018: new data structures and calls for I/O +! Philippe Wautelet 28/05/2018: corrected truncated integer division (1/3 -> 1./3.) !----------------------------------------------------------------------- ! !* 0. DECLARATIONS. @@ -269,7 +270,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 0cf0767da..049954b62 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 @@ -468,8 +469,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) ! diff --git a/src/MNH/subl_blowsnow.f90 b/src/MNH/subl_blowsnow.f90 index 4046b46b7..015169c26 100644 --- a/src/MNH/subl_blowsnow.f90 +++ b/src/MNH/subl_blowsnow.f90 @@ -43,6 +43,9 @@ END MODULE MODI_SUBL_BLOWSNOW SUBROUTINE SUBL_BLOWSNOW(PZZ, PRHODJ , PRHODREF, PEXNREF , PPABST, & PTHT, PRVT, PRCT, PRRT, PRIT, PRST, PRGT, PSVT, & PTHS, PRVS, PSVS,PSNWSUBL3D,PVGK) +!! MODIFICATIONS +!! ------------- +!! Philippe Wautelet 28/05/2018: corrected truncated integer division (1*10**(-6) -> 1E-6) USE MODD_PARAMETERS USE MODD_CST @@ -453,7 +456,7 @@ DO JL=1,IMICRO ZSUM_SUBL=0. ZUSI(JL) = MIN(ZUSI(JL), 0.) !Only the undersaturation over ice is considered. DO JN=1,NMAX(JL) - ZR = 1*10**(-6)+(JN-0.5)*ZDELTAR + ZR = 1E-6+(JN-0.5)*ZDELTAR ! Carrier settling velocity ZVEL_CARRIER = - ZAA(JL)/ZR+((ZAA(JL)/ZR)**2+ZBB(JL)*ZR)**0.5 ! Weight of the corresponding bin following the gamma distribution diff --git a/src/SURFEX/blowsnw_velgrav1d.f90 b/src/SURFEX/blowsnw_velgrav1d.f90 index 27f1ba54a..d5bc2a19d 100644 --- a/src/SURFEX/blowsnw_velgrav1d.f90 +++ b/src/SURFEX/blowsnw_velgrav1d.f90 @@ -1,3 +1,8 @@ +!SFX_LIC Copyright 1994-2018 CNRS, Meteo-France and Universite Paul Sabatier +!SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence +!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt +!SFX_LIC for details. version 1. +!----------------------------------------------------------------- !! ####################################### SUBROUTINE BLOWSNW_VELGRAV1D(PBETA, PRG, PTA, PRHODREF,PPABST,PVGK) @@ -26,6 +31,10 @@ SUBROUTINE BLOWSNW_VELGRAV1D(PBETA, PRG, PTA, PRHODREF,PPABST,PVGK) !! ------ !! V. Vionnet (CNRM/GMME/MOSAYC) !! +!! MODIFICATIONS +!! ------------- +!! Philippe Wautelet 28/05/2018: corrected truncated integer division (1*10**(-6) -> 1E-6) +!! !! NB : this routine is similar to the routine implemented in Meso-NH (blowsnow_velgrav.f90) ! !! @@ -159,7 +168,7 @@ DO JI=1,SIZE(PTA,1) ZSUM_VEL_M0=0. ZSUM_VEL_M3=0. DO II=1,NMAX(JI,JK) - ZR = 1*10**(-6)+(II-0.5)*ZDELTAR + ZR = 1E-6+(II-0.5)*ZDELTAR ZVEL_CARRIER = - ZAA(JI,JK)/ZR+((ZAA(JI,JK)/ZR)**2.+ZBB(JI)*ZR)**0.5 ZW_M0=ZR**(XEMIALPHA_SNW-1)*exp(-ZR/PBETA(JI,JK))/(PBETA(JI,JK)**XEMIALPHA_SNW*ZGAM) -- GitLab