Skip to content

Commit

Permalink
small bug fixes
Browse files Browse the repository at this point in the history
  • Loading branch information
avaldebe committed Feb 4, 2020
1 parent 60ab2f9 commit 83e1d95
Show file tree
Hide file tree
Showing 7 changed files with 40 additions and 21 deletions.
6 changes: 4 additions & 2 deletions ExternalBICs_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -121,11 +121,13 @@ subroutine set_extbic_id(idate)
EXTERNAL_BIC_VERSION='IFS_MOZ_fkya'
case(2014030100:2014091723) ! 2014-03-01 00:00 to 2014-09-17 23:00 (avail. 2012-09-04)
EXTERNAL_BIC_VERSION='IFS_MOZ_fnyp'
case(2014091800:) ! from 2014-09-18 00:00
case(2014091800:2019120123) ! 2014-09-18 00:00 to 2019-12-31 23:00
EXTERNAL_BIC_VERSION='IFS_CMP_g4e2'
case(2020010100:) ! from 2020-01-01 00:00
EXTERNAL_BIC_VERSION='IFS_CMP_46r1'
end select
BC_DAYS=5 ! if BC file is not found, look for 1..5-day old files
case("IFS_MOZ_f7kn","IFS_MOZ_fkya","IFS_MOZ_fnyp","IFS_CMP_g4e2")
case("IFS_MOZ_f7kn","IFS_MOZ_fkya","IFS_MOZ_fnyp","IFS_CMP_g4e2","IFS_CMP_46r1")
BC_DAYS=5 ! explicit MACC_ENS BC mapping version
case("MACC_EVA","REANALYSIS") ! GRG & AER
select case (idate(1))
Expand Down
16 changes: 9 additions & 7 deletions GasParticleCoeffs_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -83,7 +83,7 @@ module GasParticleCoeffs_mod
!OLD DH2O = 21.0e-6 &! comp old m2/s at STP, Massman

integer, public, parameter ::&
NDRYDEP_GASES = 14+66 &! no. of gases in Wesely tables, DDdefs below
NDRYDEP_GASES = 14+67 &! no. of gases in Wesely tables, DDdefs below
,NDRYDEP_AERO = 14 &! no. of particles in DDdefs below
,NDRYDEP_DEF = NDRYDEP_GASES + NDRYDEP_AERO ! gases + aerosol defs
!mafor ,NDRYDEP_DEF = 17 ! gases + aerosol defs ! MSK 26.01.2015 start
Expand Down Expand Up @@ -172,11 +172,11 @@ module GasParticleCoeffs_mod
,DD_t( 'HO2NO2 ',DH2O/2.1, 2.1, 6.0E4, 9999, 1.0E+04, 1.0, 0., -1,-1,-1,-1)&
,DD_t( 'C3H7OOH',DH2O/2.7, 2.7, 8.3E+01, 9999, 1.0E+04, 0.2, 0., -1,-1,-1,-1)&
,DD_t( 'ACETOL', DH2O/2.6, 2.6, 8.0e3, 9999, 1.0E+04, 0.05, 0.,-1,-1,-1,-1)&
,DD_t( 'MDNO3OH', DH2O/3.7, 3.7, 5.0e4, 9999, 1.0E+04, 0.3, 0.,-1,-1,-1,-1)& ! rather low soluble (H* ca 0.7 - 1.7e4 M/atm) organic nitrates (mixed group)
,DD_t( 'C5DICARB', DH2O/3.1, 3.1, 6.E+05, 9999, 1.0E+04, 0.05, 0.,-1,-1,-1,-1)& ! perhaps f=0.1?
,DD_t( 'MDNO3OH', DH2O/3.7, 3.7, 5.0e4, 9999, 1.0E+04, 0.3, 0.,-1,-1,-1,-1)& ! intermediate solubility (H* ca 4 - 8e4 M/atm) organic nitrates (mixed group)
,DD_t( 'C5DICARB', DH2O/3.1, 3.1, 6.E+05, 9999, 1.0E+04, 0.05, 0.,-1,-1,-1,-1)& ! perhaps f=0.1? C5DICARB should probably be combined with DICARB!
,DD_t( 'MDSOLOOH',DH2O/3.3 , 3.3, 1.1E+05, 9999, 1.0E+04, 0.2, 0., -1,-1,-1,-1)& ! from CRI version
,DD_t( 'GLYOX', DH2O/2.1, 2.1, 3.0e5, 9999, 1.0E+04, 0., 0.,-1,-1,-1,-1)& !
,DD_t( 'DICARB', DH2O/3.0, 3.0, 2.3e5, 9999, 1.0E+04, 0., 0., -1,-1,-1,-1)& ! DICARB - mixture of C4 and C5 dicarbonyls + UCARB12 (which is not a dicarbonyl but with similar estimated D and H*
,DD_t( 'DICARB', DH2O/3.0, 3.0, 2.e5, 9999, 1.0E+04, 0.05, 0., -1,-1,-1,-1)& ! DICARB - mixture of C4 and C5 dicarbonyls + UCARB12 (which is not a dicarbonyl but with similar estimated D and H*
,DD_t( 'MEOOH', DH2O/1.9, 1.9, 3.0e2, 9999, 1.0E+04, 0.2, 0.,-1,-1,-1,-1)& ! Methyl hydroperoxide - maybe reactivity should be higher!
,DD_t( 'SHISOLOOH', DH2O/2.9, 2.9, 1.2e6, 9999, 1.0E+04, 0.2, 0.,-1,-1,-1,-1)& ! Small (C2-C5) High solubility (estimated H* ca 1 - 1.4e6 M/atm) multifunctional organic hydroperoxides
,DD_t( 'LHISOLOOH', DH2O/4.3, 4.3, 1.6e6, 9999, 1.0E+04, 0.2, 0.,-1,-1,-1,-1)& ! Large (C7-C10) High solubility (estimated H* ca 1.6e6 M/atm) multifunctional organic hydroperoxides
Expand Down Expand Up @@ -205,7 +205,7 @@ module GasParticleCoeffs_mod
,DD_t( 'HYPERACET', DH2O/2.8, 2.8, 3.1e4, 9999, 1.0E+04, 0.2, 0.,-1,-1,-1,-1)& !
,DD_t( 'VLSOLNO3', DH2O/3.2, 3.2, 1.0e0, 9999, 1.0E+04, 0.3, 0.,-1,-1,-1,-1)& ! very low solubility (H* < ca 1e3 M/atm) organic nitrates (mixed group)
,DD_t( 'HOCH2CHO', DH2O/2.2, 2.2, 4.1e4, 9999, 1.0E+04, 0., 0.,-1,-1,-1,-1)& !glycolaldehyde
,DD_t( 'CARB12', DH2O/3.1, 3.1, 3.4e4, 9999, 1.0E+04, 0., 0.,-1,-1,-1,-1)& ! moderately soluble carbonyls (mixed) with estimated H* ca 3.0 - 3.8E4 M/atm
,DD_t( 'CARB12', DH2O/3.1, 3.1, 3.4e4, 9999, 1.0E+04, 0.05, 0.,-1,-1,-1,-1)& ! moderately soluble carbonyls (mixed) with estimated H* ca 3.0 - 3.8E4 M/atm
,DD_t( 'CH3CO2H', DH2O/2.0, 2.0, 7.0e5, 9999, 1.0E+04, 0, 0.,-1,-1,-1,-1)& !acetic acid
,DD_t( 'HCOCO3H', DH2O/2.6, 2.6, 3.2e6, 9999, 1.0E+04, 0.2, 0.,-1,-1,-1,-1)&
,DD_t( 'CH3NO3', DH2O/2.3, 2.3, 2.0e0, 9999, 1.0E+04, 0.3, 0.,-1,-1,-1,-1)& !methyl nitrate (and ethyl nitrate)
Expand All @@ -221,7 +221,8 @@ module GasParticleCoeffs_mod
,DD_t( 'C10NO3OOH', DH2O/4.8, 4.8, 2.2e4, 9999, 1.0E+04, 0.3, 0.,-1,-1,-1,-1)& ! moderately soluble C10-organic nitrates with a hydro peroxide group
,DD_t( 'C10PAN2', DH2O/4.8, 4.8, 5.2e3, 9999, 1.0E+04, 0.2, 0.,-1,-1,-1,-1)&
,DD_t( 'C96OOH', DH2O/4.3, 4.3, 9.0e4, 9999, 1.0E+04, 0.2, 0.,-1,-1,-1,-1)&
,DD_t( 'CO23C4CHO', DH2O/3.2, 3.2, 5.5e6, 9999, 1.0E+04, 0, 0.,-1,-1,-1,-1)&
,DD_t( 'CO23C4CHO', DH2O/3.2, 3.2, 5.5e6, 9999, 1.0E+04, 0, 0.,-1,-1,-1,-1)& ! perhaps combine and replace this by TRICARB?
,DD_t( 'TRICARB', DH2O/3., 3., 1.e6, 9999, 1.0E+04, 0.05, 0.,-1,-1,-1,-1)&
,DD_t( 'NOPINAOOH', DH2O/4.2, 4.2, 1.8e5, 9999, 1.0E+04, 0.2, 0.,-1,-1,-1,-1)&
,DD_t( 'ANHY', DH2O/2.9, 2.9, 2.5e2, 9999, 1.0E+04, 1.0, 0.,-1,-1,-1,-1)& ! Maleic anhydride (2,5-furandione)
,DD_t( 'MACROH', DH2O/3.1, 3.1, 1.5e3, 9999, 1.0E+04, 0.05, 0.,-1,-1,-1,-1)&
Expand Down Expand Up @@ -273,7 +274,7 @@ module GasParticleCoeffs_mod
real :: W_sub
end type WD_t

integer, parameter :: NWETDEP_DEF = 22+1
integer, parameter :: NWETDEP_DEF = 22+2
type(WD_t), public, dimension(NWETDEP_DEF),parameter :: WDdefs = [ &
WD_t('SO2' , 0.3, 0.15) &! Berge+Jakobsen
,WD_t('SO4' , 1.0, EFF25) &! Berge+Jakobsen
Expand All @@ -298,6 +299,7 @@ module GasParticleCoeffs_mod
,WD_t('0p6' , 0.6, 0.18) &!
,WD_t('0p7' , 0.7, 0.21) &!
,WD_t('0p8' , 0.8, 0.24) &!
,WD_t('1p1' , 1.1, 0.33) &!
,WD_t('1p2' , 1.2, 0.36) &!
,WD_t('1p3' , 1.3, 0.39) &!
]
Expand Down
13 changes: 8 additions & 5 deletions GridValues_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -109,7 +109,7 @@ Module GridValues_mod
public :: extendarea_N ! returns array which includes neighbours from other subdomains
public :: set_EuropeanAndGlobal_Config
public :: remake_vertical_levels_interpolation_coeff
public :: Meteo_Get_KMAXMET
public :: Read_KMAX

private :: Alloc_GridFields
private :: GetFullDomainSize
Expand Down Expand Up @@ -1976,7 +1976,7 @@ subroutine make_vertical_levels_interpolation_coeff

end subroutine make_vertical_levels_interpolation_coeff

subroutine Meteo_Get_KMAXMET(filename, KMAX, ncfileID_in)
subroutine Read_KMAX(filename, KMAX, ncfileID_in)

character(len=*), intent(in) :: filename
integer, intent(out) :: KMAX
Expand All @@ -1998,16 +1998,19 @@ subroutine Meteo_Get_KMAXMET(filename, KMAX, ncfileID_in)
status=nf90_inq_dimid(ncid=ncFileID, name="lev", dimID=kdimID)!hybrid coordinates
if(status/=nf90_noerr) then
status=nf90_inq_dimid(ncid=ncFileID, name="hybrid", dimID=kdimID)!hybrid coordinates
if(status/=nf90_noerr) then ! WRF format
if(status/=nf90_noerr) then ! nesting cwf-cifs_XXX_raqbcformat
status=nf90_inq_dimid(ncid=ncFileID, name="level", dimID=kdimID)
if(status/=nf90_noerr) then ! WRF format
call check(nf90_inq_dimid(ncid=ncFileID, name="bottom_top", dimID=kdimID))
end if
end if
end if
end if
call check(nf90_inquire_dimension(ncid=ncFileID,dimID=kdimID,len=KMAX))

if(.not.present(ncfileID_in))call check(nf90_close(ncFileID))

end subroutine Meteo_Get_KMAXMET
end subroutine Read_KMAX

subroutine remake_vertical_levels_interpolation_coeff(filename)
! make again interpolation coefficients to convert the levels defined in meteo
Expand All @@ -2033,7 +2036,7 @@ subroutine remake_vertical_levels_interpolation_coeff(filename)
deallocate(A_bnd_met,B_bnd_met)
end if

call Meteo_Get_KMAXMET(filename, KMAX_MET, ncfileID)
call Read_KMAX(filename, KMAX_MET, ncfileID)

status=nf90_inq_varid(ncid=ncFileID, name="k", varID=varID)
if(status/=nf90_noerr)then
Expand Down
4 changes: 2 additions & 2 deletions Met_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -92,7 +92,7 @@ module Met_mod
,debug_proc, debug_li, debug_lj, A_mid, B_mid &
,Eta_bnd,Eta_mid,dA,dB,A_mid,B_mid,A_bnd,B_bnd &
,KMAX_MET,External_Levels_Def,k1_met,k2_met,x_k1_met,rot_angle&
,Meteo_Get_KMAXMET,remake_vertical_levels_interpolation_coeff
,Read_KMAX,remake_vertical_levels_interpolation_coeff

use Io_mod , only: ios, datewrite, PrintLog, IO_LOG
use Landuse_mod, only: water_fraction, water_frac_set, &
Expand Down Expand Up @@ -403,7 +403,7 @@ subroutine MeteoRead()
meteoname = date2string(meteo,next_inptime,mode='YMDH')

!check if the number of vertical levels has changed
call Meteo_Get_KMAXMET(meteoname,kmax)
call Read_KMAX(meteoname,kmax)

if(kmax/=KMAX_MET)then
if(me==0)write(*,*)'WARNING: number of vertical levels in meteo file has changed from ',KMAX_MET,' to ', KMAX
Expand Down
17 changes: 15 additions & 2 deletions Nest_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -71,7 +71,8 @@ module Nest_mod
use Chemfields_mod, only: xn_adv ! emep model concs.
use ChemDims_mod, only: NSPEC_ADV, NSPEC_SHL
use ChemSpecs_mod, only: species_adv
use GridValues_mod, only: A_mid,B_mid, glon,glat, i_fdom,j_fdom, RestrictDomain
use GridValues_mod, only: A_mid,B_mid, glon, glat, i_fdom, j_fdom, &
RestrictDomain, Read_KMAX
use Io_mod, only: open_file,IO_TMP,PrintLog
use InterpolationRoutines_mod, only : grid2grid_coeff,point2grid_coeff
use MetFields_mod, only: roa
Expand Down Expand Up @@ -1425,7 +1426,8 @@ subroutine read_newdata_LATERAL(ndays_indate)
character (len=80) ::units
real :: scale_factor,add_offset
logical :: time_exists,divbyroa

integer ::KMAX_nest

KMAX_BC=KMAX_MID
if(mydebug)write(*,*)'Nest: read_newdata_LATERAL, first?', first_call
if(first_call)then
Expand Down Expand Up @@ -1480,6 +1482,17 @@ subroutine read_newdata_LATERAL(ndays_indate)
rtime_saved(2)=-99.0!just to put a value
if(mydebug)write(*,*)'Nest: end initializations 2D'

else
!not first call
call Read_KMAX(filename_read_BC, KMAX_nest)
if(KMAX_nest /= KMAX_ext_BC)then
if(MasterProc)write(*,*)'WARNING: the number of vertical levels has changed in NEST_BC file!'
if(MasterProc)write(*,*)'WARNING: reinitializing nesting'
call init_nest(ndays_indate,filename_read_BC,NEST_native_grid_BC,&
IIij,JJij,Weight,k1_ext,k2_ext,weight_k1,weight_k2,&
N_ext_BC,KMAX_ext_BC,GIMAX_ext,GJMAX_ext)

endif
end if

rtime_saved(1)=rtime_saved(2) ! put old values in 1
Expand Down
2 changes: 1 addition & 1 deletion NetCDF_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -3515,7 +3515,7 @@ subroutine ReadField_CDF(fileName,varname,Rvar,nstart,kstart,kend,interpol, &
if(ig<0.5 .or. ig>dims(1))then
!try to come from the other side
!check first that it covers all latitudes
if(abs(Rlon(dims(1))-Rlon(1))<0.1+1/dRloni)then
if(abs(Rlon(dims(1))-Rlon(1))<0.1+1/dRloni .or. abs(Rlon(dims(1))-Rlon(1)-360.0)<0.1+1/dRloni)then
if(ig<0.5)ig=ig+dims(1)
if(ig>dims(1))ig=ig-dims(1)
endif
Expand Down
3 changes: 1 addition & 2 deletions Pollen_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -54,7 +54,7 @@ module Pollen_mod
dt=>dt_advec, &
outdate=>NEST_OUTDATE,OUTDATE_NDUMP=>NEST_OUTDATE_NDUMP,&
out_DOMAIN=>NEST_out_DOMAIN,&
MODE_READ=>NEST_MODE_READ,MODE_SAVE=>NEST_MODE_SAVE,&
MODE_READ=>NEST_MODE_READ,&
template_read_IC=>NEST_template_read_3D,&
template_write_IC=>NEST_template_write
use MPI_Groups_mod, only: MPI_INTEGER,MPI_LOGICAL,MPI_COMM_CALC,&
Expand Down Expand Up @@ -946,7 +946,6 @@ subroutine pollen_dump()
type(Deriv) :: def1
real,allocatable, dimension(:,:,:) :: data ! Data arrays

if(MODE_SAVE/='OUTDATE') return
if(.not.checkdates(daynumber,"pollen")) return
if(.not.compare_date(OUTDATE_NDUMP,current_date,&
outdate(:OUTDATE_NDUMP),wildcard=-1))return
Expand Down

0 comments on commit 83e1d95

Please sign in to comment.