diff --git a/src/MNH/ini_budget.f90 b/src/MNH/ini_budget.f90 index 22303fd0c1d61b75c6b1142d14a8c7002ecfffa7..a7e3208cd565e1e564ca8c7739ddb5c58b227b06 100644 --- a/src/MNH/ini_budget.f90 +++ b/src/MNH/ini_budget.f90 @@ -8,12 +8,16 @@ !----------------------------------------------------------------- module mode_ini_budget + use mode_msg + implicit none private public :: Budget_preallocate, Ini_budget + integer, parameter :: NSOURCESMAX = 60 !Maximum number of sources in a budget + contains subroutine Budget_preallocate() @@ -24,8 +28,6 @@ use modd_budget, only: nbudgets, tbudgets, NBUDGET_RG, NBUDGET_RH, NBUDGET_SV1 use modd_nsv, only: csvnames, nsv -use mode_msg - integer :: ibudget integer :: jsv @@ -205,6 +207,7 @@ end subroutine Budget_preallocate ! P. Wautelet 11/02/2021: budgets: add missing term SCAV for NSV_LIMA_SCAVMASS budget ! P. Wautelet 02/03/2021: budgets: add terms for blowing snow ! P. Wautelet 04/03/2021: budgets: add terms for drag due to buildings +! P. Wautelet 17/03/2021: choose source terms for budgets with character strings instead of multiple integer variables !------------------------------------------------------------------------------- ! !* 0. DECLARATIONS @@ -250,7 +253,6 @@ use modd_salt, only: lsalt use modd_viscosity, only: lvisc, lvisc_r, lvisc_sv, lvisc_th, lvisc_uvw USE MODE_ll -USE MODE_MSG IMPLICIT NONE ! @@ -306,7 +308,7 @@ CHARACTER (LEN=*), INTENT(IN) :: HCLOUD ! type of microphysical scheme ! real, parameter :: ITOL = 1e-6 -INTEGER :: JI, JJ, JK , JJJ ! loop indices +INTEGER :: JI, JJ ! loop indices INTEGER :: IIMAX_ll, IJMAX_ll ! size of the physical global domain INTEGER :: IIU, IJU ! size along x and y directions ! of the extended subdomain @@ -322,9 +324,6 @@ INTEGER :: IBUDIM3 ! third dimension of t INTEGER :: JSV ! loop indice for the SVs INTEGER :: IINFO_ll ! return status of the interface routine integer :: ibudget -integer :: isourcesmax ! Maximum number of source terms in a budget -integer :: igroup -logical :: gcond logical :: gtmp type(tbusourcedata) :: tzsource ! Used to prepare metadate of source terms @@ -533,9 +532,8 @@ if ( lbu_ru ) then !Allocate all basic source terms (used or not) !The size should be large enough (bigger than necessary is OK) - isourcesmax = 19 - tbudgets(NBUDGET_U)%nsourcesmax = isourcesmax - allocate( tbudgets(NBUDGET_U)%tsources(isourcesmax) ) + tbudgets(NBUDGET_U)%nsourcesmax = NSOURCESMAX + allocate( tbudgets(NBUDGET_U)%tsources(NSOURCESMAX) ) allocate( tbudgets(NBUDGET_U)%xtmpstore(ibudim1, ibudim2, ibudim3) ) @@ -546,102 +544,107 @@ if ( lbu_ru ) then tzsource%cunits = 'm s-1' - gcond = .true. - tzsource%cmnhname = 'INIF' - tzsource%clongname = 'initial state' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'INIF' + tzsource%clongname = 'initial state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_U), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'ENDF' - tzsource%clongname = 'final state' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'ENDF' + tzsource%clongname = 'final state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_U), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'AVEF' - tzsource%clongname = 'averaged state' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .false. ) + tzsource%cmnhname = 'AVEF' + tzsource%clongname = 'averaged state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_U), tzsource, odonotinit = .true., ooverwrite = .false. ) tzsource%cunits = 'm s-2' - gcond = .true. - tzsource%cmnhname = 'ASSE' - tzsource%clongname = 'time filter (Asselin)' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, nasseu ) - - gcond = nmodel > 1 - tzsource%cmnhname = 'NEST' - tzsource%clongname = 'nesting' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, nnestu ) - - gcond = lforcing - tzsource%cmnhname = 'FRC' - tzsource%clongname = 'forcing' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, nfrcu ) - - gcond = onudging - tzsource%cmnhname = 'NUD' - tzsource%clongname = 'nudging' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, nnudu ) - - gcond = .not.l1d .and. .not.lcartesian - tzsource%cmnhname = 'CURV' - tzsource%clongname = 'curvature' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, ncurvu ) - - gcond = lcorio - tzsource%cmnhname = 'COR' - tzsource%clongname = 'Coriolis' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, ncoru ) - - gcond = onumdifu - tzsource%cmnhname = 'DIF' - tzsource%clongname = 'numerical diffusion' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, ndifu ) - - gcond = ohorelax_uvwth .or. ove_relax .or. ove_relax_grd - tzsource%cmnhname = 'REL' - tzsource%clongname = 'relaxation' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, nrelu ) - - gcond = odragtree - tzsource%cmnhname = 'DRAG' - tzsource%clongname = 'drag force' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, ndragu ) - - gcond = ldragbldg - tzsource%cmnhname = 'DRAGB' - tzsource%clongname = 'drag force due to buildings' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, ndragbu ) - - gcond = hturb == 'TKEL' - tzsource%cmnhname = 'VTURB' - tzsource%clongname = 'vertical turbulent diffusion' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, nvturbu ) - - gcond = hturb == 'TKEL' .and. HTURBDIM == '3DIM' - tzsource%cmnhname = 'HTURB' - tzsource%clongname = 'horizontal turbulent diffusion' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, nhturbu ) - - gcond = hsconv == 'EDKF' - tzsource%cmnhname = 'MAFL' - tzsource%clongname = 'mass flux' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, nmaflu ) - - gcond = lvisc .and. lvisc_uvw - tzsource%cmnhname = 'VISC' - tzsource%clongname = 'viscosity' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, nviscu ) - - gcond = .true. - tzsource%cmnhname = 'ADV' - tzsource%clongname = 'advection' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, nadvu ) - - gcond = .true. - tzsource%cmnhname = 'PRES' - tzsource%clongname = 'pressure' - call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, npresu ) + tzsource%cmnhname = 'ASSE' + tzsource%clongname = 'time filter (Asselin)' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_U), tzsource ) + + tzsource%cmnhname = 'NEST' + tzsource%clongname = 'nesting' + tzsource%lavailable = nmodel > 1 + call Budget_source_add( tbudgets(NBUDGET_U), tzsource ) + + tzsource%cmnhname = 'FRC' + tzsource%clongname = 'forcing' + tzsource%lavailable = lforcing + call Budget_source_add( tbudgets(NBUDGET_U), tzsource ) + + tzsource%cmnhname = 'NUD' + tzsource%clongname = 'nudging' + tzsource%lavailable = onudging + call Budget_source_add( tbudgets(NBUDGET_U), tzsource ) + + tzsource%cmnhname = 'CURV' + tzsource%clongname = 'curvature' + tzsource%lavailable = .not.l1d .and. .not.lcartesian + call Budget_source_add( tbudgets(NBUDGET_U), tzsource ) + + tzsource%cmnhname = 'COR' + tzsource%clongname = 'Coriolis' + tzsource%lavailable = lcorio + call Budget_source_add( tbudgets(NBUDGET_U), tzsource ) + + tzsource%cmnhname = 'DIF' + tzsource%clongname = 'numerical diffusion' + tzsource%lavailable = onumdifu + call Budget_source_add( tbudgets(NBUDGET_U), tzsource ) + + tzsource%cmnhname = 'REL' + tzsource%clongname = 'relaxation' + tzsource%lavailable = ohorelax_uvwth .or. ove_relax .or. ove_relax_grd + call Budget_source_add( tbudgets(NBUDGET_U), tzsource ) + + tzsource%cmnhname = 'DRAG' + tzsource%clongname = 'drag force' + tzsource%lavailable = odragtree + call Budget_source_add( tbudgets(NBUDGET_U), tzsource ) + + tzsource%cmnhname = 'DRAGB' + tzsource%clongname = 'drag force due to buildings' + tzsource%lavailable = ldragbldg + call Budget_source_add( tbudgets(NBUDGET_U), tzsource ) + + tzsource%cmnhname = 'VTURB' + tzsource%clongname = 'vertical turbulent diffusion' + tzsource%lavailable = hturb == 'TKEL' + call Budget_source_add( tbudgets(NBUDGET_U), tzsource ) + + tzsource%cmnhname = 'HTURB' + tzsource%clongname = 'horizontal turbulent diffusion' + tzsource%lavailable = hturb == 'TKEL' .and. HTURBDIM == '3DIM' + call Budget_source_add( tbudgets(NBUDGET_U), tzsource ) + + tzsource%cmnhname = 'MAFL' + tzsource%clongname = 'mass flux' + tzsource%lavailable = hsconv == 'EDKF' + call Budget_source_add( tbudgets(NBUDGET_U), tzsource ) + + tzsource%cmnhname = 'VISC' + tzsource%clongname = 'viscosity' + tzsource%lavailable = lvisc .and. lvisc_uvw + call Budget_source_add( tbudgets(NBUDGET_U), tzsource ) + + tzsource%cmnhname = 'ADV' + tzsource%clongname = 'advection' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_U), tzsource ) + + tzsource%cmnhname = 'PRES' + tzsource%clongname = 'pressure' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_U), tzsource ) + + + call Sourcelist_sort_compact( tbudgets(NBUDGET_U) ) + + call Sourcelist_scan( tbudgets(NBUDGET_U), cbulist_ru ) end if ! Budget of RV @@ -664,9 +667,8 @@ if ( lbu_rv ) then !Allocate all basic source terms (used or not) !The size should be large enough (bigger than necessary is OK) - isourcesmax = 19 - tbudgets(NBUDGET_V)%nsourcesmax = isourcesmax - allocate( tbudgets(NBUDGET_V)%tsources(isourcesmax) ) + tbudgets(NBUDGET_V)%nsourcesmax = NSOURCESMAX + allocate( tbudgets(NBUDGET_V)%tsources(NSOURCESMAX) ) allocate( tbudgets(NBUDGET_V)%xtmpstore(ibudim1, ibudim2, ibudim3) ) @@ -677,102 +679,107 @@ if ( lbu_rv ) then tzsource%cunits = 'm s-1' - gcond = .true. - tzsource%cmnhname = 'INIF' - tzsource%clongname = 'initial state' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'INIF' + tzsource%clongname = 'initial state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_V), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'ENDF' - tzsource%clongname = 'final state' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'ENDF' + tzsource%clongname = 'final state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_V), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'AVEF' - tzsource%clongname = 'averaged state' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .false. ) + tzsource%cmnhname = 'AVEF' + tzsource%clongname = 'averaged state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_V), tzsource, odonotinit = .true., ooverwrite = .false. ) tzsource%cunits = 'm s-2' - gcond = .true. - tzsource%cmnhname = 'ASSE' - tzsource%clongname = 'time filter (Asselin)' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, nassev ) - - gcond = nmodel > 1 - tzsource%cmnhname = 'NEST' - tzsource%clongname = 'nesting' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, nnestv ) - - gcond = lforcing - tzsource%cmnhname = 'FRC' - tzsource%clongname = 'forcing' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, nfrcv ) - - gcond = onudging - tzsource%cmnhname = 'NUD' - tzsource%clongname = 'nudging' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, nnudv ) - - gcond = .not.l1d .and. .not.lcartesian - tzsource%cmnhname = 'CURV' - tzsource%clongname = 'curvature' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, ncurvv ) - - gcond = lcorio - tzsource%cmnhname = 'COR' - tzsource%clongname = 'Coriolis' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, ncorv ) - - gcond = onumdifu - tzsource%cmnhname = 'DIF' - tzsource%clongname = 'numerical diffusion' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, ndifv ) - - gcond = ohorelax_uvwth .or. ove_relax .or. ove_relax_grd - tzsource%cmnhname = 'REL' - tzsource%clongname = 'relaxation' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, nrelv ) - - gcond = odragtree - tzsource%cmnhname = 'DRAG' - tzsource%clongname = 'drag force' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, ndragv ) - - gcond = ldragbldg - tzsource%cmnhname = 'DRAGB' - tzsource%clongname = 'drag force due to buildings' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, ndragbv ) - - gcond = hturb == 'TKEL' - tzsource%cmnhname = 'VTURB' - tzsource%clongname = 'vertical turbulent diffusion' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, nvturbv ) - - gcond = hturb == 'TKEL' .and. HTURBDIM == '3DIM' - tzsource%cmnhname = 'HTURB' - tzsource%clongname = 'horizontal turbulent diffusion' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, nhturbv ) - - gcond = hsconv == 'EDKF' - tzsource%cmnhname = 'MAFL' - tzsource%clongname = 'mass flux' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, nmaflv ) - - gcond = lvisc .and. lvisc_uvw - tzsource%cmnhname = 'VISC' - tzsource%clongname = 'viscosity' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, nviscv ) - - gcond = .true. - tzsource%cmnhname = 'ADV' - tzsource%clongname = 'advection' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, nadvv ) - - gcond = .true. - tzsource%cmnhname = 'PRES' - tzsource%clongname = 'pressure' - call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, npresv ) + tzsource%cmnhname = 'ASSE' + tzsource%clongname = 'time filter (Asselin)' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_V), tzsource ) + + tzsource%cmnhname = 'NEST' + tzsource%clongname = 'nesting' + tzsource%lavailable = nmodel > 1 + call Budget_source_add( tbudgets(NBUDGET_V), tzsource ) + + tzsource%cmnhname = 'FRC' + tzsource%clongname = 'forcing' + tzsource%lavailable = lforcing + call Budget_source_add( tbudgets(NBUDGET_V), tzsource ) + + tzsource%cmnhname = 'NUD' + tzsource%clongname = 'nudging' + tzsource%lavailable = onudging + call Budget_source_add( tbudgets(NBUDGET_V), tzsource ) + + tzsource%cmnhname = 'CURV' + tzsource%clongname = 'curvature' + tzsource%lavailable = .not.l1d .and. .not.lcartesian + call Budget_source_add( tbudgets(NBUDGET_V), tzsource ) + + tzsource%cmnhname = 'COR' + tzsource%clongname = 'Coriolis' + tzsource%lavailable = lcorio + call Budget_source_add( tbudgets(NBUDGET_V), tzsource ) + + tzsource%cmnhname = 'DIF' + tzsource%clongname = 'numerical diffusion' + tzsource%lavailable = onumdifu + call Budget_source_add( tbudgets(NBUDGET_V), tzsource ) + + tzsource%cmnhname = 'REL' + tzsource%clongname = 'relaxation' + tzsource%lavailable = ohorelax_uvwth .or. ove_relax .or. ove_relax_grd + call Budget_source_add( tbudgets(NBUDGET_V), tzsource ) + + tzsource%cmnhname = 'DRAG' + tzsource%clongname = 'drag force' + tzsource%lavailable = odragtree + call Budget_source_add( tbudgets(NBUDGET_V), tzsource ) + + tzsource%cmnhname = 'DRAGB' + tzsource%clongname = 'drag force due to buildings' + tzsource%lavailable = ldragbldg + call Budget_source_add( tbudgets(NBUDGET_V), tzsource ) + + tzsource%cmnhname = 'VTURB' + tzsource%clongname = 'vertical turbulent diffusion' + tzsource%lavailable = hturb == 'TKEL' + call Budget_source_add( tbudgets(NBUDGET_V), tzsource ) + + tzsource%cmnhname = 'HTURB' + tzsource%clongname = 'horizontal turbulent diffusion' + tzsource%lavailable = hturb == 'TKEL' .and. HTURBDIM == '3DIM' + call Budget_source_add( tbudgets(NBUDGET_V), tzsource ) + + tzsource%cmnhname = 'MAFL' + tzsource%clongname = 'mass flux' + tzsource%lavailable = hsconv == 'EDKF' + call Budget_source_add( tbudgets(NBUDGET_V), tzsource ) + + tzsource%cmnhname = 'VISC' + tzsource%clongname = 'viscosity' + tzsource%lavailable = lvisc .and. lvisc_uvw + call Budget_source_add( tbudgets(NBUDGET_V), tzsource ) + + tzsource%cmnhname = 'ADV' + tzsource%clongname = 'advection' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_V), tzsource ) + + tzsource%cmnhname = 'PRES' + tzsource%clongname = 'pressure' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_V), tzsource ) + + + call Sourcelist_sort_compact( tbudgets(NBUDGET_V) ) + + call Sourcelist_scan( tbudgets(NBUDGET_V), cbulist_rv ) end if ! Budget of RW @@ -795,9 +802,8 @@ if ( lbu_rw ) then !Allocate all basic source terms (used or not) !The size should be large enough (bigger than necessary is OK) - isourcesmax = 17 - tbudgets(NBUDGET_W)%nsourcesmax = isourcesmax - allocate( tbudgets(NBUDGET_W)%tsources(isourcesmax) ) + tbudgets(NBUDGET_W)%nsourcesmax = NSOURCESMAX + allocate( tbudgets(NBUDGET_W)%tsources(NSOURCESMAX) ) allocate( tbudgets(NBUDGET_W)%xtmpstore(ibudim1, ibudim2, ibudim3) ) @@ -808,92 +814,97 @@ if ( lbu_rw ) then tzsource%cunits = 'm s-1' - gcond = .true. - tzsource%cmnhname = 'INIF' - tzsource%clongname = 'initial state' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'INIF' + tzsource%clongname = 'initial state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_W), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'ENDF' - tzsource%clongname = 'final state' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'ENDF' + tzsource%clongname = 'final state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_W), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'AVEF' - tzsource%clongname = 'averaged state' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .false. ) + tzsource%cmnhname = 'AVEF' + tzsource%clongname = 'averaged state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_W), tzsource, odonotinit = .true., ooverwrite = .false. ) tzsource%cunits = 'm s-2' - gcond = .true. - tzsource%cmnhname = 'ASSE' - tzsource%clongname = 'time filter (Asselin)' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, nassew ) - - gcond = nmodel > 1 - tzsource%cmnhname = 'NEST' - tzsource%clongname = 'nesting' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, nnestw ) - - gcond = lforcing - tzsource%cmnhname = 'FRC' - tzsource%clongname = 'forcing' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, nfrcw ) - - gcond = onudging - tzsource%cmnhname = 'NUD' - tzsource%clongname = 'nudging' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, nnudw ) - - gcond = .not.l1d .and. .not.lcartesian .and. .not.lthinshell - tzsource%cmnhname = 'CURV' - tzsource%clongname = 'curvature' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, ncurvw ) - - gcond = lcorio .and. .not.l1d .and. .not.lthinshell - tzsource%cmnhname = 'COR' - tzsource%clongname = 'Coriolis' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, ncorw ) - - gcond = onumdifu - tzsource%cmnhname = 'DIF' - tzsource%clongname = 'numerical diffusion' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, ndifw ) - - gcond = ohorelax_uvwth .or. ove_relax .or. ove_relax_grd - tzsource%cmnhname = 'REL' - tzsource%clongname = 'relaxation' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, nrelw ) - - gcond = hturb == 'TKEL' - tzsource%cmnhname = 'VTURB' - tzsource%clongname = 'vertical turbulent diffusion' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, nvturbw ) - - gcond = hturb == 'TKEL' .and. HTURBDIM == '3DIM' - tzsource%cmnhname = 'HTURB' - tzsource%clongname = 'horizontal turbulent diffusion' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, nhturbw ) - - gcond = lvisc .and. lvisc_uvw - tzsource%cmnhname = 'VISC' - tzsource%clongname = 'viscosity' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, nviscw ) - - gcond = .true. - tzsource%cmnhname = 'GRAV' - tzsource%clongname = 'gravity' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, ngravw ) - - gcond = .true. - tzsource%cmnhname = 'ADV' - tzsource%clongname = 'advection' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, nadvw ) - - gcond = .true. - tzsource%cmnhname = 'PRES' - tzsource%clongname = 'pressure' - call Budget_source_add( tbudgets(NBUDGET_W), tzsource, gcond, npresw ) + tzsource%cmnhname = 'ASSE' + tzsource%clongname = 'time filter (Asselin)' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_W), tzsource ) + + tzsource%cmnhname = 'NEST' + tzsource%clongname = 'nesting' + tzsource%lavailable = nmodel > 1 + call Budget_source_add( tbudgets(NBUDGET_W), tzsource ) + + tzsource%cmnhname = 'FRC' + tzsource%clongname = 'forcing' + tzsource%lavailable = lforcing + call Budget_source_add( tbudgets(NBUDGET_W), tzsource ) + + tzsource%cmnhname = 'NUD' + tzsource%clongname = 'nudging' + tzsource%lavailable = onudging + call Budget_source_add( tbudgets(NBUDGET_W), tzsource ) + + tzsource%cmnhname = 'CURV' + tzsource%clongname = 'curvature' + tzsource%lavailable = .not.l1d .and. .not.lcartesian .and. .not.lthinshell + call Budget_source_add( tbudgets(NBUDGET_W), tzsource ) + + tzsource%cmnhname = 'COR' + tzsource%clongname = 'Coriolis' + tzsource%lavailable = lcorio .and. .not.l1d .and. .not.lthinshell + call Budget_source_add( tbudgets(NBUDGET_W), tzsource ) + + tzsource%cmnhname = 'DIF' + tzsource%clongname = 'numerical diffusion' + tzsource%lavailable = onumdifu + call Budget_source_add( tbudgets(NBUDGET_W), tzsource ) + + tzsource%cmnhname = 'REL' + tzsource%clongname = 'relaxation' + tzsource%lavailable = ohorelax_uvwth .or. ove_relax .or. ove_relax_grd + call Budget_source_add( tbudgets(NBUDGET_W), tzsource ) + + tzsource%cmnhname = 'VTURB' + tzsource%clongname = 'vertical turbulent diffusion' + tzsource%lavailable = hturb == 'TKEL' + call Budget_source_add( tbudgets(NBUDGET_W), tzsource ) + + tzsource%cmnhname = 'HTURB' + tzsource%clongname = 'horizontal turbulent diffusion' + tzsource%lavailable = hturb == 'TKEL' .and. HTURBDIM == '3DIM' + call Budget_source_add( tbudgets(NBUDGET_W), tzsource ) + + tzsource%cmnhname = 'VISC' + tzsource%clongname = 'viscosity' + tzsource%lavailable = lvisc .and. lvisc_uvw + call Budget_source_add( tbudgets(NBUDGET_W), tzsource ) + + tzsource%cmnhname = 'GRAV' + tzsource%clongname = 'gravity' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_W), tzsource ) + + tzsource%cmnhname = 'ADV' + tzsource%clongname = 'advection' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_W), tzsource ) + + tzsource%cmnhname = 'PRES' + tzsource%clongname = 'pressure' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_W), tzsource ) + + + call Sourcelist_sort_compact( tbudgets(NBUDGET_W) ) + + call Sourcelist_scan( tbudgets(NBUDGET_W), cbulist_rw ) end if ! Budget of RTH @@ -904,9 +915,8 @@ if ( lbu_rth ) then !Allocate all basic source terms (used or not) !The size should be large enough (bigger than necessary is OK) - isourcesmax = 53 - tbudgets(NBUDGET_TH)%nsourcesmax = isourcesmax - allocate( tbudgets(NBUDGET_TH)%tsources(isourcesmax) ) + tbudgets(NBUDGET_TH)%nsourcesmax = NSOURCESMAX + allocate( tbudgets(NBUDGET_TH)%tsources(NSOURCESMAX) ) allocate( tbudgets(NBUDGET_TH)%xtmpstore(ibudim1, ibudim2, ibudim3) ) @@ -917,288 +927,302 @@ if ( lbu_rth ) then tzsource%cunits = 'K' - gcond = .true. - tzsource%cmnhname = 'INIF' - tzsource%clongname = 'initial state' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'INIF' + tzsource%clongname = 'initial state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'ENDF' - tzsource%clongname = 'final state' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'ENDF' + tzsource%clongname = 'final state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'AVEF' - tzsource%clongname = 'averaged state' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .false. ) + tzsource%cmnhname = 'AVEF' + tzsource%clongname = 'averaged state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, odonotinit = .true., ooverwrite = .false. ) tzsource%cunits = 'K s-1' - gcond = .true. - tzsource%cmnhname = 'ASSE' - tzsource%clongname = 'time filter (Asselin)' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nasseth ) - - gcond = nmodel > 1 - tzsource%cmnhname = 'NEST' - tzsource%clongname = 'nesting' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nnestth ) - - gcond = lforcing - tzsource%cmnhname = 'FRC' - tzsource%clongname = 'forcing' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nfrcth ) - - gcond = l2d_adv_frc - tzsource%cmnhname = '2DADV' - tzsource%clongname = 'advective forcing' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, n2dadvth ) - - gcond = l2d_rel_frc - tzsource%cmnhname = '2DREL' - tzsource%clongname = 'relaxation forcing' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, n2drelth ) - - gcond = onudging - tzsource%cmnhname = 'NUD' - tzsource%clongname = 'nudging' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nnudth ) - - gcond = krr > 0 .and. .not.l1d - tzsource%cmnhname = 'PREF' - tzsource%clongname = 'reference pressure' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nprefth ) - - gcond = onumdifth - tzsource%cmnhname = 'DIF' - tzsource%clongname = 'numerical diffusion' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, ndifth ) - - gcond = ohorelax_uvwth .or. ove_relax .or. ove_relax_grd - tzsource%cmnhname = 'REL' - tzsource%clongname = 'relaxation' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nrelth ) - - gcond = hrad /= 'NONE' - tzsource%cmnhname = 'RAD' - tzsource%clongname = 'radiation' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nradth ) - - gcond = hdconv == 'KAFR' .OR. hsconv == 'KAFR' - tzsource%cmnhname = 'DCONV' - tzsource%clongname = 'KAFR convection' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, ndconvth ) - - gcond = hturb == 'TKEL' - tzsource%cmnhname = 'VTURB' - tzsource%clongname = 'vertical turbulent diffusion' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nvturbth ) - - gcond = hturb == 'TKEL' .and. HTURBDIM == '3DIM' - tzsource%cmnhname = 'HTURB' - tzsource%clongname = 'horizontal turbulent diffusion' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nhturbth ) - - gcond = hturb == 'TKEL' - tzsource%cmnhname = 'DISSH' - tzsource%clongname = 'dissipation' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, ndisshth ) - - gcond = hturb == 'TKEL' .and. ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) - tzsource%cmnhname = 'NETUR' - tzsource%clongname = 'negative correction induced by turbulence' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nneturth ) - - gcond = hsconv == 'EDKF' - tzsource%cmnhname = 'MAFL' - tzsource%clongname = 'mass flux' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nmaflth ) - - gcond = lblowsnow .and. lsnowsubl - tzsource%cmnhname = 'SNSUB' - tzsource%clongname = 'blowing snow sublimation' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nsnsubth ) - - gcond = lvisc .and. lvisc_th - tzsource%cmnhname = 'VISC' - tzsource%clongname = 'viscosity' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nviscth ) - - gcond = .true. - tzsource%cmnhname = 'ADV' - tzsource%clongname = 'total advection' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nadvth ) - - gcond = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' - tzsource%cmnhname = 'NEADV' - tzsource%clongname = 'negative correction induced by advection' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nneadvth ) - - gcond = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' - tzsource%cmnhname = 'NEGA' - tzsource%clongname = 'negative correction' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nnegath ) - - gcond = hcloud == 'LIMA' .and. lptsplit - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'heat transport by hydrometeors sedimentation' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nsedith ) - + tzsource%cmnhname = 'ASSE' + tzsource%clongname = 'time filter (Asselin)' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'NEST' + tzsource%clongname = 'nesting' + tzsource%lavailable = nmodel > 1 + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'FRC' + tzsource%clongname = 'forcing' + tzsource%lavailable = lforcing + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = '2DADV' + tzsource%clongname = 'advective forcing' + tzsource%lavailable = l2d_adv_frc + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = '2DREL' + tzsource%clongname = 'relaxation forcing' + tzsource%lavailable = l2d_rel_frc + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'NUD' + tzsource%clongname = 'nudging' + tzsource%lavailable = onudging + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'PREF' + tzsource%clongname = 'reference pressure' + tzsource%lavailable = krr > 0 .and. .not.l1d + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'DIF' + tzsource%clongname = 'numerical diffusion' + tzsource%lavailable = onumdifth + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'REL' + tzsource%clongname = 'relaxation' + tzsource%lavailable = ohorelax_uvwth .or. ove_relax .or. ove_relax_grd + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'RAD' + tzsource%clongname = 'radiation' + tzsource%lavailable = hrad /= 'NONE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'DCONV' + tzsource%clongname = 'KAFR convection' + tzsource%lavailable = hdconv == 'KAFR' .OR. hsconv == 'KAFR' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'VTURB' + tzsource%clongname = 'vertical turbulent diffusion' + tzsource%lavailable = hturb == 'TKEL' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'HTURB' + tzsource%clongname = 'horizontal turbulent diffusion' + tzsource%lavailable = hturb == 'TKEL' .and. HTURBDIM == '3DIM' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'DISSH' + tzsource%clongname = 'dissipation' + tzsource%lavailable = hturb == 'TKEL' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'NETUR' + tzsource%clongname = 'negative correction induced by turbulence' + tzsource%lavailable = hturb == 'TKEL' .and. ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'MAFL' + tzsource%clongname = 'mass flux' + tzsource%lavailable = hsconv == 'EDKF' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'SNSUB' + tzsource%clongname = 'blowing snow sublimation' + tzsource%lavailable = lblowsnow .and. lsnowsubl + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'VISC' + tzsource%clongname = 'viscosity' + tzsource%lavailable = lvisc .and. lvisc_th + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'ADV' + tzsource%clongname = 'total advection' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'NEADV' + tzsource%clongname = 'negative correction induced by advection' + tzsource%lavailable = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'NEGA' + tzsource%clongname = 'negative correction' + tzsource%lavailable = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'heat transport by hydrometeors sedimentation' + tzsource%lavailable = hcloud == 'LIMA' .and. lptsplit + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'HENU' + tzsource%clongname = 'heterogeneous nucleation' gtmp = cactccn == 'ABRK' .and. (lorilam .or. ldust .or. lsalt ) - gcond = ( hcloud == 'LIMA' .and. lwarm_lima .and. lacti_lima .and. nmod_ccn >= 1 ) & - .or. hcloud(1:3) == 'ICE' & - .or. ( hcloud == 'C2R2' .and. ( gtmp .or. .not.lsupsat_c2r2 ) ) & - .or. ( hcloud == 'KHKO' .and. ( gtmp .or. .not.lsupsat_c2r2 ) ) - tzsource%cmnhname = 'HENU' - tzsource%clongname = 'heterogeneous nucleation' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nhenuth ) - - gcond = ( hcloud == 'LIMA' .and. ( ( .not. lptsplit .and. lwarm_lima .and. lrain_lima ) .or. lptsplit ) ) & - .or. ( hcloud(1:3) == 'ICE' .and. lwarm_ice ) & - .or. ( hcloud == 'C2R2' .and. lrain_c2r2 ) & - .or. ( hcloud == 'KHKO' .and. lrain_c2r2 ) & - .or. hcloud == 'KESS' - tzsource%cmnhname = 'REVA' - tzsource%clongname = 'rain evaporation' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nrevath ) - - gcond = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima - tzsource%cmnhname = 'HIND' - tzsource%clongname = 'heterogeneous nucleation by deposition' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nhindth ) - - gcond = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima - tzsource%cmnhname = 'HINC' - tzsource%clongname = 'heterogeneous nucleation by contact' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nhincth ) - - gcond = hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'HON' - tzsource%clongname = 'homogeneous nucleation' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nhonth ) - - gcond = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima .and. lhhoni_lima .and. nmod_ccn >= 1 - tzsource%cmnhname = 'HONH' - tzsource%clongname = 'haze homogeneous nucleation' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nhonhth ) - - gcond = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima ) ) - tzsource%cmnhname = 'HONC' - tzsource%clongname = 'droplet homogeneous freezing' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nhoncth ) - - gcond = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima .and. lrain_lima ) ) - tzsource%cmnhname = 'HONR' - tzsource%clongname = 'raindrop homogeneous freezing' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nhonrth ) - - gcond = hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'SFR' - tzsource%clongname = 'spontaneous freezing' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nsfrth ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'DEPS' - tzsource%clongname = 'deposition on snow' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, ndepsth ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'DEPG' - tzsource%clongname = 'deposition on graupel' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, ndepgth ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'IMLT' - tzsource%clongname = 'ice melting' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nimltth ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'BERFI' - tzsource%clongname = 'Bergeron-Findeisen' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nberfith ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'RIM' - tzsource%clongname = 'riming of cloud droplets' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nrimth ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima .and. lrain_lima ) ) ) & - .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'ACC' - tzsource%clongname = 'accretion of rain' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, naccth ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'CFRZ' - tzsource%clongname = 'conversion freezing of rain' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, ncfrzth ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'WETG' - tzsource%clongname = 'wet growth of graupel' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nwetgth ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'DRYG' - tzsource%clongname = 'dry growth of graupel' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, ndrygth ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'GMLT' - tzsource%clongname = 'graupel melting' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, ngmltth ) - - gcond = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima ) & - .or. hcloud == 'ICE4' - tzsource%cmnhname = 'WETH' - tzsource%clongname = 'wet growth of hail' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nwethth ) - - gcond = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'DRYH' - tzsource%clongname = 'dry growth of hail' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, ndryhth ) - - gcond = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima ) & - .or. hcloud == 'ICE4' - tzsource%cmnhname = 'HMLT' - tzsource%clongname = 'melting of hail' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nhmltth ) - - gcond = hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'CORR' - tzsource%clongname = 'correction' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, ncorrth ) - - gcond = hcloud == 'LIMA' - tzsource%cmnhname = 'CEDS' - tzsource%clongname = 'adjustment to saturation' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, ncedsth ) - - gcond = hcloud(1:3) == 'ICE' .and. lred .and. ladj_before .and. celec == 'NONE' - tzsource%cmnhname = 'ADJU' - tzsource%clongname = '' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nadjuth ) - - gcond = hcloud(1:3) == 'ICE' .and. ( .not. lred .or. ( lred .and. ladj_after ) .or. celec /= 'NONE' ) - tzsource%cmnhname = 'CDEPI' - tzsource%clongname = 'deposition on ice' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, ncdepith ) - - gcond = hcloud == 'C2R2' .or. hcloud == 'KHKO' .or. hcloud == 'KESS' .or. hcloud == 'REVE' - tzsource%cmnhname = 'COND' - tzsource%clongname = 'vapor condensation or cloud water evaporation' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, ncondth ) - - gcond = ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) & - .and. celec == 'NONE' - tzsource%cmnhname = 'NECON' - tzsource%clongname = 'negative correction induced by condensation' - call Budget_source_add( tbudgets(NBUDGET_TH), tzsource, gcond, nneconth ) + tzsource%lavailable = ( hcloud == 'LIMA' .and. lwarm_lima .and. lacti_lima .and. nmod_ccn >= 1 ) & + .or. hcloud(1:3) == 'ICE' & + .or. ( hcloud == 'C2R2' .and. ( gtmp .or. .not.lsupsat_c2r2 ) ) & + .or. ( hcloud == 'KHKO' .and. ( gtmp .or. .not.lsupsat_c2r2 ) ) + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'REVA' + tzsource%clongname = 'rain evaporation' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( ( .not. lptsplit .and. lwarm_lima .and. lrain_lima ) .or. lptsplit ) ) & + .or. ( hcloud(1:3) == 'ICE' .and. lwarm_ice ) & + .or. ( hcloud == 'C2R2' .and. lrain_c2r2 ) & + .or. ( hcloud == 'KHKO' .and. lrain_c2r2 ) & + .or. hcloud == 'KESS' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'HIND' + tzsource%clongname = 'heterogeneous nucleation by deposition' + tzsource%lavailable = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'HINC' + tzsource%clongname = 'heterogeneous nucleation by contact' + tzsource%lavailable = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'HON' + tzsource%clongname = 'homogeneous nucleation' + tzsource%lavailable = hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'HONH' + tzsource%clongname = 'haze homogeneous nucleation' + tzsource%lavailable = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima .and. lhhoni_lima .and. nmod_ccn >= 1 + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'HONC' + tzsource%clongname = 'droplet homogeneous freezing' + tzsource%lavailable = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima ) ) + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'HONR' + tzsource%clongname = 'raindrop homogeneous freezing' + tzsource%lavailable = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima .and. lrain_lima ) ) + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'SFR' + tzsource%clongname = 'spontaneous freezing' + tzsource%lavailable = hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'DEPS' + tzsource%clongname = 'deposition on snow' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'DEPG' + tzsource%clongname = 'deposition on graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'IMLT' + tzsource%clongname = 'ice melting' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima ) ) ) .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'BERFI' + tzsource%clongname = 'Bergeron-Findeisen' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima ) ) ) .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'RIM' + tzsource%clongname = 'riming of cloud droplets' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'ACC' + tzsource%clongname = 'accretion of rain' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit & + .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima .and. lrain_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'CFRZ' + tzsource%clongname = 'conversion freezing of rain' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'WETG' + tzsource%clongname = 'wet growth of graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'DRYG' + tzsource%clongname = 'dry growth of graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'GMLT' + tzsource%clongname = 'graupel melting' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'WETH' + tzsource%clongname = 'wet growth of hail' + tzsource%lavailable = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima & + .and. lwarm_lima .and. lsnow_lima ) & + .or. hcloud == 'ICE4' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'DRYH' + tzsource%clongname = 'dry growth of hail' + tzsource%lavailable = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'HMLT' + tzsource%clongname = 'melting of hail' + tzsource%lavailable = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima & + .and. lwarm_lima .and. lsnow_lima ) & + .or. hcloud == 'ICE4' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'CORR' + tzsource%clongname = 'correction' + tzsource%lavailable = hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'CEDS' + tzsource%clongname = 'adjustment to saturation' + tzsource%lavailable = hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'ADJU' + tzsource%clongname = 'adjustment before' + tzsource%lavailable = hcloud(1:3) == 'ICE' .and. lred .and. ladj_before .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'CDEPI' + tzsource%clongname = 'deposition on ice' + tzsource%lavailable = hcloud(1:3) == 'ICE' .and. ( .not. lred .or. ( lred .and. ladj_after ) .or. celec /= 'NONE' ) + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'COND' + tzsource%clongname = 'vapor condensation or cloud water evaporation' + tzsource%lavailable = hcloud == 'C2R2' .or. hcloud == 'KHKO' .or. hcloud == 'KESS' .or. hcloud == 'REVE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + tzsource%cmnhname = 'NECON' + tzsource%clongname = 'negative correction induced by condensation' + tzsource%lavailable = ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) & + .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_TH), tzsource ) + + + call Sourcelist_sort_compact( tbudgets(NBUDGET_TH) ) + + call Sourcelist_scan( tbudgets(NBUDGET_TH), cbulist_rth ) end if ! Budget of RTKE @@ -1209,9 +1233,8 @@ if ( lbu_rtke ) then !Allocate all basic source terms (used or not) !The size should be large enough (bigger than necessary is OK) - isourcesmax = 14 - tbudgets(NBUDGET_TKE)%nsourcesmax = isourcesmax - allocate( tbudgets(NBUDGET_TKE)%tsources(isourcesmax) ) + tbudgets(NBUDGET_TKE)%nsourcesmax = NSOURCESMAX + allocate( tbudgets(NBUDGET_TKE)%tsources(NSOURCESMAX) ) allocate( tbudgets(NBUDGET_TKE)%xtmpstore(ibudim1, ibudim2, ibudim3) ) @@ -1222,78 +1245,82 @@ if ( lbu_rtke ) then tzsource%cunits = 'm2 s-1' - gcond = .true. - tzsource%cmnhname = 'INIF' - tzsource%clongname = 'initial state' - call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'INIF' + tzsource%clongname = 'initial state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'ENDF' - tzsource%clongname = 'final state' - call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'ENDF' + tzsource%clongname = 'final state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'AVEF' - tzsource%clongname = 'averaged state' - call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .false. ) + tzsource%cmnhname = 'AVEF' + tzsource%clongname = 'averaged state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, odonotinit = .true., ooverwrite = .false. ) tzsource%cunits = 'm2 s-3' - gcond = .true. - tzsource%cmnhname = 'ASSE' - tzsource%clongname = 'time filter (Asselin)' - call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, gcond, nassetke ) - - gcond = lforcing - tzsource%cmnhname = 'FRC' - tzsource%clongname = 'forcing' - call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, gcond, nfrctke ) - - gcond = onumdifth - tzsource%cmnhname = 'DIF' - tzsource%clongname = 'numerical diffusion' - call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, gcond, ndiftke ) - - gcond = ohorelax_tke - tzsource%cmnhname = 'REL' - tzsource%clongname = 'relaxation' - call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, gcond, nreltke ) - - gcond = odragtree - tzsource%cmnhname = 'DRAG' - tzsource%clongname = 'drag force' - call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, gcond, ndragtke ) - - gcond = ldragbldg - tzsource%cmnhname = 'DRAGB' - tzsource%clongname = 'drag force due to buildings' - call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, gcond, ndragbtke ) - - gcond = hturb == 'TKEL' - tzsource%cmnhname = 'DP' - tzsource%clongname = 'dynamic production' - call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, gcond, ndptke ) - - gcond = hturb == 'TKEL' - tzsource%cmnhname = 'TP' - tzsource%clongname = 'thermal production' - call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, gcond, ntptke ) - - gcond = hturb == 'TKEL' - tzsource%cmnhname = 'DISS' - tzsource%clongname = 'dissipation of TKE' - call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, gcond, ndisstke ) - - gcond = hturb == 'TKEL' - tzsource%cmnhname = 'TR' - tzsource%clongname = 'turbulent transport' - call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, gcond, ntrtke ) - - gcond = hturb == 'TKEL' - tzsource%cmnhname = 'ADV' - tzsource%clongname = 'total advection' - call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, gcond, nadvtke ) - + tzsource%cmnhname = 'ASSE' + tzsource%clongname = 'time filter (Asselin)' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource ) + + tzsource%cmnhname = 'FRC' + tzsource%clongname = 'forcing' + tzsource%lavailable = lforcing + call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource ) + + tzsource%cmnhname = 'DIF' + tzsource%clongname = 'numerical diffusion' + tzsource%lavailable = onumdifth + call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource ) + + tzsource%cmnhname = 'REL' + tzsource%clongname = 'relaxation' + tzsource%lavailable = ohorelax_tke + call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource ) + + tzsource%cmnhname = 'DRAG' + tzsource%clongname = 'drag force' + tzsource%lavailable = odragtree + call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource ) + + tzsource%cmnhname = 'DRAGB' + tzsource%clongname = 'drag force due to buildings' + tzsource%lavailable = ldragbldg + call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource ) + + tzsource%cmnhname = 'DP' + tzsource%clongname = 'dynamic production' + tzsource%lavailable = hturb == 'TKEL' + call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource ) + + tzsource%cmnhname = 'TP' + tzsource%clongname = 'thermal production' + tzsource%lavailable = hturb == 'TKEL' + call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource ) + + tzsource%cmnhname = 'DISS' + tzsource%clongname = 'dissipation of TKE' + tzsource%lavailable = hturb == 'TKEL' + call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource ) + + tzsource%cmnhname = 'TR' + tzsource%clongname = 'turbulent transport' + tzsource%lavailable = hturb == 'TKEL' + call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource ) + + tzsource%cmnhname = 'ADV' + tzsource%clongname = 'total advection' + tzsource%lavailable = hturb == 'TKEL' + call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource ) + + + call Sourcelist_sort_compact( tbudgets(NBUDGET_TKE) ) + + call Sourcelist_scan( tbudgets(NBUDGET_TKE), cbulist_rtke ) end if ! Budget of RRV @@ -1304,9 +1331,8 @@ if ( tbudgets(NBUDGET_RV)%lenabled ) then !Allocate all basic source terms (used or not) !The size should be large enough (bigger than necessary is OK) - isourcesmax = 34 - tbudgets(NBUDGET_RV)%nsourcesmax = isourcesmax - allocate( tbudgets(NBUDGET_RV)%tsources(isourcesmax) ) + tbudgets(NBUDGET_RV)%nsourcesmax = NSOURCESMAX + allocate( tbudgets(NBUDGET_RV)%tsources(NSOURCESMAX) ) allocate( tbudgets(NBUDGET_RV)%xtmpstore(ibudim1, ibudim2, ibudim3) ) @@ -1317,190 +1343,197 @@ if ( tbudgets(NBUDGET_RV)%lenabled ) then tzsource%cunits = 'kg kg-1' - gcond = .true. - tzsource%cmnhname = 'INIF' - tzsource%clongname = 'initial state' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'INIF' + tzsource%clongname = 'initial state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'ENDF' - tzsource%clongname = 'final state' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'ENDF' + tzsource%clongname = 'final state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'AVEF' - tzsource%clongname = 'averaged state' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .false. ) + tzsource%cmnhname = 'AVEF' + tzsource%clongname = 'averaged state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, odonotinit = .true., ooverwrite = .false. ) tzsource%cunits = 's-1' - gcond = .true. - tzsource%cmnhname = 'ASSE' - tzsource%clongname = 'time filter (Asselin)' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nasserv ) - - gcond = nmodel > 1 - tzsource%cmnhname = 'NEST' - tzsource%clongname = 'nesting' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nnestrv ) - - gcond = lforcing - tzsource%cmnhname = 'FRC' - tzsource%clongname = 'forcing' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nfrcrv ) - - gcond = l2d_adv_frc - tzsource%cmnhname = '2DADV' - tzsource%clongname = 'advective forcing' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, n2dadvrv ) - - gcond = l2d_rel_frc - tzsource%cmnhname = '2DREL' - tzsource%clongname = 'relaxation forcing' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, n2drelrv ) - - gcond = onudging - tzsource%cmnhname = 'NUD' - tzsource%clongname = 'nudging' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nnudrv ) - - gcond = onumdifth - tzsource%cmnhname = 'DIF' - tzsource%clongname = 'numerical diffusion' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, ndifrv ) - - gcond = ohorelax_rv - tzsource%cmnhname = 'REL' - tzsource%clongname = 'relaxation' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nrelrv ) - - gcond = hdconv == 'KAFR' .OR. hsconv == 'KAFR' - tzsource%cmnhname = 'DCONV' - tzsource%clongname = 'KAFR convection' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, ndconvrv ) - - gcond = hturb == 'TKEL' - tzsource%cmnhname = 'VTURB' - tzsource%clongname = 'vertical turbulent diffusion' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nvturbrv ) - - gcond = hturb == 'TKEL' .and. HTURBDIM == '3DIM' - tzsource%cmnhname = 'HTURB' - tzsource%clongname = 'horizontal turbulent diffusion' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nhturbrv ) - - gcond = hturb == 'TKEL' .and. ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) - tzsource%cmnhname = 'NETUR' - tzsource%clongname = 'negative correction induced by turbulence' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nneturrv ) - - gcond = hsconv == 'EDKF' - tzsource%cmnhname = 'MAFL' - tzsource%clongname = 'mass flux' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nmaflrv ) - - gcond = lblowsnow .and. lsnowsubl - tzsource%cmnhname = 'SNSUB' - tzsource%clongname = 'blowing snow sublimation' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nsnsubrv ) - - gcond = lvisc .and. lvisc_r - tzsource%cmnhname = 'VISC' - tzsource%clongname = 'viscosity' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nviscrv ) - - gcond = .true. - tzsource%cmnhname = 'ADV' - tzsource%clongname = 'total advection' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nadvrv ) - - gcond = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' - tzsource%cmnhname = 'NEADV' - tzsource%clongname = 'negative correction induced by advection' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nneadvrv ) - - gcond = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' - tzsource%cmnhname = 'NEGA' - tzsource%clongname = 'negative correction' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nnegarv ) - + tzsource%cmnhname = 'ASSE' + tzsource%clongname = 'time filter (Asselin)' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'NEST' + tzsource%clongname = 'nesting' + tzsource%lavailable = nmodel > 1 + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'FRC' + tzsource%clongname = 'forcing' + tzsource%lavailable = lforcing + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = '2DADV' + tzsource%clongname = 'advective forcing' + tzsource%lavailable = l2d_adv_frc + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = '2DREL' + tzsource%clongname = 'relaxation forcing' + tzsource%lavailable = l2d_rel_frc + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'NUD' + tzsource%clongname = 'nudging' + tzsource%lavailable = onudging + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'DIF' + tzsource%clongname = 'numerical diffusion' + tzsource%lavailable = onumdifth + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'REL' + tzsource%clongname = 'relaxation' + tzsource%lavailable = ohorelax_rv .or. ove_relax + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'DCONV' + tzsource%clongname = 'KAFR convection' + tzsource%lavailable = hdconv == 'KAFR' .OR. hsconv == 'KAFR' + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'VTURB' + tzsource%clongname = 'vertical turbulent diffusion' + tzsource%lavailable = hturb == 'TKEL' + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'HTURB' + tzsource%clongname = 'horizontal turbulent diffusion' + tzsource%lavailable = hturb == 'TKEL' .and. HTURBDIM == '3DIM' + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'NETUR' + tzsource%clongname = 'negative correction induced by turbulence' + tzsource%lavailable = hturb == 'TKEL' .and. ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'MAFL' + tzsource%clongname = 'mass flux' + tzsource%lavailable = hsconv == 'EDKF' + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'SNSUB' + tzsource%clongname = 'blowing snow sublimation' + tzsource%lavailable = lblowsnow .and. lsnowsubl + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'VISC' + tzsource%clongname = 'viscosity' + tzsource%lavailable = lvisc .and. lvisc_r + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'ADV' + tzsource%clongname = 'total advection' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'NEADV' + tzsource%clongname = 'negative correction induced by advection' + tzsource%lavailable = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'NEGA' + tzsource%clongname = 'negative correction' + tzsource%lavailable = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'HENU' + tzsource%clongname = 'heterogeneous nucleation' gtmp = cactccn == 'ABRK' .and. (lorilam .or. ldust .or. lsalt ) - gcond = ( hcloud == 'LIMA' .and. lwarm_lima .and. lacti_lima .and. nmod_ccn >= 1 ) & - .or. hcloud(1:3) == 'ICE' & - .or. ( hcloud == 'C2R2' .and. ( gtmp .or. .not.lsupsat_c2r2 ) ) & - .or. ( hcloud == 'KHKO' .and. ( gtmp .or. .not.lsupsat_c2r2 ) ) - tzsource%cmnhname = 'HENU' - tzsource%clongname = 'heterogeneous nucleation' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nhenurv ) - - gcond = ( hcloud == 'LIMA' .and. ( ( .not. lptsplit .and. lwarm_lima .and. lrain_lima ) .or. lptsplit ) ) & - .or. ( hcloud(1:3) == 'ICE' .and. lwarm_ice ) & - .or. ( hcloud == 'C2R2' .and. lrain_c2r2 ) & - .or. ( hcloud == 'KHKO' .and. lrain_c2r2 ) & - .or. hcloud == 'KESS' - tzsource%cmnhname = 'REVA' - tzsource%clongname = 'rain evaporation' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nrevarv ) - - gcond = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima - tzsource%cmnhname = 'HIND' - tzsource%clongname = 'heterogeneous nucleation by deposition' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nhindrv ) - - gcond = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima .and. lhhoni_lima .and. nmod_ccn >= 1 - tzsource%cmnhname = 'HONH' - tzsource%clongname = 'haze homogeneous nucleation' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nhonhrv ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'DEPS' - tzsource%clongname = 'deposition on snow' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, ndepsrv ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'DEPG' - tzsource%clongname = 'deposition on graupel' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, ndepgrv ) - - gcond = hcloud == 'LIMA' - tzsource%cmnhname = 'CEDS' - tzsource%clongname = 'adjustment to saturation' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, ncedsrv ) - - gcond = hcloud(1:3) == 'ICE' .and. lred .and. ladj_before .and. celec == 'NONE' - tzsource%cmnhname = 'ADJU' - tzsource%clongname = 'adjustment before' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nadjurv ) - - gcond = hcloud == 'C2R2' .or. hcloud == 'KHKO' .or. hcloud == 'KESS' .or. hcloud == 'REVE' - tzsource%cmnhname = 'COND' - tzsource%clongname = 'vapor condensation or cloud water evaporation' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, ncondrv ) - - gcond = hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'CORR' - tzsource%clongname = 'correction' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, ncorrrv ) - - gcond = hcloud(1:3) == 'ICE' .and. ( .not. lred .or. ( lred .and. ladj_after ) .or. celec /= 'NONE' ) - tzsource%cmnhname = 'CDEPI' - tzsource%clongname = 'deposition on ice' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, ncdepirv ) - - gcond = hcloud == 'LIMA' .and. lptsplit - tzsource%cmnhname = 'CORR2' - tzsource%clongname = 'supplementary correction inside LIMA splitting' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, ncorr2rv ) - - gcond = ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) & - .and. celec == 'NONE' - tzsource%cmnhname = 'NECON' - tzsource%clongname = 'negative correction induced by condensation' - call Budget_source_add( tbudgets(NBUDGET_RV), tzsource, gcond, nneconrv ) + tzsource%lavailable = ( hcloud == 'LIMA' .and. lwarm_lima .and. lacti_lima .and. nmod_ccn >= 1 ) & + .or. hcloud(1:3) == 'ICE' & + .or. ( hcloud == 'C2R2' .and. ( gtmp .or. .not.lsupsat_c2r2 ) ) & + .or. ( hcloud == 'KHKO' .and. ( gtmp .or. .not.lsupsat_c2r2 ) ) + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'REVA' + tzsource%clongname = 'rain evaporation' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( ( .not. lptsplit .and. lwarm_lima .and. lrain_lima ) & + .or. lptsplit ) ) & + .or. ( hcloud(1:3) == 'ICE' .and. lwarm_ice ) & + .or. ( hcloud == 'C2R2' .and. lrain_c2r2 ) & + .or. ( hcloud == 'KHKO' .and. lrain_c2r2 ) & + .or. hcloud == 'KESS' + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'HIND' + tzsource%clongname = 'heterogeneous nucleation by deposition' + tzsource%lavailable = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'HONH' + tzsource%clongname = 'haze homogeneous nucleation' + tzsource%lavailable = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima .and. lhhoni_lima .and. nmod_ccn >= 1 + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'DEPS' + tzsource%clongname = 'deposition on snow' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'DEPG' + tzsource%clongname = 'deposition on graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'CEDS' + tzsource%clongname = 'adjustment to saturation' + tzsource%lavailable = hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'ADJU' + tzsource%clongname = 'adjustment before' + tzsource%lavailable = hcloud(1:3) == 'ICE' .and. lred .and. ladj_before .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'COND' + tzsource%clongname = 'vapor condensation or cloud water evaporation' + tzsource%lavailable = hcloud == 'C2R2' .or. hcloud == 'KHKO' .or. hcloud == 'KESS' .or. hcloud == 'REVE' + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'CORR' + tzsource%clongname = 'correction' + tzsource%lavailable = hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'CDEPI' + tzsource%clongname = 'deposition on ice' + tzsource%lavailable = hcloud(1:3) == 'ICE' .and. ( .not. lred .or. ( lred .and. ladj_after ) .or. celec /= 'NONE' ) + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'CORR2' + tzsource%clongname = 'supplementary correction inside LIMA splitting' + tzsource%lavailable = hcloud == 'LIMA' .and. lptsplit + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + tzsource%cmnhname = 'NECON' + tzsource%clongname = 'negative correction induced by condensation' + tzsource%lavailable = ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) & + .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RV), tzsource ) + + + call Sourcelist_sort_compact( tbudgets(NBUDGET_RV) ) + + call Sourcelist_scan( tbudgets(NBUDGET_RV), cbulist_rrv ) end if ! Budget of RRC @@ -1515,9 +1548,8 @@ if ( tbudgets(NBUDGET_RC)%lenabled ) then !Allocate all basic source terms (used or not) !The size should be large enough (bigger than necessary is OK) - isourcesmax = 43 - tbudgets(NBUDGET_RC)%nsourcesmax = isourcesmax - allocate( tbudgets(NBUDGET_RC)%tsources(isourcesmax) ) + tbudgets(NBUDGET_RC)%nsourcesmax = NSOURCESMAX + allocate( tbudgets(NBUDGET_RC)%tsources(NSOURCESMAX) ) allocate( tbudgets(NBUDGET_RC)%xtmpstore(ibudim1, ibudim2, ibudim3) ) @@ -1528,246 +1560,255 @@ if ( tbudgets(NBUDGET_RC)%lenabled ) then tzsource%cunits = 'kg kg-1' - gcond = .true. - tzsource%cmnhname = 'INIF' - tzsource%clongname = 'initial state' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'INIF' + tzsource%clongname = 'initial state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'ENDF' - tzsource%clongname = 'final state' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'ENDF' + tzsource%clongname = 'final state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'AVEF' - tzsource%clongname = 'averaged state' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .false. ) + tzsource%cmnhname = 'AVEF' + tzsource%clongname = 'averaged state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, odonotinit = .true., ooverwrite = .false. ) tzsource%cunits = 's-1' - gcond = .true. - tzsource%cmnhname = 'ASSE' - tzsource%clongname = 'time filter (Asselin)' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nasserc ) - - gcond = nmodel > 1 - tzsource%cmnhname = 'NEST' - tzsource%clongname = 'nesting' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nnestrc ) - - gcond = lforcing - tzsource%cmnhname = 'FRC' - tzsource%clongname = 'forcing' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nfrcrc ) - - gcond = onumdifth - tzsource%cmnhname = 'DIF' - tzsource%clongname = 'numerical diffusion' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, ndifrc ) - - gcond = ohorelax_rc - tzsource%cmnhname = 'REL' - tzsource%clongname = 'relaxation' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nrelrc ) - - gcond = hdconv == 'KAFR' .OR. hsconv == 'KAFR' - tzsource%cmnhname = 'DCONV' - tzsource%clongname = 'KAFR convection' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, ndconvrc ) - - gcond = odragtree .and. odepotree - tzsource%cmnhname = 'DEPOTR' - tzsource%clongname = 'tree droplet deposition' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, ndepotrrc ) - - gcond = hturb == 'TKEL' - tzsource%cmnhname = 'VTURB' - tzsource%clongname = 'vertical turbulent diffusion' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nvturbrc ) - - gcond = hturb == 'TKEL' .and. HTURBDIM == '3DIM' - tzsource%cmnhname = 'HTURB' - tzsource%clongname = 'horizontal turbulent diffusion' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nhturbrc ) - - gcond = hturb == 'TKEL' .and. ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) - tzsource%cmnhname = 'NETUR' - tzsource%clongname = 'negative correction induced by turbulence' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nneturrc ) - - gcond = lvisc .and. lvisc_r - tzsource%cmnhname = 'VISC' - tzsource%clongname = 'viscosity' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nviscrc ) - - gcond = .true. - tzsource%cmnhname = 'ADV' - tzsource%clongname = 'total advection' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nadvrc ) - - gcond = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' - tzsource%cmnhname = 'NEADV' - tzsource%clongname = 'negative correction induced by advection' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nneadvrc ) - - gcond = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' - tzsource%cmnhname = 'NEGA' - tzsource%clongname = 'negative correction' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nnegarc ) - - gcond = ( hcloud == 'LIMA' .and. lptsplit .and. lwarm_lima .and. lrain_lima ) & - .or. ( hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' ) - tzsource%cmnhname = 'CORR' - tzsource%clongname = 'correction' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, ncorrrc ) - - gcond = ( hcloud == 'LIMA' .and. lwarm_lima .and. lsedc_lima ) & - .or. ( hcloud(1:3) == 'ICE' .and. lsedic_ice ) & - .or. ( hcloud == 'C2R2' .and. lsedc_c2r2 ) & - .or. ( hcloud == 'KHKO' .and. lsedc_c2r2 ) - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation of cloud' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nsedirc ) - - gcond = ( hcloud == 'LIMA' .and. lwarm_lima .and. ldepoc_lima ) & - .or. ( hcloud == 'C2R2' .and. ldepoc_c2r2 ) & - .or. ( hcloud == 'KHKO' .and. ldepoc_c2r2 ) & - .or. ( hcloud(1:3) == 'ICE' .and. ldeposc_ice .and. celec == 'NONE' ) - tzsource%cmnhname = 'DEPO' - tzsource%clongname = 'surface droplet deposition' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, ndeporc ) - - gcond = hcloud == 'LIMA' .and. lptsplit .and. lwarm_lima .and. lrain_lima - tzsource%cmnhname = 'R2C1' - tzsource%clongname = 'rain to cloud change after sedimentation' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nr2c1rc ) - + tzsource%cmnhname = 'ASSE' + tzsource%clongname = 'time filter (Asselin)' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'NEST' + tzsource%clongname = 'nesting' + tzsource%lavailable = nmodel > 1 + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'FRC' + tzsource%clongname = 'forcing' + tzsource%lavailable = lforcing + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'DIF' + tzsource%clongname = 'numerical diffusion' + tzsource%lavailable = onumdifth + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'REL' + tzsource%clongname = 'relaxation' + tzsource%lavailable = ohorelax_rc + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'DCONV' + tzsource%clongname = 'KAFR convection' + tzsource%lavailable = hdconv == 'KAFR' .OR. hsconv == 'KAFR' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'DEPOTR' + tzsource%clongname = 'tree droplet deposition' + tzsource%lavailable = odragtree .and. odepotree + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'VTURB' + tzsource%clongname = 'vertical turbulent diffusion' + tzsource%lavailable = hturb == 'TKEL' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'HTURB' + tzsource%clongname = 'horizontal turbulent diffusion' + tzsource%lavailable = hturb == 'TKEL' .and. HTURBDIM == '3DIM' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'NETUR' + tzsource%clongname = 'negative correction induced by turbulence' + tzsource%lavailable = hturb == 'TKEL' .and. ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'VISC' + tzsource%clongname = 'viscosity' + tzsource%lavailable = lvisc .and. lvisc_r + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'ADV' + tzsource%clongname = 'total advection' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'NEADV' + tzsource%clongname = 'negative correction induced by advection' + tzsource%lavailable = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'NEGA' + tzsource%clongname = 'negative correction' + tzsource%lavailable = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'CORR' + tzsource%clongname = 'correction' + tzsource%lavailable = ( hcloud == 'LIMA' .and. lptsplit .and. lwarm_lima .and. lrain_lima ) & + .or. ( hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' ) + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation of cloud' + tzsource%lavailable = ( hcloud == 'LIMA' .and. lwarm_lima .and. lsedc_lima ) & + .or. ( hcloud(1:3) == 'ICE' .and. lsedic_ice ) & + .or. ( hcloud == 'C2R2' .and. lsedc_c2r2 ) & + .or. ( hcloud == 'KHKO' .and. lsedc_c2r2 ) + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'DEPO' + tzsource%clongname = 'surface droplet deposition' + tzsource%lavailable = ( hcloud == 'LIMA' .and. lwarm_lima .and. ldepoc_lima ) & + .or. ( hcloud == 'C2R2' .and. ldepoc_c2r2 ) & + .or. ( hcloud == 'KHKO' .and. ldepoc_c2r2 ) & + .or. ( hcloud(1:3) == 'ICE' .and. ldeposc_ice .and. celec == 'NONE' ) + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'R2C1' + tzsource%clongname = 'rain to cloud change after sedimentation' + tzsource%lavailable = hcloud == 'LIMA' .and. lptsplit .and. lwarm_lima .and. lrain_lima + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'HENU' + tzsource%clongname = 'CCN activation' gtmp = cactccn == 'ABRK' .and. (lorilam .or. ldust .or. lsalt ) - gcond = ( hcloud == 'LIMA' .and. lwarm_lima .and. lacti_lima .and. nmod_ccn >= 1 ) & - .or. ( hcloud == 'C2R2' .and. ( gtmp .or. .not.lsupsat_c2r2 ) ) & - .or. ( hcloud == 'KHKO' .and. ( gtmp .or. .not.lsupsat_c2r2 ) ) - tzsource%cmnhname = 'HENU' - tzsource%clongname = 'CCN activation' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nhenurc ) - - gcond = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima - tzsource%cmnhname = 'HINC' - tzsource%clongname = 'heterogeneous nucleation by contact' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nhincrc ) - - gcond = hcloud(1:3) == 'ICE' .and. lred .and. ladj_before .and. celec == 'NONE' - tzsource%cmnhname = 'ADJU' - tzsource%clongname = 'adjustment to saturation' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nadjurc ) - - gcond = hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'HON' - tzsource%clongname = 'homogeneous nucleation' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nhonrc ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lwarm_lima .and. lrain_lima ) ) ) & - .or. hcloud == 'KESS' & - .or. ( hcloud(1:3) == 'ICE' .and. lwarm_ice ) & - .or. ( hcloud == 'C2R2' .and. lrain_c2r2 ) & - .or. ( hcloud == 'KHKO' .and. lrain_c2r2 ) - tzsource%cmnhname = 'AUTO' - tzsource%clongname = 'autoconversion into rain' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nautorc ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lwarm_lima .and. lrain_lima ) ) ) & - .or. hcloud == 'KESS' & - .or. ( hcloud(1:3) == 'ICE' .and. lwarm_ice ) & - .or. ( hcloud == 'C2R2' .and. lrain_c2r2 ) & - .or. ( hcloud == 'KHKO' .and. lrain_c2r2 ) - tzsource%cmnhname = 'ACCR' - tzsource%clongname = 'accretion' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, naccrrc ) - - gcond = hcloud == 'LIMA' .and. ( lptsplit .or. ( lwarm_lima .and. lrain_lima ) ) - tzsource%cmnhname = 'REVA' - tzsource%clongname = 'rain evaporation' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nrevarc ) - - gcond = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima ) ) - tzsource%cmnhname = 'HONC' - tzsource%clongname = 'droplet homogeneous freezing' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nhoncrc ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'IMLT' - tzsource%clongname = 'ice melting' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nimltrc ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'BERFI' - tzsource%clongname = 'Bergeron-Findeisen' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nberfirc ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'RIM' - tzsource%clongname = 'riming of cloud water' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nrimrc ) - - gcond = hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'CMEL' - tzsource%clongname = 'collection by snow and conversion into rain with T>XTT on ice' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, ncmelrc ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'WETG' - tzsource%clongname = 'wet growth of graupel' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nwetgrc ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'DRYG' - tzsource%clongname = 'dry growth of graupel' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, ndrygrc ) - - gcond = hcloud == 'LIMA' .and. lptsplit - tzsource%cmnhname = 'CVRC' - tzsource%clongname = 'rain to cloud change after other microphysical processes' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, ncvrcrc ) - - gcond = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima ) & - .or. hcloud == 'ICE4' - tzsource%cmnhname = 'WETH' - tzsource%clongname = 'wet growth of hail' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nwethrc ) - - gcond = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'DRYH' - tzsource%clongname = 'dry growth of hail' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, ndryhrc ) - - gcond = hcloud == 'LIMA' - tzsource%cmnhname = 'CEDS' - tzsource%clongname = 'adjustment to saturation' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, ncedsrc ) - - gcond = hcloud(1:3) == 'ICE' .and. ( .not. lred .or. ( lred .and. ladj_after ) .or. celec /= 'NONE' ) - tzsource%cmnhname = 'CDEPI' - tzsource%clongname = 'condensation/deposition on ice' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, ncdepirc ) - - gcond = hcloud == 'C2R2' .or. hcloud == 'KHKO' .or. hcloud == 'KESS' .or. hcloud == 'REVE' - tzsource%cmnhname = 'COND' - tzsource%clongname = 'vapor condensation or cloud water evaporation' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, ncondrc ) - - gcond = hcloud == 'LIMA' .and. lptsplit - tzsource%cmnhname = 'CORR2' - tzsource%clongname = 'supplementary correction inside LIMA splitting' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, 1 ) - - gcond = ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) & - .and. celec == 'NONE' - tzsource%cmnhname = 'NECON' - tzsource%clongname = 'negative correction induced by condensation' - call Budget_source_add( tbudgets(NBUDGET_RC), tzsource, gcond, nneconrc ) + tzsource%lavailable = ( hcloud == 'LIMA' .and. lwarm_lima .and. lacti_lima .and. nmod_ccn >= 1 ) & + .or. ( hcloud == 'C2R2' .and. ( gtmp .or. .not.lsupsat_c2r2 ) ) & + .or. ( hcloud == 'KHKO' .and. ( gtmp .or. .not.lsupsat_c2r2 ) ) + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'HINC' + tzsource%clongname = 'heterogeneous nucleation by contact' + tzsource%lavailable = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'ADJU' + tzsource%clongname = 'adjustment to saturation' + tzsource%lavailable = hcloud(1:3) == 'ICE' .and. lred .and. ladj_before .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'HON' + tzsource%clongname = 'homogeneous nucleation' + tzsource%lavailable = hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'AUTO' + tzsource%clongname = 'autoconversion into rain' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lwarm_lima .and. lrain_lima ) ) ) & + .or. hcloud == 'KESS' & + .or. ( hcloud(1:3) == 'ICE' .and. lwarm_ice ) & + .or. ( hcloud == 'C2R2' .and. lrain_c2r2 ) & + .or. ( hcloud == 'KHKO' .and. lrain_c2r2 ) + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'ACCR' + tzsource%clongname = 'accretion' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lwarm_lima .and. lrain_lima ) ) ) & + .or. hcloud == 'KESS' & + .or. ( hcloud(1:3) == 'ICE' .and. lwarm_ice ) & + .or. ( hcloud == 'C2R2' .and. lrain_c2r2 ) & + .or. ( hcloud == 'KHKO' .and. lrain_c2r2 ) + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'REVA' + tzsource%clongname = 'rain evaporation' + tzsource%lavailable = hcloud == 'LIMA' .and. ( lptsplit .or. ( lwarm_lima .and. lrain_lima ) ) + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'HONC' + tzsource%clongname = 'droplet homogeneous freezing' + tzsource%lavailable = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima ) ) + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'IMLT' + tzsource%clongname = 'ice melting' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima ) ) ) .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'BERFI' + tzsource%clongname = 'Bergeron-Findeisen' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima) ) ) .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'RIM' + tzsource%clongname = 'riming of cloud water' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'CMEL' + tzsource%clongname = 'collection by snow and conversion into rain with T>XTT on ice' + tzsource%lavailable = hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'WETG' + tzsource%clongname = 'wet growth of graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'DRYG' + tzsource%clongname = 'dry growth of graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'CVRC' + tzsource%clongname = 'rain to cloud change after other microphysical processes' + tzsource%lavailable = hcloud == 'LIMA' .and. lptsplit + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'WETH' + tzsource%clongname = 'wet growth of hail' + tzsource%lavailable = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima & + .and. lwarm_lima .and. lsnow_lima ) & + .or. hcloud == 'ICE4' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'DRYH' + tzsource%clongname = 'dry growth of hail' + tzsource%lavailable = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'CEDS' + tzsource%clongname = 'adjustment to saturation' + tzsource%lavailable = hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'CDEPI' + tzsource%clongname = 'condensation/deposition on ice' + tzsource%lavailable = hcloud(1:3) == 'ICE' .and. ( .not. lred .or. ( lred .and. ladj_after ) .or. celec /= 'NONE' ) + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'COND' + tzsource%clongname = 'vapor condensation or cloud water evaporation' + tzsource%lavailable = hcloud == 'C2R2' .or. hcloud == 'KHKO' .or. hcloud == 'KESS' .or. hcloud == 'REVE' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'CORR2' + tzsource%clongname = 'supplementary correction inside LIMA splitting' + tzsource%lavailable = hcloud == 'LIMA' .and. lptsplit + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + tzsource%cmnhname = 'NECON' + tzsource%clongname = 'negative correction induced by condensation' + tzsource%lavailable = ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) & + .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RC), tzsource ) + + + call Sourcelist_sort_compact( tbudgets(NBUDGET_RC) ) + + call Sourcelist_scan( tbudgets(NBUDGET_RC), cbulist_rrc ) end if ! Budget of RRR @@ -1778,9 +1819,8 @@ if ( tbudgets(NBUDGET_RR)%lenabled ) then !Allocate all basic source terms (used or not) !The size should be large enough (bigger than necessary is OK) - isourcesmax = 33 - tbudgets(NBUDGET_RR)%nsourcesmax = isourcesmax - allocate( tbudgets(NBUDGET_RR)%tsources(isourcesmax) ) + tbudgets(NBUDGET_RR)%nsourcesmax = NSOURCESMAX + allocate( tbudgets(NBUDGET_RR)%tsources(NSOURCESMAX) ) allocate( tbudgets(NBUDGET_RR)%xtmpstore(ibudim1, ibudim2, ibudim3) ) @@ -1791,197 +1831,210 @@ if ( tbudgets(NBUDGET_RR)%lenabled ) then tzsource%cunits = 'kg kg-1' - gcond = .true. - tzsource%cmnhname = 'INIF' - tzsource%clongname = 'initial state' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'INIF' + tzsource%clongname = 'initial state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'ENDF' - tzsource%clongname = 'final state' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'ENDF' + tzsource%clongname = 'final state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'AVEF' - tzsource%clongname = 'averaged state' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .false. ) + tzsource%cmnhname = 'AVEF' + tzsource%clongname = 'averaged state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, odonotinit = .true., ooverwrite = .false. ) tzsource%cunits = 's-1' - gcond = .true. - tzsource%cmnhname = 'ASSE' - tzsource%clongname = 'time filter (Asselin)' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nasserr ) - - gcond = nmodel > 1 - tzsource%cmnhname = 'NEST' - tzsource%clongname = 'nesting' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nnestrr ) - - gcond = lforcing - tzsource%cmnhname = 'FRC' - tzsource%clongname = 'forcing' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nfrcrr ) - - gcond = onumdifth - tzsource%cmnhname = 'DIF' - tzsource%clongname = 'numerical diffusion' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, ndifrr ) - - gcond = ohorelax_rr - tzsource%cmnhname = 'REL' - tzsource%clongname = 'relaxation' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nrelrr ) - - gcond = hturb == 'TKEL' .and. ( hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) - tzsource%cmnhname = 'NETUR' - tzsource%clongname = 'negative correction induced by turbulence' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nneturrr ) - - gcond = lvisc .and. lvisc_r - tzsource%cmnhname = 'VISC' - tzsource%clongname = 'viscosity' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nviscrr ) - - gcond = .true. - tzsource%cmnhname = 'ADV' - tzsource%clongname = 'total advection' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nadvrr ) - - gcond = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' - tzsource%cmnhname = 'NEADV' - tzsource%clongname = 'negative correction induced by advection' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nneadvrr ) - - gcond = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' - tzsource%cmnhname = 'NEGA' - tzsource%clongname = 'negative correction' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nnegarr ) - - gcond = ( hcloud == 'LIMA' .and. lptsplit .and. lwarm_lima .and. lrain_lima ) & - .or. ( hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' ) - tzsource%cmnhname = 'CORR' - tzsource%clongname = 'correction' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, ncorrrr ) - - gcond = ( hcloud == 'LIMA' .and. lwarm_lima .and. lrain_lima ) & - .or. hcloud == 'KESS' & - .or. hcloud(1:3) == 'ICE' & - .or. hcloud == 'C2R2' & - .or. hcloud == 'KHKO' - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation of rain drops' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nsedirr ) - - gcond = hcloud == 'LIMA' .and. lptsplit .and. lwarm_lima .and. lrain_lima - tzsource%cmnhname = 'R2C1' - tzsource%clongname = 'rain to cloud after sedimentation' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nr2c1rr ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lwarm_lima .and. lrain_lima ) ) ) & - .or. hcloud == 'KESS' & - .or. ( hcloud(1:3) == 'ICE' .and. lwarm_ice ) & - .or. ( hcloud == 'C2R2' .and. lrain_c2r2 ) & - .or. ( hcloud == 'KHKO' .and. lrain_c2r2 ) - tzsource%cmnhname = 'AUTO' - tzsource%clongname = 'autoconversion into rain drops' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nautorr ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lwarm_lima .and. lrain_lima ) ) ) & - .or. hcloud == 'KESS' & - .or. ( hcloud(1:3) == 'ICE' .and. lwarm_ice ) & - .or. ( hcloud == 'C2R2' .and. lrain_c2r2 ) & - .or. ( hcloud == 'KHKO' .and. lrain_c2r2 ) - tzsource%cmnhname = 'ACCR' - tzsource%clongname = 'accretion of cloud droplets' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, naccrrr ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lwarm_lima .and. lrain_lima ) ) ) & - .or. hcloud == 'KESS' & - .or. ( hcloud(1:3) == 'ICE' .and. lwarm_ice ) & - .or. ( hcloud == 'C2R2' .and. lrain_c2r2 ) & - .or. ( hcloud == 'KHKO' .and. lrain_c2r2 ) - tzsource%cmnhname = 'REVA' - tzsource%clongname = 'rain evaporation' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nrevarr ) - - gcond = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima .and. lrain_lima ) ) - tzsource%cmnhname = 'HONR' - tzsource%clongname = 'rain homogeneous freezing' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nhonrrr ) - - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima .and. lrain_lima) ) ) & - .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'ACC' - tzsource%clongname = 'accretion of rain water on aggregates' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, naccrr ) - - gcond = hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'CMEL' - tzsource%clongname = 'collection of droplets by snow and conversion into rain' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, ncmelrr ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'CFRZ' - tzsource%clongname = 'conversion freezing of rain drops' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, ncfrzrr ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'WETG' - tzsource%clongname = 'wet growth of graupel' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nwetgrr ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'DRYG' - tzsource%clongname = 'dry growth of graupel' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, ndrygrr ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'GMLT' - tzsource%clongname = 'graupel melting' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, ngmltrr ) - - gcond = hcloud == 'LIMA' .and. lptsplit - tzsource%cmnhname = 'CVRC' - tzsource%clongname = 'rain to cloud change after other microphysical processes' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, ncvrcrr ) - - gcond = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima ) & - .or. hcloud == 'ICE4' - tzsource%cmnhname = 'WETH' - tzsource%clongname = 'wet growth of hail' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nwethrr ) - - gcond = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'DRYH' - tzsource%clongname = 'dry growth of hail' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, ndryhrr ) - - gcond = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima ) & - .or. hcloud == 'ICE4' - tzsource%cmnhname = 'HMLT' - tzsource%clongname = 'melting of hail' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nhmltrr ) - - gcond = hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'SFR' - tzsource%clongname = 'spontaneous freezing' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nsfrrr ) - - gcond = hcloud == 'LIMA' .and. lptsplit - tzsource%cmnhname = 'CORR2' - tzsource%clongname = 'supplementary correction inside LIMA splitting' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, ncorr2rr ) - - gcond = ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) & - .and. celec == 'NONE' - tzsource%cmnhname = 'NECON' - tzsource%clongname = 'negative correction induced by condensation' - call Budget_source_add( tbudgets(NBUDGET_RR), tzsource, gcond, nneconrr ) + tzsource%cmnhname = 'ASSE' + tzsource%clongname = 'time filter (Asselin)' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'NEST' + tzsource%clongname = 'nesting' + tzsource%lavailable = nmodel > 1 + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'FRC' + tzsource%clongname = 'forcing' + tzsource%lavailable = lforcing + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'DIF' + tzsource%clongname = 'numerical diffusion' + tzsource%lavailable = onumdifth + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'REL' + tzsource%clongname = 'relaxation' + tzsource%lavailable = ohorelax_rr + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'NETUR' + tzsource%clongname = 'negative correction induced by turbulence' + tzsource%lavailable = hturb == 'TKEL' .and. ( hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'VISC' + tzsource%clongname = 'viscosity' + tzsource%lavailable = lvisc .and. lvisc_r + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'ADV' + tzsource%clongname = 'total advection' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'NEADV' + tzsource%clongname = 'negative correction induced by advection' + tzsource%lavailable = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'NEGA' + tzsource%clongname = 'negative correction' + tzsource%lavailable = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'CORR' + tzsource%clongname = 'correction' + tzsource%lavailable = ( hcloud == 'LIMA' .and. lptsplit .and. lwarm_lima .and. lrain_lima ) & + .or. ( hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' ) + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation of rain drops' + tzsource%lavailable = ( hcloud == 'LIMA' .and. lwarm_lima .and. lrain_lima ) & + .or. hcloud == 'KESS' & + .or. hcloud(1:3) == 'ICE' & + .or. hcloud == 'C2R2' & + .or. hcloud == 'KHKO' + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'R2C1' + tzsource%clongname = 'rain to cloud after sedimentation' + tzsource%lavailable = hcloud == 'LIMA' .and. lptsplit .and. lwarm_lima .and. lrain_lima + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'AUTO' + tzsource%clongname = 'autoconversion into rain drops' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lwarm_lima .and. lrain_lima ) ) ) & + .or. hcloud == 'KESS' & + .or. ( hcloud(1:3) == 'ICE' .and. lwarm_ice ) & + .or. ( hcloud == 'C2R2' .and. lrain_c2r2 ) & + .or. ( hcloud == 'KHKO' .and. lrain_c2r2 ) + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'ACCR' + tzsource%clongname = 'accretion of cloud droplets' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lwarm_lima .and. lrain_lima ) ) ) & + .or. hcloud == 'KESS' & + .or. ( hcloud(1:3) == 'ICE' .and. lwarm_ice ) & + .or. ( hcloud == 'C2R2' .and. lrain_c2r2 ) & + .or. ( hcloud == 'KHKO' .and. lrain_c2r2 ) + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'REVA' + tzsource%clongname = 'rain evaporation' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lwarm_lima .and. lrain_lima ) ) ) & + .or. hcloud == 'KESS' & + .or. ( hcloud(1:3) == 'ICE' .and. lwarm_ice ) & + .or. ( hcloud == 'C2R2' .and. lrain_c2r2 ) & + .or. ( hcloud == 'KHKO' .and. lrain_c2r2 ) + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'HONR' + tzsource%clongname = 'rain homogeneous freezing' + tzsource%lavailable = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima .and. lrain_lima ) ) + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + + tzsource%cmnhname = 'ACC' + tzsource%clongname = 'accretion of rain water on aggregates' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima & + .and. lsnow_lima .and. lrain_lima) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'CMEL' + tzsource%clongname = 'collection of droplets by snow and conversion into rain' + tzsource%lavailable = hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'CFRZ' + tzsource%clongname = 'conversion freezing of rain drops' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'WETG' + tzsource%clongname = 'wet growth of graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'DRYG' + tzsource%clongname = 'dry growth of graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'GMLT' + tzsource%clongname = 'graupel melting' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'CVRC' + tzsource%clongname = 'rain to cloud change after other microphysical processes' + tzsource%lavailable = hcloud == 'LIMA' .and. lptsplit + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'WETH' + tzsource%clongname = 'wet growth of hail' + tzsource%lavailable = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima & + .and. lwarm_lima .and. lsnow_lima ) & + .or. hcloud == 'ICE4' + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'DRYH' + tzsource%clongname = 'dry growth of hail' + tzsource%lavailable = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'HMLT' + tzsource%clongname = 'melting of hail' + tzsource%lavailable = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima & + .and. lwarm_lima .and. lsnow_lima ) & + .or. hcloud == 'ICE4' + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'SFR' + tzsource%clongname = 'spontaneous freezing' + tzsource%lavailable = hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + +!PW: a documenter + tzsource%cmnhname = 'CORR2' + tzsource%clongname = 'supplementary correction inside LIMA splitting' + tzsource%lavailable = hcloud == 'LIMA' .and. lptsplit + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + tzsource%cmnhname = 'NECON' + tzsource%clongname = 'negative correction induced by condensation' + tzsource%lavailable = ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) & + .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RR), tzsource ) + + + call Sourcelist_sort_compact( tbudgets(NBUDGET_RR) ) + + call Sourcelist_scan( tbudgets(NBUDGET_RR), cbulist_rrr ) end if ! Budget of RRI @@ -1992,9 +2045,8 @@ if ( tbudgets(NBUDGET_RI)%lenabled ) then !Allocate all basic source terms (used or not) !The size should be large enough (bigger than necessary is OK) - isourcesmax = 42 - tbudgets(NBUDGET_RI)%nsourcesmax = isourcesmax - allocate( tbudgets(NBUDGET_RI)%tsources(isourcesmax) ) + tbudgets(NBUDGET_RI)%nsourcesmax = NSOURCESMAX + allocate( tbudgets(NBUDGET_RI)%tsources(NSOURCESMAX) ) allocate( tbudgets(NBUDGET_RI)%xtmpstore(ibudim1, ibudim2, ibudim3) ) @@ -2005,224 +2057,233 @@ if ( tbudgets(NBUDGET_RI)%lenabled ) then tzsource%cunits = 'kg kg-1' - gcond = .true. - tzsource%cmnhname = 'INIF' - tzsource%clongname = 'initial state' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'INIF' + tzsource%clongname = 'initial state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'ENDF' - tzsource%clongname = 'final state' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'ENDF' + tzsource%clongname = 'final state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'AVEF' - tzsource%clongname = 'averaged state' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .false. ) + tzsource%cmnhname = 'AVEF' + tzsource%clongname = 'averaged state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, odonotinit = .true., ooverwrite = .false. ) tzsource%cunits = 's-1' - gcond = .true. - tzsource%cmnhname = 'ASSE' - tzsource%clongname = 'time filter (Asselin)' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nasseri ) - - gcond = nmodel > 1 - tzsource%cmnhname = 'NEST' - tzsource%clongname = 'nesting' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nnestri ) - - gcond = lforcing - tzsource%cmnhname = 'FRC' - tzsource%clongname = 'forcing' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nfrcri ) - - gcond = onumdifth - tzsource%cmnhname = 'DIF' - tzsource%clongname = 'numerical diffusion' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, ndifri ) - - gcond = ohorelax_ri - tzsource%cmnhname = 'REL' - tzsource%clongname = 'relaxation' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nrelri ) - - gcond = hdconv == 'KAFR' .OR. hsconv == 'KAFR' - tzsource%cmnhname = 'DCONV' - tzsource%clongname = 'KAFR convection' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, ndconvri ) - - gcond = hturb == 'TKEL' - tzsource%cmnhname = 'VTURB' - tzsource%clongname = 'vertical turbulent diffusion' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nvturbri ) - - gcond = hturb == 'TKEL' .and. HTURBDIM == '3DIM' - tzsource%cmnhname = 'HTURB' - tzsource%clongname = 'horizontal turbulent diffusion' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nhturbri ) - - gcond = hturb == 'TKEL' .and. ( hcloud == 'ICE3' .or. hcloud == 'ICE4' .or. hcloud == 'LIMA' ) - tzsource%cmnhname = 'NETUR' - tzsource%clongname = 'negative correction induced by turbulence' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nneturri ) - - gcond = lvisc .and. lvisc_r - tzsource%cmnhname = 'VISC' - tzsource%clongname = 'viscosity' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nviscri ) - - gcond = .true. - tzsource%cmnhname = 'ADV' - tzsource%clongname = 'total advection' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nadvri ) - - gcond = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' - tzsource%cmnhname = 'NEADV' - tzsource%clongname = 'negative correction induced by advection' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nneadvri ) - - gcond = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' - tzsource%cmnhname = 'NEGA' - tzsource%clongname = 'negative correction' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nnegari ) - - gcond = ( hcloud == 'LIMA' .and. lptsplit .and. lcold_lima .and. lsnow_lima ) & - .or. ( hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' ) - tzsource%cmnhname = 'CORR' - tzsource%clongname = 'correction' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, ncorrri ) - - gcond = hcloud(1:3) == 'ICE' .and. lred .and. ladj_before .and. celec == 'NONE' - tzsource%cmnhname = 'ADJU' - tzsource%clongname = 'adjustment before on ice' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nadjuri ) - - gcond = ( hcloud == 'LIMA' .and. lcold_lima .and. lsedi_lima ) & - .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation of rain drops' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nsediri ) - - gcond = hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'HENU' - tzsource%clongname = 'heterogeneous nucleation' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nhenuri ) - - gcond = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima - tzsource%cmnhname = 'HIND' - tzsource%clongname = 'heterogeneous nucleation by deposition' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nhindri ) - - gcond = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima - tzsource%cmnhname = 'HINC' - tzsource%clongname = 'heterogeneous nucleation by contact' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nhincri ) - - gcond = hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'HON' - tzsource%clongname = 'homogeneous nucleation' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nhonri ) - - gcond = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima .and. lhhoni_lima .and. nmod_ccn >= 1 - tzsource%cmnhname = 'HONH' - tzsource%clongname = 'haze homogeneous nucleation' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nhonhri ) - - gcond = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima ) ) - tzsource%cmnhname = 'HONC' - tzsource%clongname = 'droplet homogeneous nucleation' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nhoncri ) - - gcond = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) - tzsource%cmnhname = 'CNVI' - tzsource%clongname = 'conversion of snow to cloud ice' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, ncnviri ) - - gcond = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) - tzsource%cmnhname = 'CNVS' - tzsource%clongname = 'conversion of pristine ice to snow' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, ncnvsri ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'AGGS' - tzsource%clongname = 'aggregation of snow' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, naggsri ) - - gcond = hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'AUTS' - tzsource%clongname = 'autoconversion of ice' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nautsri ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'IMLT' - tzsource%clongname = 'ice melting' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nimltri ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'BERFI' - tzsource%clongname = 'Bergeron-Findeisen' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nberfiri ) - - gcond = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) - tzsource%cmnhname = 'HMS' - tzsource%clongname = 'Hallett-Mossop ice multiplication process due to snow riming' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nhmsri ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'CFRZ' - tzsource%clongname = 'conversion freezing of rain drops' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, ncfrzri ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'WETG' - tzsource%clongname = 'wet growth of graupel' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nwetgri ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'DRYG' - tzsource%clongname = 'dry growth of graupel' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, ndrygri ) - - gcond = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) - tzsource%cmnhname = 'HMG' - tzsource%clongname = 'Hallett-Mossop ice multiplication process due to graupel riming' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nhmgri ) - - gcond = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima ) & - .or. hcloud == 'ICE4' - tzsource%cmnhname = 'WETH' - tzsource%clongname = 'wet growth of hail' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nwethri ) - - gcond = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'DRYH' - tzsource%clongname = 'dry growth of hail' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, ndryhri ) - - gcond = hcloud == 'LIMA' - tzsource%cmnhname = 'CEDS' - tzsource%clongname = 'adjustment to saturation' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, ncedsri ) - - gcond = hcloud(1:3) == 'ICE' .and. ( .not. lred .or. ( lred .and. ladj_after ) .or. celec /= 'NONE' ) - tzsource%cmnhname = 'CDEPI' - tzsource%clongname = 'condensation/deposition on ice' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, ncdepiri ) - - gcond = hcloud == 'LIMA' .and. lptsplit - tzsource%cmnhname = 'CORR2' - tzsource%clongname = 'supplementary correction inside LIMA splitting' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, ncorr2ri ) - - gcond = ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) & - .and. celec == 'NONE' - tzsource%cmnhname = 'NECON' - tzsource%clongname = 'negative correction induced by condensation' - call Budget_source_add( tbudgets(NBUDGET_RI), tzsource, gcond, nneconri ) + tzsource%cmnhname = 'ASSE' + tzsource%clongname = 'time filter (Asselin)' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'NEST' + tzsource%clongname = 'nesting' + tzsource%lavailable = nmodel > 1 + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'FRC' + tzsource%clongname = 'forcing' + tzsource%lavailable = lforcing + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'DIF' + tzsource%clongname = 'numerical diffusion' + tzsource%lavailable = onumdifth + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'REL' + tzsource%clongname = 'relaxation' + tzsource%lavailable = ohorelax_ri + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'DCONV' + tzsource%clongname = 'KAFR convection' + tzsource%lavailable = hdconv == 'KAFR' .OR. hsconv == 'KAFR' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'VTURB' + tzsource%clongname = 'vertical turbulent diffusion' + tzsource%lavailable = hturb == 'TKEL' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'HTURB' + tzsource%clongname = 'horizontal turbulent diffusion' + tzsource%lavailable = hturb == 'TKEL' .and. HTURBDIM == '3DIM' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'NETUR' + tzsource%clongname = 'negative correction induced by turbulence' + tzsource%lavailable = hturb == 'TKEL' .and. ( hcloud == 'ICE3' .or. hcloud == 'ICE4' .or. hcloud == 'LIMA' ) + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'VISC' + tzsource%clongname = 'viscosity' + tzsource%lavailable = lvisc .and. lvisc_r + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'ADV' + tzsource%clongname = 'total advection' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'NEADV' + tzsource%clongname = 'negative correction induced by advection' + tzsource%lavailable = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'NEGA' + tzsource%clongname = 'negative correction' + tzsource%lavailable = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'CORR' + tzsource%clongname = 'correction' + tzsource%lavailable = ( hcloud == 'LIMA' .and. lptsplit .and. lcold_lima .and. lsnow_lima ) & + .or. ( hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' ) + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'ADJU' + tzsource%clongname = 'adjustment before on ice' + tzsource%lavailable = hcloud(1:3) == 'ICE' .and. lred .and. ladj_before .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation of rain drops' + tzsource%lavailable = ( hcloud == 'LIMA' .and. lcold_lima .and. lsedi_lima ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'HENU' + tzsource%clongname = 'heterogeneous nucleation' + tzsource%lavailable = hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'HIND' + tzsource%clongname = 'heterogeneous nucleation by deposition' + tzsource%lavailable = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'HINC' + tzsource%clongname = 'heterogeneous nucleation by contact' + tzsource%lavailable = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'HON' + tzsource%clongname = 'homogeneous nucleation' + tzsource%lavailable = hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'HONH' + tzsource%clongname = 'haze homogeneous nucleation' + tzsource%lavailable = hcloud == 'LIMA' .and. lcold_lima .and. lnucl_lima .and. lhhoni_lima .and. nmod_ccn >= 1 + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'HONC' + tzsource%clongname = 'droplet homogeneous nucleation' + tzsource%lavailable = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima ) ) + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'CNVI' + tzsource%clongname = 'conversion of snow to cloud ice' + tzsource%lavailable = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'CNVS' + tzsource%clongname = 'conversion of pristine ice to snow' + tzsource%lavailable = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'AGGS' + tzsource%clongname = 'aggregation of snow' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'AUTS' + tzsource%clongname = 'autoconversion of ice' + tzsource%lavailable = hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'IMLT' + tzsource%clongname = 'ice melting' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima ) ) ) .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'BERFI' + tzsource%clongname = 'Bergeron-Findeisen' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima ) ) ) .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'HMS' + tzsource%clongname = 'Hallett-Mossop ice multiplication process due to snow riming' + tzsource%lavailable = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'CFRZ' + tzsource%clongname = 'conversion freezing of rain drops' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'WETG' + tzsource%clongname = 'wet growth of graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'DRYG' + tzsource%clongname = 'dry growth of graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'HMG' + tzsource%clongname = 'Hallett-Mossop ice multiplication process due to graupel riming' + tzsource%lavailable = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'WETH' + tzsource%clongname = 'wet growth of hail' + tzsource%lavailable = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima & + .and. lwarm_lima .and. lsnow_lima ) & + .or. hcloud == 'ICE4' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'DRYH' + tzsource%clongname = 'dry growth of hail' + tzsource%lavailable = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'CEDS' + tzsource%clongname = 'adjustment to saturation' + tzsource%lavailable = hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'CDEPI' + tzsource%clongname = 'condensation/deposition on ice' + tzsource%lavailable = hcloud(1:3) == 'ICE' .and. ( .not. lred .or. ( lred .and. ladj_after ) .or. celec /= 'NONE' ) + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'CORR2' + tzsource%clongname = 'supplementary correction inside LIMA splitting' + tzsource%lavailable = hcloud == 'LIMA' .and. lptsplit + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + tzsource%cmnhname = 'NECON' + tzsource%clongname = 'negative correction induced by condensation' + tzsource%lavailable = ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) & + .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RI), tzsource ) + + + call Sourcelist_sort_compact( tbudgets(NBUDGET_RI) ) + + call Sourcelist_scan( tbudgets(NBUDGET_RI), cbulist_rri ) end if ! Budget of RRS @@ -2233,9 +2294,8 @@ if ( tbudgets(NBUDGET_RS)%lenabled ) then !Allocate all basic source terms (used or not) !The size should be large enough (bigger than necessary is OK) - isourcesmax = 28 - tbudgets(NBUDGET_RS)%nsourcesmax = isourcesmax - allocate( tbudgets(NBUDGET_RS)%tsources(isourcesmax) ) + tbudgets(NBUDGET_RS)%nsourcesmax = NSOURCESMAX + allocate( tbudgets(NBUDGET_RS)%tsources(NSOURCESMAX) ) allocate( tbudgets(NBUDGET_RS)%xtmpstore(ibudim1, ibudim2, ibudim3) ) @@ -2246,161 +2306,172 @@ if ( tbudgets(NBUDGET_RS)%lenabled ) then tzsource%cunits = 'kg kg-1' - gcond = .true. - tzsource%cmnhname = 'INIF' - tzsource%clongname = 'initial state' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'INIF' + tzsource%clongname = 'initial state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'ENDF' - tzsource%clongname = 'final state' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'ENDF' + tzsource%clongname = 'final state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'AVEF' - tzsource%clongname = 'averaged state' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .false. ) + tzsource%cmnhname = 'AVEF' + tzsource%clongname = 'averaged state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, odonotinit = .true., ooverwrite = .false. ) tzsource%cunits = 's-1' - gcond = .true. - tzsource%cmnhname = 'ASSE' - tzsource%clongname = 'time filter (Asselin)' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, nassers ) - - gcond = nmodel > 1 - tzsource%cmnhname = 'NEST' - tzsource%clongname = 'nesting' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, nnestrs ) - - gcond = lforcing - tzsource%cmnhname = 'FRC' - tzsource%clongname = 'forcing' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, nfrcrs ) - - gcond = onumdifth - tzsource%cmnhname = 'DIF' - tzsource%clongname = 'numerical diffusion' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, ndifrs ) - - gcond = ohorelax_rs - tzsource%cmnhname = 'REL' - tzsource%clongname = 'relaxation' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, nrelrs ) - -! gcond = hturb == 'TKEL' .and. ( hcloud == 'ICE3' .or. hcloud == 'ICE4' & + tzsource%cmnhname = 'ASSE' + tzsource%clongname = 'time filter (Asselin)' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'NEST' + tzsource%clongname = 'nesting' + tzsource%lavailable = nmodel > 1 + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'FRC' + tzsource%clongname = 'forcing' + tzsource%lavailable = lforcing + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'DIF' + tzsource%clongname = 'numerical diffusion' + tzsource%lavailable = onumdifth + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'REL' + tzsource%clongname = 'relaxation' + tzsource%lavailable = ohorelax_rs + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + +! tzsource%cmnhname = 'NETUR' +! tzsource%clongname = 'negative correction induced by turbulence' +! tzsource%lavailable = hturb == 'TKEL' .and. ( hcloud == 'ICE3' .or. hcloud == 'ICE4' & ! .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) -! tzsource%cmnhname = 'NETUR' -! tzsource%clongname = 'negative correction induced by turbulence' -! call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, nneturrs ) - - gcond = lvisc .and. lvisc_r - tzsource%cmnhname = 'VISC' - tzsource%clongname = 'viscosity' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, nviscrs ) - - gcond = .true. - tzsource%cmnhname = 'ADV' - tzsource%clongname = 'total advection' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, nadvrs ) - - gcond = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' - tzsource%cmnhname = 'NEADV' - tzsource%clongname = 'negative correction induced by advection' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, nneadvrs ) - - gcond = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' - tzsource%cmnhname = 'NEGA' - tzsource%clongname = 'negative correction' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, nnegars ) - - gcond = ( hcloud == 'LIMA' .and. lptsplit .and. lcold_lima .and. lsnow_lima ) & - .or. ( hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' ) - tzsource%cmnhname = 'CORR' - tzsource%clongname = 'correction' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, ncorrrs ) - - gcond = ( hcloud == 'LIMA' .and. lcold_lima .and. lsnow_lima ) & - .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, nsedirs ) - - gcond = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) - tzsource%cmnhname = 'CNVI' - tzsource%clongname = 'conversion of snow to cloud ice' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, ncnvirs ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'DEPS' - tzsource%clongname = 'deposition on snow' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, ndepsrs ) - - gcond = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) - tzsource%cmnhname = 'CNVS' - tzsource%clongname = 'conversion of pristine ice to snow' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, ncnvsrs ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'AGGS' - tzsource%clongname = 'aggregation of snow' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, naggsrs ) - - gcond = hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'AUTS' - tzsource%clongname = 'autoconversion of ice' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, nautsrs ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'RIM' - tzsource%clongname = 'riming of cloud water' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, nrimrs ) - - gcond = hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) - tzsource%cmnhname = 'HMS' - tzsource%clongname = 'Hallett-Mossop ice multiplication process due to snow riming' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, nhmsrs ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima .and. lrain_lima) ) ) & - .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'ACC' - tzsource%clongname = 'accretion of rain water' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, naccrs ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'CMEL' - tzsource%clongname = 'conversion melting' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, ncmelrs ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'WETG' - tzsource%clongname = 'wet growth of graupel' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, nwetgrs ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'DRYG' - tzsource%clongname = 'dry growth of graupel' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, ndrygrs ) - - gcond = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima ) & - .or. hcloud == 'ICE4' - tzsource%cmnhname = 'WETH' - tzsource%clongname = 'wet growth of hail' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, nwethrs ) - - gcond = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'DRYH' - tzsource%clongname = 'dry growth of hail' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, ndryhrs ) - - gcond = ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) & - .and. celec == 'NONE' - tzsource%cmnhname = 'NECON' - tzsource%clongname = 'negative correction induced by condensation' - call Budget_source_add( tbudgets(NBUDGET_RS), tzsource, gcond, nneconrs ) +! call Budget_source_add( tbudgets(NBUDGET_RS), tzsource nneturrs ) + + tzsource%cmnhname = 'VISC' + tzsource%clongname = 'viscosity' + tzsource%lavailable = lvisc .and. lvisc_r + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'ADV' + tzsource%clongname = 'total advection' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'NEADV' + tzsource%clongname = 'negative correction induced by advection' + tzsource%lavailable = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'NEGA' + tzsource%clongname = 'negative correction' + tzsource%lavailable = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'CORR' + tzsource%clongname = 'correction' + tzsource%lavailable = ( hcloud == 'LIMA' .and. lptsplit .and. lcold_lima .and. lsnow_lima ) & + .or. ( hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' ) + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation' + tzsource%lavailable = ( hcloud == 'LIMA' .and. lcold_lima .and. lsnow_lima ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'CNVI' + tzsource%clongname = 'conversion of snow to cloud ice' + tzsource%lavailable = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'DEPS' + tzsource%clongname = 'deposition on snow' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'CNVS' + tzsource%clongname = 'conversion of pristine ice to snow' + tzsource%lavailable = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'AGGS' + tzsource%clongname = 'aggregation of snow' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'AUTS' + tzsource%clongname = 'autoconversion of ice' + tzsource%lavailable = hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'RIM' + tzsource%clongname = 'riming of cloud water' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'HMS' + tzsource%clongname = 'Hallett-Mossop ice multiplication process due to snow riming' + tzsource%lavailable = hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'ACC' + tzsource%clongname = 'accretion of rain water' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima & + .and. lsnow_lima .and. lrain_lima) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'CMEL' + tzsource%clongname = 'conversion melting' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'WETG' + tzsource%clongname = 'wet growth of graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'DRYG' + tzsource%clongname = 'dry growth of graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'WETH' + tzsource%clongname = 'wet growth of hail' + tzsource%lavailable = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima & + .and. lwarm_lima .and. lsnow_lima ) & + .or. hcloud == 'ICE4' + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'DRYH' + tzsource%clongname = 'dry growth of hail' + tzsource%lavailable = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + tzsource%cmnhname = 'NECON' + tzsource%clongname = 'negative correction induced by condensation' + tzsource%lavailable = ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) & + .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RS), tzsource ) + + + call Sourcelist_sort_compact( tbudgets(NBUDGET_RS) ) + + call Sourcelist_scan( tbudgets(NBUDGET_RS), cbulist_rrs ) end if ! Budget of RRG @@ -2411,9 +2482,8 @@ if ( tbudgets(NBUDGET_RG)%lenabled ) then !Allocate all basic source terms (used or not) !The size should be large enough (bigger than necessary is OK) - isourcesmax = 31 - tbudgets(NBUDGET_RG)%nsourcesmax = isourcesmax - allocate( tbudgets(NBUDGET_RG)%tsources(isourcesmax) ) + tbudgets(NBUDGET_RG)%nsourcesmax = NSOURCESMAX + allocate( tbudgets(NBUDGET_RG)%tsources(NSOURCESMAX) ) allocate( tbudgets(NBUDGET_RG)%xtmpstore(ibudim1, ibudim2, ibudim3) ) @@ -2424,175 +2494,189 @@ if ( tbudgets(NBUDGET_RG)%lenabled ) then tzsource%cunits = 'kg kg-1' - gcond = .true. - tzsource%cmnhname = 'INIF' - tzsource%clongname = 'initial state' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'INIF' + tzsource%clongname = 'initial state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'ENDF' - tzsource%clongname = 'final state' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'ENDF' + tzsource%clongname = 'final state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'AVEF' - tzsource%clongname = 'averaged state' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .false. ) + tzsource%cmnhname = 'AVEF' + tzsource%clongname = 'averaged state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, odonotinit = .true., ooverwrite = .false. ) tzsource%cunits = 's-1' - gcond = .true. - tzsource%cmnhname = 'ASSE' - tzsource%clongname = 'time filter (Asselin)' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nasserg ) - - gcond = nmodel > 1 - tzsource%cmnhname = 'NEST' - tzsource%clongname = 'nesting' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nnestrg ) - - gcond = lforcing - tzsource%cmnhname = 'FRC' - tzsource%clongname = 'forcing' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nfrcrg ) - - gcond = onumdifth - tzsource%cmnhname = 'DIF' - tzsource%clongname = 'numerical diffusion' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, ndifrg ) - - gcond = ohorelax_rg - tzsource%cmnhname = 'REL' - tzsource%clongname = 'relaxation' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nrelrg ) - -! gcond = hturb == 'TKEL' .and. ( hcloud == 'ICE3' .or. hcloud == 'ICE4' & + tzsource%cmnhname = 'ASSE' + tzsource%clongname = 'time filter (Asselin)' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'NEST' + tzsource%clongname = 'nesting' + tzsource%lavailable = nmodel > 1 + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'FRC' + tzsource%clongname = 'forcing' + tzsource%lavailable = lforcing + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'DIF' + tzsource%clongname = 'numerical diffusion' + tzsource%lavailable = onumdifth + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'REL' + tzsource%clongname = 'relaxation' + tzsource%lavailable = ohorelax_rg + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + +! tzsource%cmnhname = 'NETUR' +! tzsource%clongname = 'negative correction induced by turbulence' +! tzsource%lavailable = hturb == 'TKEL' .and. ( hcloud == 'ICE3' .or. hcloud == 'ICE4' & ! .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) -! tzsource%cmnhname = 'NETUR' -! tzsource%clongname = 'negative correction induced by turbulence' -! call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nneturrg ) - - gcond = lvisc .and. lvisc_r - tzsource%cmnhname = 'VISC' - tzsource%clongname = 'viscosity' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nviscrg ) - - gcond = .true. - tzsource%cmnhname = 'ADV' - tzsource%clongname = 'total advection' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nadvrg ) - - gcond = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' - tzsource%cmnhname = 'NEADV' - tzsource%clongname = 'negative correction induced by advection' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nneadvrg ) - - gcond = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' - tzsource%cmnhname = 'NEGA' - tzsource%clongname = 'negative correction' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nnegarg ) - - gcond = hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'CORR' - tzsource%clongname = 'correction' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, ncorrrg ) - - gcond = ( hcloud == 'LIMA' .and. lcold_lima .and. lsnow_lima ) & - .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nsedirg ) - - gcond = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima .and. lrain_lima ) ) - tzsource%cmnhname = 'HONR' - tzsource%clongname = 'rain homogeneous freezing' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nhonrrg ) - - gcond = hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'SFR' - tzsource%clongname = 'spontaneous freezing' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nsfrrg ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'DEPG' - tzsource%clongname = 'deposition on graupel' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, ndepgrg ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'RIM' - tzsource%clongname = 'riming of cloud water' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nrimrg ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima .and. lrain_lima) ) ) & - .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'ACC' - tzsource%clongname = 'rain accretion on graupel' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, naccrg ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'CMEL' - tzsource%clongname = 'conversion melting of snow' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, ncmelrg ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'CFRZ' - tzsource%clongname = 'conversion freezing of rain' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, ncfrzrg ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'WETG' - tzsource%clongname = 'wet growth of graupel' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nwetgrg ) - - gcond = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'GHCV' - tzsource%clongname = 'graupel to hail conversion' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nghcvrg ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'DRYG' - tzsource%clongname = 'dry growth of graupel' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, ndrygrg ) - - gcond = hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) - tzsource%cmnhname = 'HMG' - tzsource%clongname = 'Hallett-Mossop ice multiplication process due to graupel riming' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nhmgrg ) - - gcond = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) .or. hcloud(1:3) == 'ICE' - tzsource%cmnhname = 'GMLT' - tzsource%clongname = 'graupel melting' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, ngmltrg ) - - gcond = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima ) & - .or. hcloud == 'ICE4' - tzsource%cmnhname = 'WETH' - tzsource%clongname = 'wet growth of hail' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nwethrg ) - - gcond = hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima - tzsource%cmnhname = 'COHG' - tzsource%clongname = 'conversion of hail to graupel' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, ncohgrg ) - - gcond = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'HGCV' - tzsource%clongname = 'hail to graupel conversion' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nhgcvrg ) - - gcond = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'DRYH' - tzsource%clongname = 'dry growth of hail' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, ndryhrg ) - - gcond = ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) & - .and. celec == 'NONE' - tzsource%cmnhname = 'NECON' - tzsource%clongname = 'negative correction induced by condensation' - call Budget_source_add( tbudgets(NBUDGET_RG), tzsource, gcond, nneconrg ) +! call Budget_source_add( tbudgets(NBUDGET_RG), tzsource nneturrg ) + + tzsource%cmnhname = 'VISC' + tzsource%clongname = 'viscosity' + tzsource%lavailable = lvisc .and. lvisc_r + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'ADV' + tzsource%clongname = 'total advection' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'NEADV' + tzsource%clongname = 'negative correction induced by advection' + tzsource%lavailable = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'NEGA' + tzsource%clongname = 'negative correction' + tzsource%lavailable = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'CORR' + tzsource%clongname = 'correction' + tzsource%lavailable = hcloud(1:3) == 'ICE' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation' + tzsource%lavailable = ( hcloud == 'LIMA' .and. lcold_lima .and. lsnow_lima ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'HONR' + tzsource%clongname = 'rain homogeneous freezing' + tzsource%lavailable = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima .and. lrain_lima ) ) + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'SFR' + tzsource%clongname = 'spontaneous freezing' + tzsource%lavailable = hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'DEPG' + tzsource%clongname = 'deposition on graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'RIM' + tzsource%clongname = 'riming of cloud water' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'ACC' + tzsource%clongname = 'rain accretion on graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima & + .and. lsnow_lima .and. lrain_lima) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'CMEL' + tzsource%clongname = 'conversion melting of snow' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'CFRZ' + tzsource%clongname = 'conversion freezing of rain' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'WETG' + tzsource%clongname = 'wet growth of graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'GHCV' + tzsource%clongname = 'graupel to hail conversion' + tzsource%lavailable = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'DRYG' + tzsource%clongname = 'dry growth of graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'HMG' + tzsource%clongname = 'Hallett-Mossop ice multiplication process due to graupel riming' + tzsource%lavailable = hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'GMLT' + tzsource%clongname = 'graupel melting' + tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) & + .or. hcloud(1:3) == 'ICE' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'WETH' + tzsource%clongname = 'wet growth of hail' + tzsource%lavailable = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima & + .and. lwarm_lima .and. lsnow_lima ) & + .or. hcloud == 'ICE4' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'COHG' + tzsource%clongname = 'conversion of hail to graupel' + tzsource%lavailable = hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'HGCV' + tzsource%clongname = 'hail to graupel conversion' + tzsource%lavailable = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'DRYH' + tzsource%clongname = 'dry growth of hail' + tzsource%lavailable = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + tzsource%cmnhname = 'NECON' + tzsource%clongname = 'negative correction induced by condensation' + tzsource%lavailable = ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) & + .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RG), tzsource ) + + + call Sourcelist_sort_compact( tbudgets(NBUDGET_RG) ) + + call Sourcelist_scan( tbudgets(NBUDGET_RG), cbulist_rrg ) end if ! Budget of RRH @@ -2603,9 +2687,8 @@ if ( tbudgets(NBUDGET_RH)%lenabled ) then !Allocate all basic source terms (used or not) !The size should be large enough (bigger than necessary is OK) - isourcesmax = 22 - tbudgets(NBUDGET_RH)%nsourcesmax = isourcesmax - allocate( tbudgets(NBUDGET_RH)%tsources(isourcesmax) ) + tbudgets(NBUDGET_RH)%nsourcesmax = NSOURCESMAX + allocate( tbudgets(NBUDGET_RH)%tsources(NSOURCESMAX) ) allocate( tbudgets(NBUDGET_RH)%xtmpstore(ibudim1, ibudim2, ibudim3) ) @@ -2616,131 +2699,140 @@ if ( tbudgets(NBUDGET_RH)%lenabled ) then tzsource%cunits = 'kg kg-1' - gcond = .true. - tzsource%cmnhname = 'INIF' - tzsource%clongname = 'initial state' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'INIF' + tzsource%clongname = 'initial state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'ENDF' - tzsource%clongname = 'final state' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'ENDF' + tzsource%clongname = 'final state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'AVEF' - tzsource%clongname = 'averaged state' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .false. ) + tzsource%cmnhname = 'AVEF' + tzsource%clongname = 'averaged state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, odonotinit = .true., ooverwrite = .false. ) tzsource%cunits = 's-1' - gcond = .true. - tzsource%cmnhname = 'ASSE' - tzsource%clongname = 'time filter (Asselin)' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, nasserh ) - - gcond = nmodel > 1 - tzsource%cmnhname = 'NEST' - tzsource%clongname = 'nesting' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, nnestrh ) - - gcond = lforcing - tzsource%cmnhname = 'FRC' - tzsource%clongname = 'forcing' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, nfrcrh ) - - gcond = onumdifth - tzsource%cmnhname = 'DIF' - tzsource%clongname = 'numerical diffusion' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, ndifrh ) - - gcond = ohorelax_rh - tzsource%cmnhname = 'REL' - tzsource%clongname = 'relaxation' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, nrelrh ) - -! gcond = hturb == 'TKEL' .and. ( hcloud == 'ICE3' .or. hcloud == 'ICE4' & + tzsource%cmnhname = 'ASSE' + tzsource%clongname = 'time filter (Asselin)' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'NEST' + tzsource%clongname = 'nesting' + tzsource%lavailable = nmodel > 1 + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'FRC' + tzsource%clongname = 'forcing' + tzsource%lavailable = lforcing + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'DIF' + tzsource%clongname = 'numerical diffusion' + tzsource%lavailable = onumdifth + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'REL' + tzsource%clongname = 'relaxation' + tzsource%lavailable = ohorelax_rh + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + +! tzsource%cmnhname = 'NETUR' +! tzsource%clongname = 'negative correction induced by turbulence' +! tzsource%lavailable = hturb == 'TKEL' .and. ( hcloud == 'ICE3' .or. hcloud == 'ICE4' & ! .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) -! tzsource%cmnhname = 'NETUR' -! tzsource%clongname = 'negative correction induced by turbulence' -! call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, nneturrh ) - - gcond = lvisc .and. lvisc_r - tzsource%cmnhname = 'VISC' - tzsource%clongname = 'viscosity' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, nviscrh ) - - gcond = .true. - tzsource%cmnhname = 'ADV' - tzsource%clongname = 'total advection' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, nadvrh ) - - gcond = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' - tzsource%cmnhname = 'NEADV' - tzsource%clongname = 'negative correction induced by advection' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, nneadvrh ) - - gcond = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' - tzsource%cmnhname = 'NEGA' - tzsource%clongname = 'negative correction' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, nnegarh ) - - gcond = ( hcloud == 'LIMA' .and. lcold_lima .and. lhail_lima ) & - .or. hcloud == 'ICE4' - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, nsedirh ) - - gcond = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'GHCV' - tzsource%clongname = 'graupel to hail conversion' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, nghcvrh ) - - gcond = ( hcloud == 'LIMA' .and. lhail_lima .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & - .or. ( hcloud == 'ICE4' .and. ( .not. lred .or. celec /= 'NONE' ) ) - tzsource%cmnhname = 'WETG' - tzsource%clongname = 'wet growth of graupel' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, nwetgrh ) - - gcond = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima ) & - .or. hcloud == 'ICE4' - tzsource%cmnhname = 'WETH' - tzsource%clongname = 'wet growth of hail' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, nwethrh ) - - gcond = hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima - tzsource%cmnhname = 'COHG' - tzsource%clongname = 'conversion from hail to graupel' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, ncohgrh ) - - gcond = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'HGCV' - tzsource%clongname = 'hail to graupel conversion' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, nhgcvrh ) - - gcond = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'DRYH' - tzsource%clongname = 'dry growth of hail' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, ndryhrh ) - - gcond = ( hcloud == 'LIMA' .and. .not. lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima ) & - .or. hcloud == 'ICE4' - tzsource%cmnhname = 'HMLT' - tzsource%clongname = 'melting of hail' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, nhmltrh ) - - gcond = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' - tzsource%cmnhname = 'CORR' - tzsource%clongname = 'correction' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, ncorrrh ) - - gcond = ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & - .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) & - .and. celec == 'NONE' - tzsource%cmnhname = 'NECON' - tzsource%clongname = 'negative correction induced by condensation' - call Budget_source_add( tbudgets(NBUDGET_RH), tzsource, gcond, nneconrh ) +! call Budget_source_add( tbudgets(NBUDGET_RH), tzsource nneturrh ) + + tzsource%cmnhname = 'VISC' + tzsource%clongname = 'viscosity' + tzsource%lavailable = lvisc .and. lvisc_r + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'ADV' + tzsource%clongname = 'total advection' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'NEADV' + tzsource%clongname = 'negative correction induced by advection' + tzsource%lavailable = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'NEGA' + tzsource%clongname = 'negative correction' + tzsource%lavailable = hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation' + tzsource%lavailable = ( hcloud == 'LIMA' .and. lcold_lima .and. lhail_lima ) & + .or. hcloud == 'ICE4' + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'GHCV' + tzsource%clongname = 'graupel to hail conversion' + tzsource%lavailable = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'WETG' + tzsource%clongname = 'wet growth of graupel' + tzsource%lavailable = ( hcloud == 'LIMA' .and. lhail_lima & + .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) & + .or. ( hcloud == 'ICE4' .and. ( .not. lred .or. celec /= 'NONE' ) ) + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'WETH' + tzsource%clongname = 'wet growth of hail' + tzsource%lavailable = ( hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima & + .and. lwarm_lima .and. lsnow_lima ) & + .or. hcloud == 'ICE4' + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'COHG' + tzsource%clongname = 'conversion from hail to graupel' + tzsource%lavailable = hcloud == 'LIMA' .and. .not.lptsplit .and. lhail_lima .and. lcold_lima & + .and. lwarm_lima .and. lsnow_lima + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'HGCV' + tzsource%clongname = 'hail to graupel conversion' + tzsource%lavailable = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'DRYH' + tzsource%clongname = 'dry growth of hail' + tzsource%lavailable = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'HMLT' + tzsource%clongname = 'melting of hail' + tzsource%lavailable = ( hcloud == 'LIMA' .and. .not. lptsplit .and. lhail_lima .and. lcold_lima & + .and. lwarm_lima .and. lsnow_lima ) & + .or. hcloud == 'ICE4' + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'CORR' + tzsource%clongname = 'correction' + tzsource%lavailable = hcloud == 'ICE4' .and. lred .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + tzsource%cmnhname = 'NECON' + tzsource%clongname = 'negative correction induced by condensation' + tzsource%lavailable = ( hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' & + .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) & + .and. celec == 'NONE' + call Budget_source_add( tbudgets(NBUDGET_RH), tzsource ) + + + call Sourcelist_sort_compact( tbudgets(NBUDGET_RH) ) + + call Sourcelist_scan( tbudgets(NBUDGET_RH), cbulist_rrh ) end if ! Budgets of RSV (scalar variables) @@ -2757,9 +2849,8 @@ SV_BUDGETS: do jsv = 1, ksv !Allocate all basic source terms (used or not) !The size should be large enough (bigger than necessary is OK) - isourcesmax = 38 - tbudgets(ibudget)%nsourcesmax = isourcesmax - allocate( tbudgets(ibudget)%tsources(isourcesmax) ) + tbudgets(ibudget)%nsourcesmax = NSOURCESMAX + allocate( tbudgets(ibudget)%tsources(NSOURCESMAX) ) allocate( tbudgets(ibudget)%xtmpstore(ibudim1, ibudim2, ibudim3) ) @@ -2770,85 +2861,85 @@ SV_BUDGETS: do jsv = 1, ksv tzsource%cunits = '1' - gcond = .true. - tzsource%cmnhname = 'INIF' - tzsource%clongname = 'initial state' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'INIF' + tzsource%clongname = 'initial state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'ENDF' - tzsource%clongname = 'final state' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .true. ) + tzsource%cmnhname = 'ENDF' + tzsource%clongname = 'final state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource, odonotinit = .true., ooverwrite = .true. ) - gcond = .true. - tzsource%cmnhname = 'AVEF' - tzsource%clongname = 'averaged state' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, 1, odonotinit = .true., ooverwrite = .false. ) + tzsource%cmnhname = 'AVEF' + tzsource%clongname = 'averaged state' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource, odonotinit = .true., ooverwrite = .false. ) tzsource%cunits = 's-1' - gcond = .true. - tzsource%cmnhname = 'ASSE' - tzsource%clongname = 'time filter (Asselin)' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nassesv ) - - gcond = nmodel > 1 - tzsource%cmnhname = 'NEST' - tzsource%clongname = 'nesting' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nnestsv ) - - gcond = lforcing - tzsource%cmnhname = 'FRC' - tzsource%clongname = 'forcing' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nfrcsv ) - - gcond = onumdifsv - tzsource%cmnhname = 'DIF' - tzsource%clongname = 'numerical diffusion' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndifsv ) - - gcond = ohorelax_sv( jsv ) .or. ( celec /= 'NONE' .and. lrelax2fw_ion .and. (jsv == nsv_elecbeg .or. jsv == nsv_elecend ) ) - tzsource%cmnhname = 'REL' - tzsource%clongname = 'relaxation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nrelsv ) - - gcond = ( hdconv == 'KAFR' .or. hsconv == 'KAFR' ) .and. ochtrans - tzsource%cmnhname = 'DCONV' - tzsource%clongname = 'KAFR convection' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndconvsv ) - - gcond = hturb == 'TKEL' - tzsource%cmnhname = 'VTURB' - tzsource%clongname = 'vertical turbulent diffusion' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nvturbsv ) - - gcond = hturb == 'TKEL' .and. HTURBDIM == '3DIM' - tzsource%cmnhname = 'HTURB' - tzsource%clongname = 'horizontal turbulent diffusion' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nhturbsv ) - - gcond = hsconv == 'EDKF' - tzsource%cmnhname = 'MAFL' - tzsource%clongname = 'mass flux' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nmaflsv ) - - gcond = lvisc .and. lvisc_sv - tzsource%cmnhname = 'VISC' - tzsource%clongname = 'viscosity' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nviscsv ) - - gcond = .true. - tzsource%cmnhname = 'ADV' - tzsource%clongname = 'total advection' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nadvsv ) - - gcond = .true. - tzsource%cmnhname = 'NEGA2' - tzsource%clongname = 'negative correction' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nnega2sv ) + tzsource%cmnhname = 'ASSE' + tzsource%clongname = 'time filter (Asselin)' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'NEST' + tzsource%clongname = 'nesting' + tzsource%lavailable = nmodel > 1 + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'FRC' + tzsource%clongname = 'forcing' + tzsource%lavailable = lforcing + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'DIF' + tzsource%clongname = 'numerical diffusion' + tzsource%lavailable = onumdifsv + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'REL' + tzsource%clongname = 'relaxation' + tzsource%lavailable = ohorelax_sv( jsv ) .or. ( celec /= 'NONE' .and. lrelax2fw_ion & + .and. (jsv == nsv_elecbeg .or. jsv == nsv_elecend ) ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'DCONV' + tzsource%clongname = 'KAFR convection' + tzsource%lavailable = ( hdconv == 'KAFR' .or. hsconv == 'KAFR' ) .and. ochtrans + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'VTURB' + tzsource%clongname = 'vertical turbulent diffusion' + tzsource%lavailable = hturb == 'TKEL' + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'HTURB' + tzsource%clongname = 'horizontal turbulent diffusion' + tzsource%lavailable = hturb == 'TKEL' .and. HTURBDIM == '3DIM' + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'MAFL' + tzsource%clongname = 'mass flux' + tzsource%lavailable = hsconv == 'EDKF' + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'VISC' + tzsource%clongname = 'viscosity' + tzsource%lavailable = lvisc .and. lvisc_sv + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'ADV' + tzsource%clongname = 'total advection' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'NEGA2' + tzsource%clongname = 'negative correction' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) ! Add specific source terms to different scalar variables - igroup = 1 SV_VAR: if ( jsv <= nsv_user ) then ! nsv_user case ! Nothing to do @@ -2857,116 +2948,115 @@ SV_BUDGETS: do jsv = 1, ksv ! C2R2 or KHKO Case ! Source terms in common for all C2R2/KHKO budgets - gcond = hturb == 'TKEL' - tzsource%cmnhname = 'NETUR' - tzsource%clongname = 'negative correction induced by turbulence' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nnetursv ) - - gcond = .true. - tzsource%cmnhname = 'NEADV' - tzsource%clongname = 'negative correction induced by advection' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nneadvsv ) - - gcond = .true. - tzsource%cmnhname = 'NEGA' - tzsource%clongname = 'negative correction' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nnegasv ) - - gcond = .true. - tzsource%cmnhname = 'NECON' - tzsource%clongname = 'negative correction induced by condensation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nneconsv ) + tzsource%cmnhname = 'NETUR' + tzsource%clongname = 'negative correction induced by turbulence' + tzsource%lavailable = hturb == 'TKEL' + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'NEADV' + tzsource%clongname = 'negative correction induced by advection' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'NEGA' + tzsource%clongname = 'negative correction' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'NECON' + tzsource%clongname = 'negative correction induced by condensation' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) ! Source terms specific to each budget SV_C2R2: select case( jsv - nsv_c2r2beg + 1 ) case ( 1 ) SV_C2R2 ! Concentration of activated nuclei + tzsource%cmnhname = 'HENU' + tzsource%clongname = 'CCN activation' gtmp = cactccn == 'ABRK' .and. (lorilam .or. ldust .or. lsalt ) - gcond = gtmp .or. ( .not.gtmp .and. .not.lsupsat_c2r2 ) - tzsource%cmnhname = 'HENU' - tzsource%clongname = 'CCN activation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%lavailable = gtmp .or. ( .not.gtmp .and. .not.lsupsat_c2r2 ) + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = .true. - tzsource%cmnhname = 'CEVA' - tzsource%clongname = 'evaporation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'CEVA' + tzsource%clongname = 'evaporation' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) case ( 2 ) SV_C2R2 ! Concentration of cloud droplets - gcond = odragtree .and. odepotree - tzsource%cmnhname = 'DEPOTR' - tzsource%clongname = 'tree droplet deposition' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndepotrsv ) + tzsource%cmnhname = 'DEPOTR' + tzsource%clongname = 'tree droplet deposition' + tzsource%lavailable = odragtree .and. odepotree + call Budget_source_add( tbudgets(ibudget), tzsource) + tzsource%cmnhname = 'HENU' + tzsource%clongname = 'CCN activation' gtmp = cactccn == 'ABRK' .and. (lorilam .or. ldust .or. lsalt ) - gcond = gtmp .or. ( .not.gtmp .and. .not.lsupsat_c2r2 ) - tzsource%cmnhname = 'HENU' - tzsource%clongname = 'CCN activation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%lavailable = gtmp .or. ( .not.gtmp .and. .not.lsupsat_c2r2 ) + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lrain_c2r2 - tzsource%cmnhname = 'SELF' - tzsource%clongname = 'self-collection of cloud droplets' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'SELF' + tzsource%clongname = 'self-collection of cloud droplets' + tzsource%lavailable = lrain_c2r2 + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lrain_c2r2 - tzsource%cmnhname = 'ACCR' - tzsource%clongname = 'accretion' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'ACCR' + tzsource%clongname = 'accretion' + tzsource%lavailable = lrain_c2r2 + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lsedc_c2r2 - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation' + tzsource%lavailable = lsedc_c2r2 + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = ldepoc_c2r2 - tzsource%cmnhname = 'DEPO' - tzsource%clongname = 'surface droplet deposition' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'DEPO' + tzsource%clongname = 'surface droplet deposition' + tzsource%lavailable = ldepoc_c2r2 + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = .true. - tzsource%cmnhname = 'CEVA' - tzsource%clongname = 'evaporation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'CEVA' + tzsource%clongname = 'evaporation' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) case ( 3 ) SV_C2R2 ! Concentration of raindrops + tzsource%cmnhname = 'AUTO' + tzsource%clongname = 'autoconversion into rain' + tzsource%lavailable = lrain_c2r2 + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lrain_c2r2 - tzsource%cmnhname = 'AUTO' - tzsource%clongname = 'autoconversion into rain' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = hcloud /= 'KHKO' - tzsource%cmnhname = 'SCBU' - tzsource%clongname = 'self collection - coalescence/break-up' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'SCBU' + tzsource%clongname = 'self collection - coalescence/break-up' + tzsource%lavailable = hcloud /= 'KHKO' + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lrain_c2r2 - tzsource%cmnhname = 'REVA' - tzsource%clongname = 'rain evaporation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'REVA' + tzsource%clongname = 'rain evaporation' + tzsource%lavailable = lrain_c2r2 + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lrain_c2r2 - tzsource%cmnhname = 'BRKU' - tzsource%clongname = 'spontaneous break-up' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'BRKU' + tzsource%clongname = 'spontaneous break-up' + tzsource%lavailable = lrain_c2r2 + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = .true. - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) case ( 4 ) SV_C2R2 ! Supersaturation - gcond = .true. - tzsource%cmnhname = 'CEVA' - tzsource%clongname = 'evaporation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'CEVA' + tzsource%clongname = 'evaporation' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) end select SV_C2R2 @@ -2975,878 +3065,878 @@ SV_BUDGETS: do jsv = 1, ksv ! LIMA case ! Source terms in common for all LIMA budgets - gcond = hturb == 'TKEL' - tzsource%cmnhname = 'NETUR' - tzsource%clongname = 'negative correction induced by turbulence' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nnetursv ) + tzsource%cmnhname = 'NETUR' + tzsource%clongname = 'negative correction induced by turbulence' + tzsource%lavailable = hturb == 'TKEL' + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = .true. - tzsource%cmnhname = 'NEADV' - tzsource%clongname = 'negative correction induced by advection' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nneadvsv ) + tzsource%cmnhname = 'NEADV' + tzsource%clongname = 'negative correction induced by advection' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = .true. - tzsource%cmnhname = 'NEGA' - tzsource%clongname = 'negative correction' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nnegasv ) + tzsource%cmnhname = 'NEGA' + tzsource%clongname = 'negative correction' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = .true. - tzsource%cmnhname = 'NECON' - tzsource%clongname = 'negative correction induced by condensation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nneconsv ) + tzsource%cmnhname = 'NECON' + tzsource%clongname = 'negative correction induced by condensation' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) ! Source terms specific to each budget SV_LIMA: if ( jsv == nsv_lima_nc ) then ! Cloud droplets concentration - gcond = odragtree .and. odepotree - tzsource%cmnhname = 'DEPOTR' - tzsource%clongname = 'tree droplet deposition' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndepotrsv ) - - gcond = lptsplit .and. lwarm_lima .and. lrain_lima - tzsource%cmnhname = 'CORR' - tzsource%clongname = 'correction' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lwarm_lima .and. lsedc_lima - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lwarm_lima .and. ldepoc_lima - tzsource%cmnhname = 'DEPO' - tzsource%clongname = 'surface droplet deposition' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .and. lwarm_lima .and. lrain_lima - tzsource%cmnhname = 'R2C1' - tzsource%clongname = 'rain to cloud change after sedimentation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lwarm_lima .and. lacti_lima .and. nmod_ccn >= 1 - tzsource%cmnhname = 'HENU' - tzsource%clongname = 'CCN activation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lcold_lima .and. lnucl_lima - tzsource%cmnhname = 'HINC' - tzsource%clongname = 'heterogeneous nucleation by contact' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lwarm_lima .and. lrain_lima - tzsource%cmnhname = 'SELF' - tzsource%clongname = 'self-collection of cloud droplets' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lwarm_lima .and. lrain_lima ) - tzsource%cmnhname = 'AUTO' - tzsource%clongname = 'autoconversion into rain' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lwarm_lima .and. lrain_lima ) - tzsource%cmnhname = 'ACCR' - tzsource%clongname = 'accretion' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lwarm_lima .and. lrain_lima ) - tzsource%cmnhname = 'REVA' - tzsource%clongname = 'rain evaporation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima ) - tzsource%cmnhname = 'HONC' - tzsource%clongname = 'droplet homogeneous nucleation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima ) - tzsource%cmnhname = 'IMLT' - tzsource%clongname = 'ice melting' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) - tzsource%cmnhname = 'RIM' - tzsource%clongname = 'riming of cloud water' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) - tzsource%cmnhname = 'WETG' - tzsource%clongname = 'wet growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) - tzsource%cmnhname = 'DRYG' - tzsource%clongname = 'dry growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit - tzsource%cmnhname = 'CVRC' - tzsource%clongname = 'rain to cloud change after other microphysical processes' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima - tzsource%cmnhname = 'WETH' - tzsource%clongname = 'wet growth of hail' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = hcloud == 'LIMA' .and. lptsplit - tzsource%cmnhname = 'CORR2' - tzsource%clongname = 'supplementary correction inside LIMA splitting' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = .true. - tzsource%cmnhname = 'CEDS' - tzsource%clongname = 'adjustment to saturation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'DEPOTR' + tzsource%clongname = 'tree droplet deposition' + tzsource%lavailable = odragtree .and. odepotree + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CORR' + tzsource%clongname = 'correction' + tzsource%lavailable = lptsplit .and. lwarm_lima .and. lrain_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation' + tzsource%lavailable = lwarm_lima .and. lsedc_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'DEPO' + tzsource%clongname = 'surface droplet deposition' + tzsource%lavailable = lwarm_lima .and. ldepoc_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'R2C1' + tzsource%clongname = 'rain to cloud change after sedimentation' + tzsource%lavailable = lptsplit .and. lwarm_lima .and. lrain_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'HENU' + tzsource%clongname = 'CCN activation' + tzsource%lavailable = lwarm_lima .and. lacti_lima .and. nmod_ccn >= 1 + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'HINC' + tzsource%clongname = 'heterogeneous nucleation by contact' + tzsource%lavailable = lcold_lima .and. lnucl_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'SELF' + tzsource%clongname = 'self-collection of cloud droplets' + tzsource%lavailable = lwarm_lima .and. lrain_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'AUTO' + tzsource%clongname = 'autoconversion into rain' + tzsource%lavailable = lptsplit .or. ( lwarm_lima .and. lrain_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'ACCR' + tzsource%clongname = 'accretion' + tzsource%lavailable = lptsplit .or. ( lwarm_lima .and. lrain_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'REVA' + tzsource%clongname = 'rain evaporation' + tzsource%lavailable = lptsplit .or. ( lwarm_lima .and. lrain_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'HONC' + tzsource%clongname = 'droplet homogeneous nucleation' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'IMLT' + tzsource%clongname = 'ice melting' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'RIM' + tzsource%clongname = 'riming of cloud water' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETG' + tzsource%clongname = 'wet growth of graupel' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'DRYG' + tzsource%clongname = 'dry growth of graupel' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CVRC' + tzsource%clongname = 'rain to cloud change after other microphysical processes' + tzsource%lavailable = lptsplit + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETH' + tzsource%clongname = 'wet growth of hail' + tzsource%lavailable = .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CORR2' + tzsource%clongname = 'supplementary correction inside LIMA splitting' + tzsource%lavailable = hcloud == 'LIMA' .and. lptsplit + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CEDS' + tzsource%clongname = 'adjustment to saturation' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) else if ( jsv == nsv_lima_nr ) then SV_LIMA ! Rain drops concentration - gcond = lptsplit .and. lwarm_lima .and. lrain_lima - tzsource%cmnhname = 'CORR' - tzsource%clongname = 'correction' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lwarm_lima .and. lrain_lima - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .and. lwarm_lima .and. lrain_lima - tzsource%cmnhname = 'R2C1' - tzsource%clongname = 'rain to cloud change after sedimentation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. (lwarm_lima .and. lrain_lima) - tzsource%cmnhname = 'AUTO' - tzsource%clongname = 'autoconversion into rain' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. (lwarm_lima .and. lrain_lima) - tzsource%cmnhname = 'SCBU' - tzsource%clongname = 'self collection - coalescence/break-up' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. (lwarm_lima .and. lrain_lima) - tzsource%cmnhname = 'REVA' - tzsource%clongname = 'rain evaporation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. (lwarm_lima .and. lrain_lima) - tzsource%cmnhname = 'BRKU' - tzsource%clongname = 'spontaneous break-up' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lrain_lima .and. lnucl_lima ) - tzsource%cmnhname = 'HONR' - tzsource%clongname = 'rain homogeneous freezing' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima .and. lrain_lima ) - tzsource%cmnhname = 'ACC' - tzsource%clongname = 'accretion of rain water' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) - tzsource%cmnhname = 'CFRZ' - tzsource%clongname = 'conversion freezing of rain' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) - tzsource%cmnhname = 'WETG' - tzsource%clongname = 'wet growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) - tzsource%cmnhname = 'DRYG' - tzsource%clongname = 'dry growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) - tzsource%cmnhname = 'GMLT' - tzsource%clongname = 'graupel melting' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit - tzsource%cmnhname = 'CVRC' - tzsource%clongname = 'rain to cloud change after other microphysical processes' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima - tzsource%cmnhname = 'WETH' - tzsource%clongname = 'wet growth of hail' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima - tzsource%cmnhname = 'HMLT' - tzsource%clongname = 'hail melting' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = hcloud == 'LIMA' .and. lptsplit - tzsource%cmnhname = 'CORR2' - tzsource%clongname = 'supplementary correction inside LIMA splitting' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'CORR' + tzsource%clongname = 'correction' + tzsource%lavailable = lptsplit .and. lwarm_lima .and. lrain_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation' + tzsource%lavailable = lwarm_lima .and. lrain_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'R2C1' + tzsource%clongname = 'rain to cloud change after sedimentation' + tzsource%lavailable = lptsplit .and. lwarm_lima .and. lrain_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'AUTO' + tzsource%clongname = 'autoconversion into rain' + tzsource%lavailable = lptsplit .or. (lwarm_lima .and. lrain_lima) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'SCBU' + tzsource%clongname = 'self collection - coalescence/break-up' + tzsource%lavailable = lptsplit .or. (lwarm_lima .and. lrain_lima) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'REVA' + tzsource%clongname = 'rain evaporation' + tzsource%lavailable = lptsplit .or. (lwarm_lima .and. lrain_lima) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'BRKU' + tzsource%clongname = 'spontaneous break-up' + tzsource%lavailable = lptsplit .or. (lwarm_lima .and. lrain_lima) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'HONR' + tzsource%clongname = 'rain homogeneous freezing' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lrain_lima .and. lnucl_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'ACC' + tzsource%clongname = 'accretion of rain water' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima .and. lrain_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CFRZ' + tzsource%clongname = 'conversion freezing of rain' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETG' + tzsource%clongname = 'wet growth of graupel' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'DRYG' + tzsource%clongname = 'dry growth of graupel' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'GMLT' + tzsource%clongname = 'graupel melting' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CVRC' + tzsource%clongname = 'rain to cloud change after other microphysical processes' + tzsource%lavailable = lptsplit + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETH' + tzsource%clongname = 'wet growth of hail' + tzsource%lavailable = .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'HMLT' + tzsource%clongname = 'hail melting' + tzsource%lavailable = .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CORR2' + tzsource%clongname = 'supplementary correction inside LIMA splitting' + tzsource%lavailable = hcloud == 'LIMA' .and. lptsplit + call Budget_source_add( tbudgets(ibudget), tzsource ) else if ( jsv >= nsv_lima_ccn_free .and. jsv <= nsv_lima_ccn_free + nmod_ccn - 1 ) then SV_LIMA ! Free CCN concentration - gcond = lwarm_lima .and. lacti_lima .and. nmod_ccn >= 1 - tzsource%cmnhname = 'HENU' - tzsource%clongname = 'CCN activation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'HENU' + tzsource%clongname = 'CCN activation' + tzsource%lavailable = lwarm_lima .and. lacti_lima .and. nmod_ccn >= 1 + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lcold_lima .and. lnucl_lima .and. lhhoni_lima .and. nmod_ccn >= 1 - tzsource%cmnhname = 'HONH' - tzsource%clongname = 'haze homogeneous nucleation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'HONH' + tzsource%clongname = 'haze homogeneous nucleation' + tzsource%lavailable = lcold_lima .and. lnucl_lima .and. lhhoni_lima .and. nmod_ccn >= 1 + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lwarm_lima - tzsource%cmnhname = 'CEDS' - tzsource%clongname = 'adjustment to saturation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'CEDS' + tzsource%clongname = 'adjustment to saturation' + tzsource%lavailable = lwarm_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lscav_lima - tzsource%cmnhname = 'SCAV' - tzsource%clongname = 'scavenging' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'SCAV' + tzsource%clongname = 'scavenging' + tzsource%lavailable = lscav_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) else if ( jsv >= nsv_lima_ccn_acti .and. jsv <= nsv_lima_ccn_acti + nmod_ccn - 1 ) then SV_LIMA ! Activated CCN concentration - gcond = lwarm_lima .and. lacti_lima .and. nmod_ccn >= 1 - tzsource%cmnhname = 'HENU' - tzsource%clongname = 'CCN activation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'HENU' + tzsource%clongname = 'CCN activation' + tzsource%lavailable = lwarm_lima .and. lacti_lima .and. nmod_ccn >= 1 + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lcold_lima .and. lnucl_lima .and. .not. lmeyers_lima - tzsource%cmnhname = 'HINC' - tzsource%clongname = 'heterogeneous nucleation by contact' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'HINC' + tzsource%clongname = 'heterogeneous nucleation by contact' + tzsource%lavailable = lcold_lima .and. lnucl_lima .and. .not. lmeyers_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lwarm_lima - tzsource%cmnhname = 'CEDS' - tzsource%clongname = 'adjustment to saturation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'CEDS' + tzsource%clongname = 'adjustment to saturation' + tzsource%lavailable = lwarm_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) else if ( jsv == nsv_lima_scavmass ) then SV_LIMA ! Scavenged mass variable - gcond = lscav_lima .and. laero_mass_lima - tzsource%cmnhname = 'SCAV' - tzsource%clongname = 'scavenging' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'SCAV' + tzsource%clongname = 'scavenging' + tzsource%lavailable = lscav_lima .and. laero_mass_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lscav_lima .and. laero_mass_lima - tzsource%cmnhname = 'CEDS' - tzsource%clongname = 'adjustment to saturation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'CEDS' + tzsource%clongname = 'adjustment to saturation' + tzsource%lavailable = lscav_lima .and. laero_mass_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) else if ( jsv == nsv_lima_ni ) then SV_LIMA ! Pristine ice crystals concentration - gcond = lptsplit .and. lcold_lima .and. lsnow_lima - tzsource%cmnhname = 'CORR' - tzsource%clongname = 'correction' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lcold_lima .and. lsedi_lima - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lcold_lima .and. lnucl_lima - tzsource%cmnhname = 'HIND' - tzsource%clongname = 'heterogeneous nucleation by deposition' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lcold_lima .and. lnucl_lima - tzsource%cmnhname = 'HINC' - tzsource%clongname = 'heterogeneous nucleation by contact' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lcold_lima .and. lnucl_lima .and. lhhoni_lima .and. nmod_ccn >= 1 - tzsource%cmnhname = 'HONH' - tzsource%clongname = 'haze homogeneous nucleation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima ) - tzsource%cmnhname = 'HONC' - tzsource%clongname = 'droplet homogeneous nucleation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lsnow_lima ) - tzsource%cmnhname = 'CNVI' - tzsource%clongname = 'conversion of snow to cloud ice' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lsnow_lima ) - tzsource%cmnhname = 'CNVS' - tzsource%clongname = 'conversion of pristine ice to snow' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lsnow_lima ) - tzsource%cmnhname = 'AGGS' - tzsource%clongname = 'aggregation of snow' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima ) - tzsource%cmnhname = 'IMLT' - tzsource%clongname = 'ice melting' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) - tzsource%cmnhname = 'HMS' - tzsource%clongname = 'Hallett-Mossop ice multiplication process due to snow riming' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) - tzsource%cmnhname = 'CFRZ' - tzsource%clongname = 'conversion freezing of rain' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) - tzsource%cmnhname = 'WETG' - tzsource%clongname = 'wet growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) - tzsource%cmnhname = 'DRYG' - tzsource%clongname = 'dry growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) - tzsource%cmnhname = 'HMG' - tzsource%clongname = 'Hallett-Mossop ice multiplication process due to graupel riming' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima - tzsource%cmnhname = 'WETH' - tzsource%clongname = 'wet growth of hail' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = .true. - tzsource%cmnhname = 'CEDS' - tzsource%clongname = 'adjustment to saturation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) - - gcond = hcloud == 'LIMA' .and. lptsplit - tzsource%cmnhname = 'CORR2' - tzsource%clongname = 'supplementary correction inside LIMA splitting' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'CORR' + tzsource%clongname = 'correction' + tzsource%lavailable = lptsplit .and. lcold_lima .and. lsnow_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation' + tzsource%lavailable = lcold_lima .and. lsedi_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'HIND' + tzsource%clongname = 'heterogeneous nucleation by deposition' + tzsource%lavailable = lcold_lima .and. lnucl_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'HINC' + tzsource%clongname = 'heterogeneous nucleation by contact' + tzsource%lavailable = lcold_lima .and. lnucl_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'HONH' + tzsource%clongname = 'haze homogeneous nucleation' + tzsource%lavailable = lcold_lima .and. lnucl_lima .and. lhhoni_lima .and. nmod_ccn >= 1 + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'HONC' + tzsource%clongname = 'droplet homogeneous nucleation' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CNVI' + tzsource%clongname = 'conversion of snow to cloud ice' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lsnow_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CNVS' + tzsource%clongname = 'conversion of pristine ice to snow' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lsnow_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'AGGS' + tzsource%clongname = 'aggregation of snow' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lsnow_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'IMLT' + tzsource%clongname = 'ice melting' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'HMS' + tzsource%clongname = 'Hallett-Mossop ice multiplication process due to snow riming' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CFRZ' + tzsource%clongname = 'conversion freezing of rain' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETG' + tzsource%clongname = 'wet growth of graupel' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'DRYG' + tzsource%clongname = 'dry growth of graupel' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'HMG' + tzsource%clongname = 'Hallett-Mossop ice multiplication process due to graupel riming' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETH' + tzsource%clongname = 'wet growth of hail' + tzsource%lavailable = .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima .and. lsnow_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CEDS' + tzsource%clongname = 'adjustment to saturation' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CORR2' + tzsource%clongname = 'supplementary correction inside LIMA splitting' + tzsource%lavailable = hcloud == 'LIMA' .and. lptsplit + call Budget_source_add( tbudgets(ibudget), tzsource ) else if ( jsv >= nsv_lima_ifn_free .and. jsv <= nsv_lima_ifn_free + nmod_ifn - 1 ) then SV_LIMA ! Free IFN concentration - gcond = lcold_lima .and. lnucl_lima .and. .not. lmeyers_lima - tzsource%cmnhname = 'HIND' - tzsource%clongname = 'heterogeneous nucleation by deposition' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'HIND' + tzsource%clongname = 'heterogeneous nucleation by deposition' + tzsource%lavailable = lcold_lima .and. lnucl_lima .and. .not. lmeyers_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lcold_lima - tzsource%cmnhname = 'CEDS' - tzsource%clongname = 'adjustment to saturation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'CEDS' + tzsource%clongname = 'adjustment to saturation' + tzsource%lavailable = lcold_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lscav_lima - tzsource%cmnhname = 'SCAV' - tzsource%clongname = 'scavenging' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'SCAV' + tzsource%clongname = 'scavenging' + tzsource%lavailable = lscav_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) else if ( jsv >= nsv_lima_ifn_nucl .and. jsv <= nsv_lima_ifn_nucl + nmod_ifn - 1 ) then SV_LIMA ! Nucleated IFN concentration - gcond = lcold_lima .and. lnucl_lima & - .and. ( ( lmeyers_lima .and. jsv == nsv_lima_ifn_nucl ) .or. .not. lmeyers_lima ) - tzsource%cmnhname = 'HIND' - tzsource%clongname = 'heterogeneous nucleation by deposition' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'HIND' + tzsource%clongname = 'heterogeneous nucleation by deposition' + tzsource%lavailable = lcold_lima .and. lnucl_lima & + .and. ( ( lmeyers_lima .and. jsv == nsv_lima_ifn_nucl ) .or. .not. lmeyers_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lcold_lima .and. lnucl_lima .and. lmeyers_lima .and. jsv == nsv_lima_ifn_nucl - tzsource%cmnhname = 'HINC' - tzsource%clongname = 'heterogeneous nucleation by contact' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'HINC' + tzsource%clongname = 'heterogeneous nucleation by contact' + tzsource%lavailable = lcold_lima .and. lnucl_lima .and. lmeyers_lima .and. jsv == nsv_lima_ifn_nucl + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima ) - tzsource%cmnhname = 'IMLT' - tzsource%clongname = 'ice melting' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'IMLT' + tzsource%clongname = 'ice melting' + tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima ) + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lcold_lima - tzsource%cmnhname = 'CEDS' - tzsource%clongname = 'adjustment to saturation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'CEDS' + tzsource%clongname = 'adjustment to saturation' + tzsource%lavailable = lcold_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) else if ( jsv >= nsv_lima_imm_nucl .and. jsv <= nsv_lima_imm_nucl + nmod_imm - 1 ) then SV_LIMA ! Nucleated IMM concentration - gcond = lcold_lima .and. lnucl_lima .and. .not. lmeyers_lima - tzsource%cmnhname = 'HINC' - tzsource%clongname = 'heterogeneous nucleation by contact' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'HINC' + tzsource%clongname = 'heterogeneous nucleation by contact' + tzsource%lavailable = lcold_lima .and. lnucl_lima .and. .not. lmeyers_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lcold_lima - tzsource%cmnhname = 'CEDS' - tzsource%clongname = 'adjustment to saturation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'CEDS' + tzsource%clongname = 'adjustment to saturation' + tzsource%lavailable = lcold_lima + call Budget_source_add( tbudgets(ibudget), tzsource ) else if ( jsv == nsv_lima_hom_haze ) then SV_LIMA ! Homogeneous freezing of CCN - gcond = lcold_lima .and. lnucl_lima .and. & - ( ( .not.lptsplit .and. ( ( lhhoni_lima .and. nmod_ccn >= 1 ) .or. lwarm_lima ) ) & - .or. ( lptsplit .and. ( lhhoni_lima .and. nmod_ccn >= 1 ) ) ) - tzsource%cmnhname = 'HONH' - tzsource%clongname = 'haze homogeneous nucleation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup ) + tzsource%cmnhname = 'HONH' + tzsource%clongname = 'haze homogeneous nucleation' + tzsource%lavailable = lcold_lima .and. lnucl_lima .and. & + ( ( .not.lptsplit .and. ( ( lhhoni_lima .and. nmod_ccn >= 1 ) .or. lwarm_lima ) ) & + .or. ( lptsplit .and. ( lhhoni_lima .and. nmod_ccn >= 1 ) ) ) + call Budget_source_add( tbudgets(ibudget), tzsource ) end if SV_LIMA else if ( jsv >= nsv_elecbeg .and. jsv <= nsv_elecend ) then SV_VAR ! Electricity case - gcond = .true. - tzsource%cmnhname = 'NEGA' - tzsource%clongname = 'negative correction' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nnegasv ) + tzsource%cmnhname = 'NEGA' + tzsource%clongname = 'negative correction' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) SV_ELEC: select case( jsv - nsv_elecbeg + 1 ) case ( 1 ) SV_ELEC ! volumetric charge of water vapor - gcond = .true. - tzsource%cmnhname = 'DRIFT' - tzsource%clongname = 'ion drift motion' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndriftqv ) - - gcond = .true. - tzsource%cmnhname = 'CORAY' - tzsource%clongname = 'cosmic ray source' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ncorayqv ) - - gcond = .true. - tzsource%cmnhname = 'DEPS' - tzsource%clongname = 'deposition on snow' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndepsqv ) - - gcond = .true. - tzsource%cmnhname = 'DEPG' - tzsource%clongname = 'deposition on graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndepgqv ) - - gcond = lwarm_ice - tzsource%cmnhname = 'REVA' - tzsource%clongname = 'rain evaporation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nrevaqv ) - - gcond = .true. - tzsource%cmnhname = 'CDEPI' - tzsource%clongname = 'condensation/deposition on ice' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ncdepiqv ) - - gcond = .true. - tzsource%cmnhname = 'NEUT' - tzsource%clongname = 'NEUT' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nneutqv ) + tzsource%cmnhname = 'DRIFT' + tzsource%clongname = 'ion drift motion' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CORAY' + tzsource%clongname = 'cosmic ray source' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'DEPS' + tzsource%clongname = 'deposition on snow' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'DEPG' + tzsource%clongname = 'deposition on graupel' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'REVA' + tzsource%clongname = 'rain evaporation' + tzsource%lavailable = lwarm_ice + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CDEPI' + tzsource%clongname = 'condensation/deposition on ice' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'NEUT' + tzsource%clongname = 'NEUT' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) case ( 2 ) SV_ELEC ! volumetric charge of cloud droplets - gcond = .true. - tzsource%cmnhname = 'HON' - tzsource%clongname = 'homogeneous nucleation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nhonqc ) - - gcond = lwarm_ice - tzsource%cmnhname = 'AUTO' - tzsource%clongname = 'autoconversion into rain' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nautoqc ) - - gcond = lwarm_ice - tzsource%cmnhname = 'ACCR' - tzsource%clongname = 'accretion' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, naccrqc ) - - gcond = .true. - tzsource%cmnhname = 'RIM' - tzsource%clongname = 'riming of cloud water' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nrimqc ) - - gcond = .true. - tzsource%cmnhname = 'WETG' - tzsource%clongname = 'wet growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nwetgqc ) - - gcond = .true. - tzsource%cmnhname = 'DRYG' - tzsource%clongname = 'dry growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndrygqc ) - - gcond = linductive - tzsource%cmnhname = 'INCG' - tzsource%clongname = 'inductive charge transfer between cloud droplets and graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nincgqc ) - - gcond = hcloud == 'ICE4' - tzsource%cmnhname = 'WETH' - tzsource%clongname = 'wet growth of hail' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nwethqc ) - - gcond = .true. - tzsource%cmnhname = 'IMLT' - tzsource%clongname = 'ice melting' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nimltqc ) - - gcond = .true. - tzsource%cmnhname = 'BERFI' - tzsource%clongname = 'Bergeron-Findeisen' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nberfiqc ) - - gcond = lsedic_ice - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nsediqc ) - - gcond = .true. - tzsource%cmnhname = 'CDEPI' - tzsource%clongname = 'condensation/deposition on ice' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ncdepiqc ) - - gcond = .true. - tzsource%cmnhname = 'NEUT' - tzsource%clongname = 'NEUT' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nneutqc ) + tzsource%cmnhname = 'HON' + tzsource%clongname = 'homogeneous nucleation' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'AUTO' + tzsource%clongname = 'autoconversion into rain' + tzsource%lavailable = lwarm_ice + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'ACCR' + tzsource%clongname = 'accretion' + tzsource%lavailable = lwarm_ice + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'RIM' + tzsource%clongname = 'riming of cloud water' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETG' + tzsource%clongname = 'wet growth of graupel' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'DRYG' + tzsource%clongname = 'dry growth of graupel' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'INCG' + tzsource%clongname = 'inductive charge transfer between cloud droplets and graupel' + tzsource%lavailable = linductive + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETH' + tzsource%clongname = 'wet growth of hail' + tzsource%lavailable = hcloud == 'ICE4' + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'IMLT' + tzsource%clongname = 'ice melting' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'BERFI' + tzsource%clongname = 'Bergeron-Findeisen' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation' + tzsource%lavailable = lsedic_ice + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CDEPI' + tzsource%clongname = 'condensation/deposition on ice' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'NEUT' + tzsource%clongname = 'NEUT' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) case ( 3 ) SV_ELEC ! volumetric charge of rain drops - gcond = .true. - tzsource%cmnhname = 'SFR' - tzsource%clongname = 'spontaneous freezing' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nsfrqr ) - - gcond = lwarm_ice - tzsource%cmnhname = 'AUTO' - tzsource%clongname = 'autoconversion into rain' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nautoqr ) - - gcond = lwarm_ice - tzsource%cmnhname = 'ACCR' - tzsource%clongname = 'accretion' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, naccrqr ) - - gcond = lwarm_ice - tzsource%cmnhname = 'REVA' - tzsource%clongname = 'rain evaporation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nrevaqr ) - - gcond = .true. - tzsource%cmnhname = 'ACC' - tzsource%clongname = 'accretion of rain water' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, naccqr ) - - gcond = .true. - tzsource%cmnhname = 'CFRZ' - tzsource%clongname = 'conversion freezing of rain' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ncfrzqr ) - - gcond = .true. - tzsource%cmnhname = 'WETG' - tzsource%clongname = 'wet growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nwetgqr ) - - gcond = .true. - tzsource%cmnhname = 'DRYG' - tzsource%clongname = 'dry growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndrygqr ) - - gcond = .true. - tzsource%cmnhname = 'GMLT' - tzsource%clongname = 'graupel melting' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ngmltqr ) - - gcond = hcloud == 'ICE4' - tzsource%cmnhname = 'WETH' - tzsource%clongname = 'wet growth of hail' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nwethqr ) - - gcond = hcloud == 'ICE4' - tzsource%cmnhname = 'HMLT' - tzsource%clongname = 'melting of hail' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nhmltqr ) - - gcond = .true. - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nsediqr ) - - gcond = .true. - tzsource%cmnhname = 'NEUT' - tzsource%clongname = 'NEUT' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nneutqr ) + tzsource%cmnhname = 'SFR' + tzsource%clongname = 'spontaneous freezing' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'AUTO' + tzsource%clongname = 'autoconversion into rain' + tzsource%lavailable = lwarm_ice + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'ACCR' + tzsource%clongname = 'accretion' + tzsource%lavailable = lwarm_ice + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'REVA' + tzsource%clongname = 'rain evaporation' + tzsource%lavailable = lwarm_ice + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'ACC' + tzsource%clongname = 'accretion of rain water' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CFRZ' + tzsource%clongname = 'conversion freezing of rain' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETG' + tzsource%clongname = 'wet growth of graupel' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'DRYG' + tzsource%clongname = 'dry growth of graupel' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'GMLT' + tzsource%clongname = 'graupel melting' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETH' + tzsource%clongname = 'wet growth of hail' + tzsource%lavailable = hcloud == 'ICE4' + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'HMLT' + tzsource%clongname = 'melting of hail' + tzsource%lavailable = hcloud == 'ICE4' + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'NEUT' + tzsource%clongname = 'NEUT' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) case ( 4 ) SV_ELEC ! volumetric charge of ice crystals - gcond = .true. - tzsource%cmnhname = 'HON' - tzsource%clongname = 'homogeneous nucleation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nhonqi ) - - gcond = .true. - tzsource%cmnhname = 'AGGS' - tzsource%clongname = 'aggregation of snow' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, naggsqi ) - - gcond = .true. - tzsource%cmnhname = 'AUTS' - tzsource%clongname = 'autoconversion of ice' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nautsqi ) - - gcond = .true. - tzsource%cmnhname = 'CFRZ' - tzsource%clongname = 'conversion freezing of rain' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ncfrzqi ) - - gcond = .true. - tzsource%cmnhname = 'WETG' - tzsource%clongname = 'wet growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nwetgqi ) - - gcond = .true. - tzsource%cmnhname = 'DRYG' - tzsource%clongname = 'dry growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndrygqi ) - - gcond = hcloud == 'ICE4' - tzsource%cmnhname = 'WETH' - tzsource%clongname = 'wet growth of hail' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nwethqi ) - - gcond = .true. - tzsource%cmnhname = 'IMLT' - tzsource%clongname = 'ice melting' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nimltqi ) - - gcond = .true. - tzsource%cmnhname = 'BERFI' - tzsource%clongname = 'Bergeron-Findeisen' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nberfiqi ) - - gcond = .true. - tzsource%cmnhname = 'NIIS' - tzsource%clongname = 'non-inductive charge separation due to ice-snow collisions' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nniisqi ) - - gcond = .true. - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nsediqi ) - - gcond = .true. - tzsource%cmnhname = 'CDEPI' - tzsource%clongname = 'condensation/deposition on ice' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ncdepiqi ) - - gcond = .true. - tzsource%cmnhname = 'NEUT' - tzsource%clongname = 'NEUT' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nneutqi ) + tzsource%cmnhname = 'HON' + tzsource%clongname = 'homogeneous nucleation' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'AGGS' + tzsource%clongname = 'aggregation of snow' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'AUTS' + tzsource%clongname = 'autoconversion of ice' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CFRZ' + tzsource%clongname = 'conversion freezing of rain' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETG' + tzsource%clongname = 'wet growth of graupel' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'DRYG' + tzsource%clongname = 'dry growth of graupel' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETH' + tzsource%clongname = 'wet growth of hail' + tzsource%lavailable = hcloud == 'ICE4' + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'IMLT' + tzsource%clongname = 'ice melting' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'BERFI' + tzsource%clongname = 'Bergeron-Findeisen' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'NIIS' + tzsource%clongname = 'non-inductive charge separation due to ice-snow collisions' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CDEPI' + tzsource%clongname = 'condensation/deposition on ice' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'NEUT' + tzsource%clongname = 'NEUT' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) case ( 5 ) SV_ELEC ! volumetric charge of snow - gcond = .true. - tzsource%cmnhname = 'DEPS' - tzsource%clongname = 'deposition on snow' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndepsqs ) - - gcond = .true. - tzsource%cmnhname = 'AGGS' - tzsource%clongname = 'aggregation of snow' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, naggsqs ) - - gcond = .true. - tzsource%cmnhname = 'AUTS' - tzsource%clongname = 'autoconversion of ice' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nautsqs ) - - gcond = .true. - tzsource%cmnhname = 'RIM' - tzsource%clongname = 'riming of cloud water' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nrimqs ) - - gcond = .true. - tzsource%cmnhname = 'ACC' - tzsource%clongname = 'accretion of rain water' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, naccqs ) - - gcond = .true. - tzsource%cmnhname = 'CMEL' - tzsource%clongname = 'conversion melting' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ncmelqs ) - - gcond = .true. - tzsource%cmnhname = 'WETG' - tzsource%clongname = 'wet growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nwetgqs ) - - gcond = .true. - tzsource%cmnhname = 'DRYG' - tzsource%clongname = 'dry growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndrygqs ) - - gcond = .true. - tzsource%cmnhname = 'NIIS' - tzsource%clongname = 'non-inductive charge separation due to ice-snow collisions' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nniisqs ) - - gcond = hcloud == 'ICE4' - tzsource%cmnhname = 'WETH' - tzsource%clongname = 'wet growth of hail' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nwethqs ) - - gcond = .true. - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nsediqs ) - - gcond = .true. - tzsource%cmnhname = 'NEUT' - tzsource%clongname = 'NEUT' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nneutqs ) + tzsource%cmnhname = 'DEPS' + tzsource%clongname = 'deposition on snow' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'AGGS' + tzsource%clongname = 'aggregation of snow' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'AUTS' + tzsource%clongname = 'autoconversion of ice' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'RIM' + tzsource%clongname = 'riming of cloud water' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'ACC' + tzsource%clongname = 'accretion of rain water' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CMEL' + tzsource%clongname = 'conversion melting' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETG' + tzsource%clongname = 'wet growth of graupel' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'DRYG' + tzsource%clongname = 'dry growth of graupel' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'NIIS' + tzsource%clongname = 'non-inductive charge separation due to ice-snow collisions' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETH' + tzsource%clongname = 'wet growth of hail' + tzsource%lavailable = hcloud == 'ICE4' + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'NEUT' + tzsource%clongname = 'NEUT' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) case ( 6 ) SV_ELEC ! volumetric charge of graupel - gcond = .true. - tzsource%cmnhname = 'SFR' - tzsource%clongname = 'spontaneous freezing' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nsfrqg ) - - gcond = .true. - tzsource%cmnhname = 'DEPG' - tzsource%clongname = 'deposition on graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndepgqg ) - - gcond = .true. - tzsource%cmnhname = 'RIM' - tzsource%clongname = 'riming of cloud water' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nrimqg ) - - gcond = .true. - tzsource%cmnhname = 'ACC' - tzsource%clongname = 'accretion of rain water' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, naccqg ) - - gcond = .true. - tzsource%cmnhname = 'CMEL' - tzsource%clongname = 'conversion melting' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ncmelqg ) - - gcond = .true. - tzsource%cmnhname = 'CFRZ' - tzsource%clongname = 'conversion freezing of rain' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ncfrzqg ) - - gcond = .true. - tzsource%cmnhname = 'WETG' - tzsource%clongname = 'wet growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nwetgqg ) - - gcond = .true. - tzsource%cmnhname = 'DRYG' - tzsource%clongname = 'dry growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndrygqg ) - - gcond = linductive - tzsource%cmnhname = 'INCG' - tzsource%clongname = 'inductive charge transfer between cloud droplets and graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nincgqg ) - - gcond = .true. - tzsource%cmnhname = 'GMLT' - tzsource%clongname = 'graupel melting' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ngmltqg ) - - gcond = hcloud == 'ICE4' - tzsource%cmnhname = 'WETH' - tzsource%clongname = 'wet growth of hail' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nwethqg ) - - gcond = .true. - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nsediqg ) - - gcond = .true. - tzsource%cmnhname = 'NEUT' - tzsource%clongname = 'NEUT' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nneutqg ) + tzsource%cmnhname = 'SFR' + tzsource%clongname = 'spontaneous freezing' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'DEPG' + tzsource%clongname = 'deposition on graupel' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'RIM' + tzsource%clongname = 'riming of cloud water' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'ACC' + tzsource%clongname = 'accretion of rain water' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CMEL' + tzsource%clongname = 'conversion melting' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CFRZ' + tzsource%clongname = 'conversion freezing of rain' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETG' + tzsource%clongname = 'wet growth of graupel' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'DRYG' + tzsource%clongname = 'dry growth of graupel' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'INCG' + tzsource%clongname = 'inductive charge transfer between cloud droplets and graupel' + tzsource%lavailable = linductive + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'GMLT' + tzsource%clongname = 'graupel melting' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETH' + tzsource%clongname = 'wet growth of hail' + tzsource%lavailable = hcloud == 'ICE4' + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'NEUT' + tzsource%clongname = 'NEUT' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) case ( 7: ) SV_ELEC if ( ( hcloud == 'ICE4' .and. ( jsv - nsv_elecbeg + 1 ) == 7 ) ) then ! volumetric charge of hail - gcond = .true. - tzsource%cmnhname = 'WETG' - tzsource%clongname = 'wet growth of graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nwetgqh ) - - gcond = .true. - tzsource%cmnhname = 'WETH' - tzsource%clongname = 'wet growth of hail' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nwethqh ) - - gcond = .true. - tzsource%cmnhname = 'HMLT' - tzsource%clongname = 'melting of hail' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nhmltqh ) - - gcond = .true. - tzsource%cmnhname = 'SEDI' - tzsource%clongname = 'sedimentation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nsediqh ) - - gcond = .true. - tzsource%cmnhname = 'NEUT' - tzsource%clongname = 'NEUT' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nneutqh ) + tzsource%cmnhname = 'WETG' + tzsource%clongname = 'wet growth of graupel' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'WETH' + tzsource%clongname = 'wet growth of hail' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'HMLT' + tzsource%clongname = 'melting of hail' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'SEDI' + tzsource%clongname = 'sedimentation' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'NEUT' + tzsource%clongname = 'NEUT' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) else if ( ( hcloud == 'ICE3' .and. ( jsv - nsv_elecbeg + 1 ) == 7 ) & .or. ( hcloud == 'ICE4' .and. ( jsv - nsv_elecbeg + 1 ) == 8 ) ) then ! Negative ions (NSV_ELECEND case) - gcond = .true. - tzsource%cmnhname = 'DRIFT' - tzsource%clongname = 'ion drift motion' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndriftni ) - - gcond = .true. - tzsource%cmnhname = 'CORAY' - tzsource%clongname = 'cosmic ray source' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ncorayni ) - - gcond = .true. - tzsource%cmnhname = 'DEPS' - tzsource%clongname = 'deposition on snow' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndepsni ) - - gcond = .true. - tzsource%cmnhname = 'DEPG' - tzsource%clongname = 'deposition on graupel' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ndepgni ) - - gcond = lwarm_ice - tzsource%cmnhname = 'REVA' - tzsource%clongname = 'rain evaporation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nrevani ) - - gcond = .true. - tzsource%cmnhname = 'CDEPI' - tzsource%clongname = 'condensation/deposition on ice' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, ncdepini ) - - gcond = .true. - tzsource%cmnhname = 'NEUT' - tzsource%clongname = 'NEUT' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nneutni ) + tzsource%cmnhname = 'DRIFT' + tzsource%clongname = 'ion drift motion' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CORAY' + tzsource%clongname = 'cosmic ray source' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'DEPS' + tzsource%clongname = 'deposition on snow' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'DEPG' + tzsource%clongname = 'deposition on graupel' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'REVA' + tzsource%clongname = 'rain evaporation' + tzsource%lavailable = lwarm_ice + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'CDEPI' + tzsource%clongname = 'condensation/deposition on ice' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) + + tzsource%cmnhname = 'NEUT' + tzsource%clongname = 'NEUT' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) else call Print_msg( NVERB_FATAL, 'BUD', 'Ini_budget', 'unknown electricity budget' ) @@ -3874,15 +3964,15 @@ SV_BUDGETS: do jsv = 1, ksv else if ( jsv >= nsv_chembeg .and. jsv <= nsv_chemend ) then SV_VAR !Chemical case - gcond = .true. - tzsource%cmnhname = 'CHEM' - tzsource%clongname = 'chemistry activity' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nchemsv ) + tzsource%cmnhname = 'CHEM' + tzsource%clongname = 'chemistry activity' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = .true. - tzsource%cmnhname = 'NEGA' - tzsource%clongname = 'negative correction' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nnegasv ) + tzsource%cmnhname = 'NEGA' + tzsource%clongname = 'negative correction' + tzsource%lavailable = .true. + call Budget_source_add( tbudgets(ibudget), tzsource ) else if ( jsv >= nsv_chicbeg .and. jsv <= nsv_chicend ) then SV_VAR @@ -3891,10 +3981,10 @@ SV_BUDGETS: do jsv = 1, ksv else if ( jsv >= nsv_aerbeg .and. jsv <= nsv_aerend ) then SV_VAR !Chemical aerosol case - gcond = lorilam - tzsource%cmnhname = 'NEGA' - tzsource%clongname = 'negative correction' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nnegasv ) + tzsource%cmnhname = 'NEGA' + tzsource%clongname = 'negative correction' + tzsource%lavailable = lorilam + call Budget_source_add( tbudgets(ibudget), tzsource ) else if ( jsv >= nsv_aerdepbeg .and. jsv <= nsv_aerdepend ) then SV_VAR !Aerosol wet deposition @@ -3913,15 +4003,15 @@ SV_BUDGETS: do jsv = 1, ksv else if ( jsv >= nsv_snwbeg .and. jsv <= nsv_snwend ) then SV_VAR !Snow - gcond = lblowsnow .and. lsnowsubl - tzsource%cmnhname = 'SNSUB' - tzsource%clongname = 'blowing snow sublimation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nsnsubsv ) + tzsource%cmnhname = 'SNSUB' + tzsource%clongname = 'blowing snow sublimation' + tzsource%lavailable = lblowsnow .and. lsnowsubl + call Budget_source_add( tbudgets(ibudget), tzsource ) - gcond = lblowsnow - tzsource%cmnhname = 'SNSED' - tzsource%clongname = 'blowing snow sedimentation' - call Budget_source_add( tbudgets(ibudget), tzsource, gcond, nsnsedsv ) + tzsource%cmnhname = 'SNSED' + tzsource%clongname = 'blowing snow sedimentation' + tzsource%lavailable = lblowsnow + call Budget_source_add( tbudgets(ibudget), tzsource ) else if ( jsv >= nsv_lnoxbeg .and. jsv <= nsv_lnoxend ) then SV_VAR @@ -3930,6 +4020,11 @@ SV_BUDGETS: do jsv = 1, ksv else SV_VAR call Print_msg( NVERB_FATAL, 'BUD', 'Ini_budget', 'unknown scalar variable' ) end if SV_VAR + + + call Sourcelist_sort_compact( tbudgets(ibudget) ) + + call Sourcelist_scan( tbudgets(ibudget), cbulist_rsv ) end if end do SV_BUDGETS @@ -3963,25 +4058,26 @@ call Ini_budget_groups( tbudgets, ibudim1, ibudim2, ibudim3 ) end subroutine Ini_budget -subroutine Budget_source_add( tpbudget, tpsource, ocond, kgroupin, odonotinit, ooverwrite ) +subroutine Budget_source_add( tpbudget, tpsource, odonotinit, ooverwrite ) use modd_budget, only: tbudgetdata, tbusourcedata - use mode_msg - type(tbudgetdata), intent(inout) :: tpbudget type(tbusourcedata), intent(in) :: tpsource ! Metadata basis - logical, intent(in) :: ocond ! Necessary condition for availability of the source term - integer, intent(in) :: kgroupin ! Requested group for the source term logical, optional, intent(in) :: odonotinit logical, optional, intent(in) :: ooverwrite - integer :: isourcenumber + character(len=4) :: ynum + integer :: isourcenumber - call Print_msg( NVERB_DEBUG, 'BUD', 'Budget_source_add', 'called for '//trim( tpbudget%cname )//': '//trim( tpsource%cmnhname ) ) + call Print_msg( NVERB_DEBUG, 'BUD', 'Budget_source_add', 'called for ' // Trim( tpbudget%cname ) & + // ': ' // Trim( tpsource%cmnhname ) ) isourcenumber = tpbudget%nsources + 1 if ( isourcenumber > tpbudget%nsourcesmax ) then - call Print_msg( NVERB_FATAL, 'BUD', 'Budget_source_add', 'insufficient number of source terms' ) + Write( ynum, '( i4 )' ) tpbudget%nsourcesmax + cmnhmsg(1) = 'Insufficient max number of source terms (' // Trim(ynum) // ') for budget ' // Trim( tpbudget%cname ) + cmnhmsg(2) = 'Please increaze value of parameter NSOURCESMAX' + call Print_msg( NVERB_FATAL, 'BUD', 'Budget_source_add' ) else tpbudget%nsources = tpbudget%nsources + 1 end if @@ -3990,14 +4086,6 @@ subroutine Budget_source_add( tpbudget, tpsource, ocond, kgroupin, odonotinit, o ! Modifications to source term metadata done with the other dummy arguments tpbudget%tsources(isourcenumber) = tpsource - if( ocond ) then - tpbudget%tsources(isourcenumber)%ngroup = kgroupin - else - tpbudget%tsources(isourcenumber)%ngroup = 0 - if ( kgroupin/=0 ) call Print_msg( NVERB_WARNING, 'BUD', 'Budget_source_add', 'source term '//trim( tpbudget%cname ) & - //': '//trim( tpbudget%tsources(isourcenumber)%cmnhname )//' not available' ) - end if - if ( present( odonotinit ) ) tpbudget%tsources(isourcenumber)%ldonotinit = odonotinit if ( present( ooverwrite ) ) tpbudget%tsources(isourcenumber)%loverwrite = ooverwrite @@ -4009,7 +4097,6 @@ subroutine Ini_budget_groups( tpbudgets, kbudim1, kbudim2, kbudim3 ) use modd_field, only: TYPEINT, TYPEREAL use modd_parameters, only: NMNHNAMELGTMAX, NSTDNAMELGTMAX - use mode_msg use mode_tools, only: Quicksort type(tbudgetdata), dimension(:), intent(inout) :: tpbudgets @@ -4260,4 +4347,160 @@ subroutine Ini_budget_groups( tpbudgets, kbudim1, kbudim2, kbudim3 ) end subroutine Ini_budget_groups + +subroutine Sourcelist_sort_compact( tpbudget ) + !Sort the list of sources to put the non-available source terms at the end of the list + !and compact the list + use modd_budget, only: tbudgetdata, tbusourcedata + + type(tbudgetdata), intent(inout) :: tpbudget + + integer :: ji + integer :: isrc_avail, isrc_notavail + type(tbusourcedata), dimension(:), allocatable :: tzsources_avail + type(tbusourcedata), dimension(:), allocatable :: tzsources_notavail + + isrc_avail = 0 + isrc_notavail = 0 + + Allocate( tzsources_avail (tpbudget%nsources) ) + Allocate( tzsources_notavail(tpbudget%nsources) ) + + !Separate source terms available or not during the execution + !(based on the criteria provided to Budget_source_add and stored in lavailable field) + do ji = 1, tpbudget%nsources + if ( tpbudget%tsources(ji)%lavailable ) then + isrc_avail = isrc_avail + 1 + tzsources_avail(isrc_avail) = tpbudget%tsources(ji) + else + isrc_notavail = isrc_notavail + 1 + tzsources_notavail(isrc_notavail) = tpbudget%tsources(ji) + end if + end do + + !Reallocate/compact the source list + if ( Allocated( tpbudget%tsources ) ) Deallocate( tpbudget%tsources ) + Allocate( tpbudget%tsources( tpbudget%nsources ) ) + + tpbudget%nsourcesmax = tpbudget%nsources + !Limit the number of sources to the available list + tpbudget%nsources = isrc_avail + + !Fill the source list beginning with the available sources and finishing with the non-available ones + do ji = 1, isrc_avail + tpbudget%tsources(ji) = tzsources_avail(ji) + end do + + do ji = 1, isrc_notavail + tpbudget%tsources(isrc_avail + ji) = tzsources_notavail(ji) + end do + +end subroutine Sourcelist_sort_compact + + +subroutine Sourcelist_scan( tpbudget, hbulist ) + use modd_budget, only: tbudgetdata + + type(tbudgetdata), intent(inout) :: tpbudget + character(len=*), dimension(:), intent(in) :: hbulist + + character(len=:), allocatable :: yline + character(len=:), allocatable :: ysrc + integer :: idx + integer :: igroup + integer :: igroup_idx + integer :: ipos + integer :: ji + + !Always enable INIF, ENDF and AVEF terms + ipos = Source_find( tpbudget, 'INIF' ) + if ( ipos < 1 ) call Print_msg( NVERB_FATAL, 'BUD', 'Sourcelist_scan', 'source term ' // Trim( tpbudget%cname ) & + // ': INIF not found' ) + tpbudget%tsources(ipos)%ngroup = 1 + + ipos = Source_find( tpbudget, 'ENDF' ) + if ( ipos < 1 ) call Print_msg( NVERB_FATAL, 'BUD', 'Sourcelist_scan', 'source term ' // Trim( tpbudget%cname ) & + // ': ENDF not found' ) + tpbudget%tsources(ipos)%ngroup = 1 + + ipos = Source_find( tpbudget, 'AVEF' ) + if ( ipos < 1 ) call Print_msg( NVERB_FATAL, 'BUD', 'Sourcelist_scan', 'source term ' // Trim( tpbudget%cname ) & + // ': AVEF not found' ) + tpbudget%tsources(ipos)%ngroup = 1 + + !igroup_idx start at 2 because 1 is reserved for individually stored source terms + igroup_idx = 2 + + do ji = 1, Size( hbulist ) + if ( Len_trim( hbulist(ji) ) > 0 ) then + ! Scan the line and separate the different sources (separated by + signs) + yline = Trim(hbulist(ji)) + + idx = Index( yline, '+' ) + if ( idx < 1 ) then + igroup = 1 + else + igroup = igroup_idx + igroup_idx = igroup_idx + 1 + end if + + do + idx = Index( yline, '+' ) + if ( idx < 1 ) then + ysrc = yline + else + ysrc = yline(1 : idx - 1) + yline = yline(idx + 1 :) + end if + + !Check if the source is known + if ( Len_trim( ysrc ) > 0 ) then + ipos = Source_find( tpbudget, ysrc ) + + if ( ipos > 0 ) then + call Print_msg( NVERB_DEBUG, 'BUD', 'Sourcelist_scan', 'source term ' // Trim( tpbudget%cname ) & + // ': ' // ysrc // ' found' ) + + if ( .not. tpbudget%tsources(ipos)%lavailable ) then + call Print_msg( NVERB_WARNING, 'BUD', 'Sourcelist_scan', 'source term ' // Trim( tpbudget%cname ) & + // ': ' // ysrc // ' not available' ) + tpbudget%tsources(ipos)%ngroup = 0 + else + tpbudget%tsources(ipos)%ngroup = igroup + end if + else + call Print_msg( NVERB_ERROR, 'BUD', 'Sourcelist_scan', 'source term ' // Trim( tpbudget%cname ) & + // ': ' // ysrc // ' not found' ) + end if + end if + + if ( idx < 1 ) exit + end do + end if + end do +end subroutine Sourcelist_scan + + +pure function Source_find( tpbudget, hsource ) result( ipos ) + use modd_budget, only: tbudgetdata + + type(tbudgetdata), intent(in) :: tpbudget + character(len=*), intent(in) :: hsource + integer :: ipos + + integer :: ji + logical :: gfound + + ipos = -1 + gfound = .false. + do ji = 1, tpbudget%nsourcesmax + if ( Trim( hsource ) == Trim ( tpbudget%tsources(ji)%cmnhname ) ) then + gfound = .true. + ipos = ji + exit + end if + end do + +end function Source_find + end module mode_ini_budget diff --git a/src/MNH/modd_budget.f90 b/src/MNH/modd_budget.f90 index 344de27ddfced1b2e1224fe6966fa7efe061b9ea..a6081a88c5e7c586c18249c32bd2e076271e8d2e 100644 --- a/src/MNH/modd_budget.f90 +++ b/src/MNH/modd_budget.f90 @@ -31,38 +31,22 @@ !! Original 23/02/95 !! J.-P. Lafore 10/02/98 adding of rhodj declaration for budget !! V. Ducrocq 4/06/99 // -!! J.-P. Pinty 25/09/00 additional budget terms for C2R2 scheme -!! D. Gazen 22/01/01 add NCHEMSV -!! V. Masson 06/11/02 new flags for budget calls and time counters -!! V. Masson 27/11/02 add 2way nesting effect -!! P. Jabouille 07/07/04 add budget terms for microphysics -!! C. Barthe 19/11/09 add budget terms for electricity -!! C.Lac 04/2016 negative contribution to the budget split between advection, turbulence and microphysics for KHKO/C2R2 -!! C. Barthe /16 add budget terms for LIMA -!! C. LAc 10/2016 add droplets deposition -!! S. Riette 11/2016 New budgets for ICE3/ICE4 ! P. Wautelet 05/2016-04/2018: new data structures and calls for I/O ! P. Wautelet 19/07/2019: parameters to identify budget number ! P. Wautelet 15/11/2019: remove unused CBURECORD variable ! P. Wautelet 17/01/2020: add new budget data types ! P. Wautelet 27/01/2020: use the tfield_metadata_base abstract datatype -! P. Wautelet 28/01/2020: add missing budgets for viscosity ! P. Wautelet 28/01/2020: add trhodj in tbudgetdata datatype -! B. Vie 03/02/2020: LIMA negativity checks after turbulence, advection and microphysics budgets ! P. Wautelet 09/03/2020: add tburhodj variable -! P .Wautelet 09/03/2020: add missing budgets for electricity ! P. Wautelet 17/04/2020: set default values for budgets switch values ! P. Wautelet 23/04/2020: add nid in tbudgetdata datatype -! P. Wautelet 30/06/2020: add NNETURSV, NNEADVSV and NNECONSV variables ! P. Wautelet 17/08/2020: add xtmplesstore in tbudgetdata datatype ! P. Wautelet 08/10/2020: add clessource in tbudgetdata datatype ! P. Wautelet 08/12/2020: add nbusubwrite and nbutotwrite ! P. Wautelet 11/01/2021: remove nbuwrnb (replaced by nbusubwrite) ! P. Wautelet 14/01/2021: change xbusurf type to integer (+ rename it to nbusurf) -! P. Wautelet 03/02/2021: add new source if LIMA splitting: CORR2 -! P. Wautelet 02/03/2021: add terms for blowing snow ! P. Wautelet 03/03/2021: add tbudiachrometadata type (useful to pass more information to Write_diachro) -! P. Wautelet 04/03/2021: add terms for drag due to buildings +! P. Wautelet 17/03/2021: choose source terms for budgets with character strings instead of multiple integer variables !------------------------------------------------------------------------------- ! !* 0. DECLARATIONS @@ -75,6 +59,9 @@ implicit none public +integer, parameter :: NBULISTMAXLEN = 512 +integer, parameter :: NBULISTMAXLINES = 40 + integer, parameter :: NBUDGET_RHO = 0 ! Reference number for budget of RhoJ integer, parameter :: NBUDGET_U = 1 ! Reference number for budget of RhoJu and/or LES budgets with u integer, parameter :: NBUDGET_V = 2 ! Reference number for budget of RhoJv and/or LES budgets with u @@ -99,7 +86,7 @@ type tbudgetdata character(len=100) :: clessource = '' ! Last source stored integer :: nid = -1 !Identifier number (based on parameters NBUDGET_*) integer :: ngroups = 0 !Number of groups of source terms to store - integer :: nsources = 0 !Number of source terms + integer :: nsources = 0 !Number of available source terms integer :: nsourcesmax = 0 !Maximum number of source terms integer :: ntmpstoresource = 0 !Reference of the source term using the xtmpstore array logical :: lenabled = .false. ! True if corresponding budget flag is set to true @@ -116,6 +103,8 @@ end type tbudgetdata type, extends( tfield_metadata_base ) :: tbusourcedata integer :: ngroup = 0 ! Number of the source term group in which storing the source term ! (0: no store, 1: individual store, >1: number of the group) + logical :: lavailable = .false. ! If true, the source is available in the run (conditions to access it are met), + ! but it doesn't mean it is used (see lenabled field) logical :: lenabled = .false. logical :: ldonotinit = .false. ! if true, does not need a call to Budget_store_init ! It may be true only if the source term is in a group not containing other sources @@ -149,6 +138,8 @@ type :: tbudiachrometadata integer :: nkh = -1 integer :: nsv = -1 !Reference number of the corresponding scalar variable end type tbudiachrometadata + + type(tbudgetdata), dimension(:), allocatable, save :: tbudgets type(tburhodata), pointer, save :: tburhodj => null() ! Budget array for rhodj used inside some tbudgets @@ -236,22 +227,7 @@ INTEGER, SAVE :: NBUKMAX ! dimension along K of the budget ! LOGICAL, SAVE :: LBU_RU = .FALSE. ! True when the budget of RU is performed ! -INTEGER, SAVE :: NASSEU = 0 ! time filter -INTEGER, SAVE :: NNESTU = 0 ! Efffect of 2way nesting on U -INTEGER, SAVE :: NADVU = 0 ! advection -INTEGER, SAVE :: NFRCU = 0 ! forcing -INTEGER, SAVE :: NNUDU = 0 ! nudging -INTEGER, SAVE :: NCURVU = 0 ! curvature -INTEGER, SAVE :: NCORU = 0 ! Coriolis terms -INTEGER, SAVE :: NDIFU = 0 ! numerical diffusion -INTEGER, SAVE :: NRELU = 0 ! relaxation -INTEGER, SAVE :: NHTURBU = 0 ! horizontal TURBulence -INTEGER, SAVE :: NVTURBU = 0 ! vertical turbulence -INTEGER, SAVE :: NDRAGU = 0 ! vegetation drag -INTEGER, SAVE :: NMAFLU = 0 ! mass flux -INTEGER, SAVE :: NPRESU = 0 ! pressure term -INTEGER, SAVE :: NVISCU = 0 ! viscosity -INTEGER, SAVE :: NDRAGBU = 0 ! buildings drag +CHARACTER(LEN=NBULISTMAXLEN), DIMENSION(NBULISTMAXLINES), SAVE :: CBULIST_RU = '' ! ! Allowed processes for the budget of RV (wind component along y) ! @@ -259,22 +235,7 @@ INTEGER, SAVE :: NDRAGBU = 0 ! buildings drag ! LOGICAL, SAVE :: LBU_RV = .FALSE. ! True when the budget of RV is performed ! -INTEGER, SAVE :: NASSEV = 0 ! time filter -INTEGER, SAVE :: NNESTV = 0 ! Efffect of 2way nesting on V -INTEGER, SAVE :: NADVV = 0 ! advection -INTEGER, SAVE :: NFRCV = 0 ! forcing -INTEGER, SAVE :: NNUDV = 0 ! nudging -INTEGER, SAVE :: NCURVV = 0 ! curvature -INTEGER, SAVE :: NCORV = 0 ! Coriolis terms -INTEGER, SAVE :: NDIFV = 0 ! numerical diffusion -INTEGER, SAVE :: NRELV = 0 ! relaxation -INTEGER, SAVE :: NHTURBV = 0 ! horizontal turbulence -INTEGER, SAVE :: NVTURBV = 0 ! vertical turbulence -INTEGER, SAVE :: NDRAGV = 0 ! vegetation drag -INTEGER, SAVE :: NMAFLV = 0 ! mass flux -INTEGER, SAVE :: NPRESV = 0 ! pressure term -INTEGER, SAVE :: NVISCV = 0 ! viscosity -INTEGER, SAVE :: NDRAGBV = 0 ! buildings drag +CHARACTER(LEN=NBULISTMAXLEN), DIMENSION(NBULISTMAXLINES), SAVE :: CBULIST_RV = '' ! ! Allowed processes for the budget of RW (wind vertical component) ! @@ -282,20 +243,7 @@ INTEGER, SAVE :: NDRAGBV = 0 ! buildings drag ! LOGICAL, SAVE :: LBU_RW = .FALSE. ! True when the budget of RW is performed ! -INTEGER, SAVE :: NASSEW = 0 ! time filter -INTEGER, SAVE :: NNESTW = 0 ! Efffect of 2way nesting on W -INTEGER, SAVE :: NADVW = 0 ! advection -INTEGER, SAVE :: NFRCW = 0 ! forcing -INTEGER, SAVE :: NNUDW = 0 ! nudging -INTEGER, SAVE :: NCURVW = 0 ! curvature -INTEGER, SAVE :: NCORW = 0 ! Coriolis terms -INTEGER, SAVE :: NGRAVW = 0 ! gravity term -INTEGER, SAVE :: NDIFW = 0 ! numerical diffusion -INTEGER, SAVE :: NRELW = 0 ! relaxation -INTEGER, SAVE :: NHTURBW = 0 ! horizontal turbulence -INTEGER, SAVE :: NVTURBW = 0 ! vertical turbulence -INTEGER, SAVE :: NPRESW = 0 ! pressure term -INTEGER, SAVE :: NVISCW = 0 ! viscosity +CHARACTER(LEN=NBULISTMAXLEN), DIMENSION(NBULISTMAXLINES), SAVE :: CBULIST_RW = '' ! ! Allowed processes for the budget of RTH (potential temperature) ! @@ -303,57 +251,7 @@ INTEGER, SAVE :: NVISCW = 0 ! viscosity ! LOGICAL, SAVE :: LBU_RTH = .FALSE. ! True when the budget of RTH is performed ! -INTEGER, SAVE :: NASSETH = 0 ! time filter -INTEGER, SAVE :: NNESTTH = 0 ! Efffect of 2way nesting on Th -INTEGER, SAVE :: NADVTH = 0 ! Total advection for PPM -INTEGER, SAVE :: NFRCTH = 0 ! forcing -INTEGER, SAVE :: N2DADVTH = 0 ! 2d advecting forcing -INTEGER, SAVE :: N2DRELTH = 0 ! 2d relaxation forcing -INTEGER, SAVE :: NNUDTH = 0 ! nudging -INTEGER, SAVE :: NPREFTH = 0 ! theta source term due to the reference pressure - ! (Dyn. Sources) only present if KRR>0 -INTEGER, SAVE :: NDIFTH = 0 ! numerical diffusion -INTEGER, SAVE :: NRELTH = 0 ! relaxation -INTEGER, SAVE :: NRADTH = 0 ! RADiation -INTEGER, SAVE :: NDCONVTH = 0 ! KAFR CONVection -INTEGER, SAVE :: NMAFLTH = 0 ! Mass flux -INTEGER, SAVE :: NSNSUBTH = 0 ! Blowing snow sublimation -INTEGER, SAVE :: NHTURBTH = 0 ! horizontal turbulence -INTEGER, SAVE :: NVTURBTH = 0 ! vertical turbulence -INTEGER, SAVE :: NDISSHTH = 0 ! dissipative heating -INTEGER, SAVE :: NNEGATH = 0 ! negative correction induced by hydrometeors -INTEGER, SAVE :: NNETURTH = 0 ! negative correction induced by hydrometeors -INTEGER, SAVE :: NNEADVTH = 0 ! negative correction induced by hydrometeors -INTEGER, SAVE :: NNECONTH = 0 ! negative correction induced by hydrometeors -INTEGER, SAVE :: NREVATH = 0 ! rain evaporation -INTEGER, SAVE :: NCONDTH = 0 ! evaporation/condensation -INTEGER, SAVE :: NHENUTH = 0 ! HEterogenous NUcleation ICE3 -INTEGER, SAVE :: NHONTH = 0 ! HOmogeneous Nucleation ICE3 -INTEGER, SAVE :: NSFRTH = 0 ! Spontaneous FReezing ICE3 -INTEGER, SAVE :: NDEPSTH = 0 ! DEPosition on Snow ICE3 -INTEGER, SAVE :: NDEPGTH = 0 ! DEPosition on Graupel ICE3 -INTEGER, SAVE :: NRIMTH = 0 ! RIMing of cloudwater ICE3 -INTEGER, SAVE :: NACCTH = 0 ! ACCretion of rainwater ICE3 -INTEGER, SAVE :: NCFRZTH = 0 ! Conversion FReeZing ICE3 -INTEGER, SAVE :: NWETGTH = 0 ! WET Growth of graupel ICE3 -INTEGER, SAVE :: NDRYGTH = 0 ! DRY Growth of graupel ICE3 -INTEGER, SAVE :: NGMLTTH = 0 ! Graupel MeLTing ICE3 -INTEGER, SAVE :: NIMLTTH = 0 ! Ice MeLTing ICE3 -INTEGER, SAVE :: NBERFITH = 0 ! BERgeron-FIndeisen gth. ICE3 -INTEGER, SAVE :: NCDEPITH = 0 ! Cond./DEPosition on ice ICE3 -INTEGER, SAVE :: NWETHTH = 0 ! wet growth of hail ICE4 -INTEGER, SAVE :: NDRYHTH = 0 ! dry growth of hail ICE4 -INTEGER, SAVE :: NHMLTTH = 0 ! melting of hail ICE4 -INTEGER, SAVE :: NADJUTH = 0 ! adjustement before rain_ice ICE3 -INTEGER, SAVE :: NCORRTH = 0 ! tendencies correction after ICE3 -INTEGER, SAVE :: NHINDTH = 0 ! Heterogeneous Nucleation by Deposition LIMA -INTEGER, SAVE :: NHINCTH = 0 ! Heterogeneous Nucleation by Contact LIMA -INTEGER, SAVE :: NHONHTH = 0 ! Haze Homogeneous Nucleation LIMA -INTEGER, SAVE :: NHONCTH = 0 ! droplet homogeneous nucleation LIMA -INTEGER, SAVE :: NHONRTH = 0 ! drop homogeneous nucleation LIMA -INTEGER, SAVE :: NCEDSTH = 0 ! adjustment -INTEGER, SAVE :: NSEDITH = 0 ! Temperature transport by hydrometeors sedimentation -INTEGER, SAVE :: NVISCTH = 0 ! viscosity +CHARACTER(LEN=NBULISTMAXLEN), DIMENSION(NBULISTMAXLINES), SAVE :: CBULIST_RTH = '' ! ! Allowed processes for the budget of RTKE (kinetic energy) ! @@ -361,18 +259,7 @@ INTEGER, SAVE :: NVISCTH = 0 ! viscosity ! LOGICAL, SAVE :: LBU_RTKE = .FALSE. ! True when the budget of RTKE is performed ! -INTEGER, SAVE :: NASSETKE = 0 ! time filter -INTEGER, SAVE :: NADVTKE = 0 ! Total advection for PPM -INTEGER, SAVE :: NFRCTKE = 0 ! forcing -INTEGER, SAVE :: NDIFTKE = 0 ! numerical diffusion -INTEGER, SAVE :: NRELTKE = 0 ! relaxation -INTEGER, SAVE :: NDPTKE = 0 ! dynamic production of TKE -INTEGER, SAVE :: NTPTKE = 0 ! thermal production of TKE -INTEGER, SAVE :: NDRAGTKE = 0 ! vegetation drag -INTEGER, SAVE :: NDISSTKE = 0 ! dissipation of TKE -INTEGER, SAVE :: NTRTKE = 0 ! turbulent transport of TKE -INTEGER, SAVE :: NDRAGBTKE = 0 ! buildings drag -! +CHARACTER(LEN=NBULISTMAXLEN), DIMENSION(NBULISTMAXLINES), SAVE :: CBULIST_RTKE = '' ! ! Allowed processes for the budget of moist variable RRV (water vapor) ! @@ -380,37 +267,7 @@ INTEGER, SAVE :: NDRAGBTKE = 0 ! buildings drag ! LOGICAL, SAVE :: LBU_RRV = .FALSE. ! true when the budget of RRV is performed ! -INTEGER, SAVE :: NASSERV = 0 ! time filter -INTEGER, SAVE :: NNESTRV = 0 ! Effect of 2way nesting on Rv -INTEGER, SAVE :: NADVRV = 0 ! Total advection for PPM -INTEGER, SAVE :: NFRCRV = 0 ! forcing -INTEGER, SAVE :: N2DADVRV = 0 ! 2d advecting forcing -INTEGER, SAVE :: N2DRELRV = 0 ! 2d relaxation forcing -INTEGER, SAVE :: NNUDRV = 0 ! nudging -INTEGER, SAVE :: NDIFRV = 0 ! numerical diffusion -INTEGER, SAVE :: NRELRV = 0 ! relaxation -INTEGER, SAVE :: NDCONVRV = 0 ! KAFR CONVection -INTEGER, SAVE :: NMAFLRV = 0 ! Mass flux -INTEGER, SAVE :: NSNSUBRV = 0 ! Blowing snow sublimation -INTEGER, SAVE :: NHTURBRV = 0 ! horizontal turbulence -INTEGER, SAVE :: NVTURBRV = 0 ! vertical turbulence -INTEGER, SAVE :: NNEGARV = 0 ! negative correction -INTEGER, SAVE :: NNETURRV = 0 ! negative correction -INTEGER, SAVE :: NNECONRV = 0 ! negative correction -INTEGER, SAVE :: NNEADVRV = 0 ! negative correction -INTEGER, SAVE :: NREVARV = 0 ! rain evaporation -INTEGER, SAVE :: NCONDRV = 0 ! evaporation/condensation -INTEGER, SAVE :: NHENURV = 0 ! HEterogenous NUcleation ICE3 -INTEGER, SAVE :: NDEPSRV = 0 ! DEPosition on Snow ICE3 -INTEGER, SAVE :: NDEPGRV = 0 ! DEPosition on Graupel ICE3 -INTEGER, SAVE :: NCDEPIRV = 0 ! Cond./DEPosition on ice ICE3 -INTEGER, SAVE :: NADJURV = 0 ! adjustement before rain_ice ICE3 -INTEGER, SAVE :: NCORRRV = 0 ! tendencies correction after ICE3 -INTEGER, SAVE :: NHINDRV = 0 ! Heterogeneous Nucleation by Deposition LIMA -INTEGER, SAVE :: NHONHRV = 0 ! Haze Homogeneous Nucleation LIMA -INTEGER, SAVE :: NCEDSRV = 0 ! adjustement -INTEGER, SAVE :: NVISCRV = 0 ! viscosity -INTEGER, SAVE :: NCORR2RV = 0 ! Correction in LIMA splitting +CHARACTER(LEN=NBULISTMAXLEN), DIMENSION(NBULISTMAXLINES), SAVE :: CBULIST_RRV = '' ! ! Allowed processes for the budget of moist variable RRC (cloud water) ! @@ -418,46 +275,7 @@ INTEGER, SAVE :: NCORR2RV = 0 ! Correction in LIMA splitting ! LOGICAL, SAVE :: LBU_RRC = .FALSE. ! True when the budget of RRC is performed ! -INTEGER, SAVE :: NASSERC = 0 ! time filter -INTEGER, SAVE :: NNESTRC = 0 ! Efffect of 2way nesting on Rc -INTEGER, SAVE :: NADVRC = 0 ! Total advection for PPM -INTEGER, SAVE :: NFRCRC = 0 ! forcing -INTEGER, SAVE :: NDIFRC = 0 ! numerical diffusion -INTEGER, SAVE :: NRELRC = 0 ! relaxation -INTEGER, SAVE :: NDCONVRC = 0 ! Deep CONVection -INTEGER, SAVE :: NHTURBRC = 0 ! horizontal turbulence -INTEGER, SAVE :: NVTURBRC = 0 ! vertical turbulence -INTEGER, SAVE :: NNEGARC = 0 ! negative correction -INTEGER, SAVE :: NNETURRC = 0 ! negative correction -INTEGER, SAVE :: NNECONRC = 0 ! negative correction -INTEGER, SAVE :: NNEADVRC = 0 ! negative correction -INTEGER, SAVE :: NACCRRC = 0 ! accretion -INTEGER, SAVE :: NAUTORC = 0 ! autoconversion -INTEGER, SAVE :: NCONDRC = 0 ! evaporation/condensation -INTEGER, SAVE :: NHONRC = 0 ! HOmogeneous Nucleation ICE3 -INTEGER, SAVE :: NRIMRC = 0 ! RIMing of cloudwater ICE3 -INTEGER, SAVE :: NCMELRC = 0 ! collection by snow and conversion into rain with T>XTT ICE3 -INTEGER, SAVE :: NWETGRC = 0 ! WET Growth of graupel ICE3 -INTEGER, SAVE :: NDRYGRC = 0 ! DRY Growth of graupel ICE3 -INTEGER, SAVE :: NIMLTRC = 0 ! Ice MeLTing ICE3 -INTEGER, SAVE :: NBERFIRC = 0 ! BERgeron-FIndeisen gth. ICE3 -INTEGER, SAVE :: NCDEPIRC = 0 ! Cond./DEPosition on ice ICE3 -INTEGER, SAVE :: NHENURC = 0 ! CCN Activation C2R2 -INTEGER, SAVE :: NSEDIRC = 0 ! sedimentation C2R2 -INTEGER, SAVE :: NDEPORC = 0 ! ground deposition -INTEGER, SAVE :: NDEPOTRRC = 0 ! deposition on tree -INTEGER, SAVE :: NWETHRC = 0 ! wet growth of hail -INTEGER, SAVE :: NDRYHRC = 0 ! dry growth of hail ICE4 -INTEGER, SAVE :: NADJURC = 0 ! adjustement before rain_ice ICE3 -INTEGER, SAVE :: NHINCRC = 0 ! Heterogeneous Nucleation by Contact LIMA -INTEGER, SAVE :: NHONCRC = 0 ! droplet homogeneous nucleation LIMA -INTEGER, SAVE :: NCEDSRC = 0 ! adjustment LIMA -INTEGER, SAVE :: NREVARC = 0 ! evaporation of rain drops -INTEGER, SAVE :: NCORRRC = 0 ! rain <-> cloud transfer at the beginning of LIMA -INTEGER, SAVE :: NR2C1RC = 0 ! rain -> cloud change after sedimentation in LIMA -INTEGER, SAVE :: NCVRCRC = 0 ! rain -> cloud change after other microphysical processes in LIMA -INTEGER, SAVE :: NVISCRC = 0 ! viscosity -INTEGER, SAVE :: NCORR2RC = 0 ! Correction in LIMA splitting +CHARACTER(LEN=NBULISTMAXLEN), DIMENSION(NBULISTMAXLINES), SAVE :: CBULIST_RRC = '' ! ! Allowed processes for the budget of moist variable RRR (rain water) ! @@ -465,36 +283,7 @@ INTEGER, SAVE :: NCORR2RC = 0 ! Correction in LIMA splitting ! LOGICAL, SAVE :: LBU_RRR = .FALSE. ! True when the budget of RRR is performed ! -INTEGER, SAVE :: NASSERR = 0 ! time filter -INTEGER, SAVE :: NNESTRR = 0 ! Efffect of 2way nesting on Rr -INTEGER, SAVE :: NADVRR = 0 ! Total advection for PPM -INTEGER, SAVE :: NFRCRR = 0 ! forcing -INTEGER, SAVE :: NDIFRR = 0 ! numerical diffusion -INTEGER, SAVE :: NRELRR = 0 ! relaxation -INTEGER, SAVE :: NNEGARR = 0 ! negative correction -INTEGER, SAVE :: NNETURRR = 0 ! negative correction -INTEGER, SAVE :: NNEADVRR = 0 ! negative correction -INTEGER, SAVE :: NNECONRR = 0 ! negative correction -INTEGER, SAVE :: NACCRRR = 0 ! accretion -INTEGER, SAVE :: NAUTORR = 0 ! autoconversion -INTEGER, SAVE :: NREVARR = 0 ! rain evaporation -INTEGER, SAVE :: NSEDIRR = 0 ! sedimentation -INTEGER, SAVE :: NSFRRR = 0 ! Spontaneous FReezing ICE3 -INTEGER, SAVE :: NACCRR = 0 ! ACCretion of rainwater ICE3 -INTEGER, SAVE :: NCMELRR = 0 ! collection of droplets by snow and conversion into rain with T>XTT ICE3 -INTEGER, SAVE :: NCFRZRR = 0 ! Conversion FReeZing ICE3 -INTEGER, SAVE :: NWETGRR = 0 ! WET Growth of graupel ICE3 -INTEGER, SAVE :: NDRYGRR = 0 ! DRY Growth of graupel ICE3 -INTEGER, SAVE :: NGMLTRR = 0 ! Graupel MeLTing ICE3 -INTEGER, SAVE :: NWETHRR = 0 ! wet growth of hail ICE4 -INTEGER, SAVE :: NDRYHRR = 0 ! dry growth of hail ICE4 -INTEGER, SAVE :: NHMLTRR = 0 ! melting of hail ICE4 -INTEGER, SAVE :: NCORRRR = 0 ! tendencies correction after ICE3 -INTEGER, SAVE :: NHONRRR = 0 ! drop homogeneous nucleation LIMA -INTEGER, SAVE :: NR2C1RR = 0 ! rain -> cloud change after sedimentation in LIMA -INTEGER, SAVE :: NCVRCRR = 0 ! rain -> cloud change after other microphysical processes in LIMA -INTEGER, SAVE :: NVISCRR = 0 ! viscosity -INTEGER, SAVE :: NCORR2RR = 0 ! Correction in LIMA splitting +CHARACTER(LEN=NBULISTMAXLEN), DIMENSION(NBULISTMAXLINES), SAVE :: CBULIST_RRR = '' ! ! Allowed processes for the budget of moist variable RRI (ice) ! @@ -502,45 +291,7 @@ INTEGER, SAVE :: NCORR2RR = 0 ! Correction in LIMA splitting ! LOGICAL, SAVE :: LBU_RRI = .FALSE. ! True when the budget of RRI is performed ! -INTEGER, SAVE :: NASSERI = 0 ! time filter -INTEGER, SAVE :: NNESTRI = 0 ! Efffect of 2way nesting on Ri -INTEGER, SAVE :: NADVRI = 0 ! Total advection for PPM -INTEGER, SAVE :: NFRCRI = 0 ! forcing -INTEGER, SAVE :: NDIFRI = 0 ! numerical diffusion -INTEGER, SAVE :: NRELRI = 0 ! relaxation -INTEGER, SAVE :: NDCONVRI = 0 ! Deep CONVection -INTEGER, SAVE :: NHTURBRI = 0 ! horizontal turbulence -INTEGER, SAVE :: NVTURBRI = 0 ! vertical turbulence -INTEGER, SAVE :: NNEGARI = 0 ! negative correction -INTEGER, SAVE :: NNETURRI = 0 ! negative correction -INTEGER, SAVE :: NNEADVRI = 0 ! negative correction -INTEGER, SAVE :: NNECONRI = 0 ! negative correction -INTEGER, SAVE :: NSEDIRI = 0 ! SEDImentation ICE3 -INTEGER, SAVE :: NHENURI = 0 ! HEterogenous NUcleation ICE3 -INTEGER, SAVE :: NHONRI = 0 ! HOmogeneous Nucleation ICE3 -INTEGER, SAVE :: NAGGSRI = 0 ! AGGregation of snow ICE3 -INTEGER, SAVE :: NAUTSRI = 0 ! AUToconversion of ice ICE3 -INTEGER, SAVE :: NCFRZRI = 0 ! Conversion FReeZing ICE3 -INTEGER, SAVE :: NWETGRI = 0 ! WET Growth of graupel ICE3 -INTEGER, SAVE :: NDRYGRI = 0 ! DRY Growth of graupel ICE3 -INTEGER, SAVE :: NIMLTRI = 0 ! Ice MeLTing ICE3 -INTEGER, SAVE :: NBERFIRI = 0 ! BERgeron-FIndeisen gth. ICE3 -INTEGER, SAVE :: NCDEPIRI = 0 ! Cond./DEPosition on ice ICE3 -INTEGER, SAVE :: NWETHRI = 0 ! wet growth of hail ICE4 -INTEGER, SAVE :: NDRYHRI = 0 ! dry growth of hail ICE4 -INTEGER, SAVE :: NADJURI = 0 ! adjustement before rain_ice ICE3 -INTEGER, SAVE :: NHINDRI = 0 ! heterogeneous nucleation by deposition LIMA -INTEGER, SAVE :: NHINCRI = 0 ! heterogeneous nucleation by contact LIMA -INTEGER, SAVE :: NHONHRI = 0 ! haze homogeneous nucleation source LIMA -INTEGER, SAVE :: NHONCRI = 0 ! droplet homogeneous nucleation LIMA -INTEGER, SAVE :: NCNVIRI = 0 ! Conversion of snow to r_i LIMA -INTEGER, SAVE :: NCNVSRI = 0 ! Conversion of pristine ice to r_s LIMA -INTEGER, SAVE :: NHMSRI = 0 ! Hallett-Mossop ice multiplication process due to snow riming LIMA -INTEGER, SAVE :: NHMGRI = 0 ! Hallett-Mossop ice multiplication process due to graupel riming LIMA -INTEGER, SAVE :: NCEDSRI = 0 ! adjustement LIMA -INTEGER, SAVE :: NCORRRI = 0 ! ice <-> snow transfer at the beginning of LIMA -INTEGER, SAVE :: NVISCRI = 0 ! viscosity -INTEGER, SAVE :: NCORR2RI = 0 ! Correction in LIMA splitting +CHARACTER(LEN=NBULISTMAXLEN), DIMENSION(NBULISTMAXLINES), SAVE :: CBULIST_RRI = '' ! ! Allowed processes for the budget of moist variable RRS (snow) ! @@ -548,32 +299,7 @@ INTEGER, SAVE :: NCORR2RI = 0 ! Correction in LIMA splitting ! LOGICAL, SAVE :: LBU_RRS = .FALSE. ! True when the budget of RRS is performed ! -INTEGER, SAVE :: NASSERS = 0 ! time filter -INTEGER, SAVE :: NNESTRS = 0 ! Efffect of 2way nesting on Rs -INTEGER, SAVE :: NADVRS = 0 ! Total advection for PPM -INTEGER, SAVE :: NFRCRS = 0 ! forcing -INTEGER, SAVE :: NDIFRS = 0 ! numerical diffusion -INTEGER, SAVE :: NRELRS = 0 ! relaxation -INTEGER, SAVE :: NNEGARS = 0 ! negative correction -INTEGER, SAVE :: NNETURRS = 0 ! negative correction -INTEGER, SAVE :: NNEADVRS = 0 ! negative correction -INTEGER, SAVE :: NNECONRS = 0 ! negative correction -INTEGER, SAVE :: NSEDIRS = 0 ! SEDImentation ICE3 -INTEGER, SAVE :: NDEPSRS = 0 ! DEPosition on Snow ICE3 -INTEGER, SAVE :: NAGGSRS = 0 ! AGGregation of snow ICE3 -INTEGER, SAVE :: NAUTSRS = 0 ! AUToconversion of ice ICE3 -INTEGER, SAVE :: NRIMRS = 0 ! RIMing of cloudwater ICE3 -INTEGER, SAVE :: NACCRS = 0 ! ACCretion of rainwater ICE3 -INTEGER, SAVE :: NCMELRS = 0 ! Conversion MeLTing ICE3 -INTEGER, SAVE :: NWETGRS = 0 ! WET Growth of graupel ICE3 -INTEGER, SAVE :: NDRYGRS = 0 ! DRY Growth of graupel ICE3 -INTEGER, SAVE :: NWETHRS = 0 ! wet growth of hail ICE4 -INTEGER, SAVE :: NDRYHRS = 0 ! dry growth of hail ICE4 -INTEGER, SAVE :: NCNVIRS = 0 ! Conversion of snow to r_i LIMA -INTEGER, SAVE :: NCNVSRS = 0 ! Conversion of pristine ice to r_s LIMA -INTEGER, SAVE :: NHMSRS = 0 ! Hallett-Mossop ice multiplication process due to snow riming LIMA -INTEGER, SAVE :: NCORRRS = 0 ! ice <-> snow transfer at the beginning of LIMA -INTEGER, SAVE :: NVISCRS = 0 ! viscosity +CHARACTER(LEN=NBULISTMAXLEN), DIMENSION(NBULISTMAXLINES), SAVE :: CBULIST_RRS = '' ! ! Allowed processes for the budget of moist variable RRG (graupel) ! @@ -581,35 +307,7 @@ INTEGER, SAVE :: NVISCRS = 0 ! viscosity ! LOGICAL, SAVE :: LBU_RRG = .FALSE. ! True when the budget of RRG is performed ! -INTEGER, SAVE :: NASSERG = 0 ! time filter -INTEGER, SAVE :: NNESTRG = 0 ! Efffect of 2way nesting on Rg -INTEGER, SAVE :: NADVRG = 0 ! Total advection for PPM -INTEGER, SAVE :: NFRCRG = 0 ! forcing -INTEGER, SAVE :: NDIFRG = 0 ! numerical diffusion -INTEGER, SAVE :: NRELRG = 0 ! relaxation -INTEGER, SAVE :: NNEGARG = 0 ! negative correction -INTEGER, SAVE :: NNETURRG = 0 ! negative correction -INTEGER, SAVE :: NNEADVRG = 0 ! negative correction -INTEGER, SAVE :: NNECONRG = 0 ! negative correction -INTEGER, SAVE :: NSEDIRG = 0 ! SEDImentation ICE3 -INTEGER, SAVE :: NSFRRG = 0 ! Spontaneous FReezing ICE3 -INTEGER, SAVE :: NDEPGRG = 0 ! DEPosition on Snow ICE3 -INTEGER, SAVE :: NRIMRG = 0 ! RIMing of cloudwater ICE3 -INTEGER, SAVE :: NACCRG = 0 ! ACCretion of rainwater ICE3 -INTEGER, SAVE :: NCMELRG = 0 ! Conversion MeLTing ICE3 -INTEGER, SAVE :: NCFRZRG = 0 ! Conversion FReeZing ICE3 -INTEGER, SAVE :: NWETGRG = 0 ! WET Growth of graupel ICE3 -INTEGER, SAVE :: NDRYGRG = 0 ! DRY Growth of graupel ICE3 -INTEGER, SAVE :: NGMLTRG = 0 ! Graupel MeLTing ICE3 -INTEGER, SAVE :: NWETHRG = 0 ! wet growth of hail ICE4 -INTEGER, SAVE :: NDRYHRG = 0 ! dry growth of hail ICE4 -INTEGER, SAVE :: NCORRRG = 0 ! tendencies correction after ICE3 -INTEGER, SAVE :: NHGCVRG = 0 ! Hail to Graupel ConVersion ICE4 -INTEGER, SAVE :: NGHCVRG = 0 ! Graupel to Hail ConVersion ICE4 -INTEGER, SAVE :: NHONRRG = 0 ! drop homogeneous nucleation LIMA -INTEGER, SAVE :: NHMGRG = 0 ! Hallett-Mossop ice multiplication process due to graupel riming -INTEGER, SAVE :: NCOHGRG = 0 ! conversion of hail to graupel -INTEGER, SAVE :: NVISCRG = 0 ! viscosity +CHARACTER(LEN=NBULISTMAXLEN), DIMENSION(NBULISTMAXLINES), SAVE :: CBULIST_RRG = '' ! ! Allowed processes for the budget of moist variable RRH (hail) ! @@ -617,151 +315,13 @@ INTEGER, SAVE :: NVISCRG = 0 ! viscosity ! LOGICAL, SAVE :: LBU_RRH = .FALSE. ! True when the budget of RRH is performed ! -INTEGER, SAVE :: NASSERH = 0 ! time filter -INTEGER, SAVE :: NNESTRH = 0 ! Efffect of 2way nesting on Rh -INTEGER, SAVE :: NADVRH = 0 ! Total advection for PPM -INTEGER, SAVE :: NFRCRH = 0 ! forcing -INTEGER, SAVE :: NDIFRH = 0 ! numerical diffusion -INTEGER, SAVE :: NRELRH = 0 ! relaxation -INTEGER, SAVE :: NNEGARH = 0 ! negative correction -INTEGER, SAVE :: NNETURRH = 0 ! negative correction -INTEGER, SAVE :: NNEADVRH = 0 ! negative correction -INTEGER, SAVE :: NNECONRH = 0 ! negative correction -INTEGER, SAVE :: NSEDIRH = 0 ! sedimentation -INTEGER, SAVE :: NWETGRH = 0 ! wet growth of graupel -INTEGER, SAVE :: NWETHRH = 0 ! wet growth of hail -INTEGER, SAVE :: NCOHGRH = 0 ! reconversion from hail to graupel LIMA -INTEGER, SAVE :: NDRYHRH = 0 ! dry growth of hail ICE4 -INTEGER, SAVE :: NHMLTRH = 0 ! melting -INTEGER, SAVE :: NCORRRH = 0 ! tendencies correction after ICE3 -INTEGER, SAVE :: NHGCVRH = 0 ! Hail to Graupel ConVersion ICE4 -INTEGER, SAVE :: NGHCVRH = 0 ! Graupel to Hail ConVersion ICE4 -INTEGER, SAVE :: NVISCRH = 0 ! viscosity +CHARACTER(LEN=NBULISTMAXLEN), DIMENSION(NBULISTMAXLINES), SAVE :: CBULIST_RRH = '' ! ! Courant namelist: NAM_BURSV ! LOGICAL, SAVE :: LBU_RSV = .FALSE. ! True when the budget of RSVx is performed ! -INTEGER, SAVE :: NASSESV = 0 ! Asselin-Robert time filter -INTEGER, SAVE :: NNESTSV = 0 ! Efffect of 2way nesting on Sv -INTEGER, SAVE :: NADVSV = 0 ! Total advection for PPM -INTEGER, SAVE :: NFRCSV = 0 ! forcing -INTEGER, SAVE :: NDIFSV = 0 ! numerical diffusion -INTEGER, SAVE :: NRELSV = 0 ! relaxation -INTEGER, SAVE :: NDCONVSV = 0 ! Deep CONVection -INTEGER, SAVE :: NMAFLSV = 0 ! mass flux -INTEGER, SAVE :: NDEPOTRSV = 0 ! deposition on tree -INTEGER, SAVE :: NHTURBSV = 0 ! horizontal turbulence -INTEGER, SAVE :: NVTURBSV = 0 ! vertical turbulence -INTEGER, SAVE :: NCHEMSV = 0 ! chemistry activity -INTEGER, SAVE :: NVISCSV = 0 ! viscosity -INTEGER, SAVE :: NSNSUBSV = 0 ! Blowing snow sublimation -INTEGER, SAVE :: NSNSEDSV = 0 ! Blowing snow sedimentation -! -INTEGER, SAVE :: NNEGASV = 0 ! negative correction -INTEGER, SAVE :: NNETURSV = 0 ! negative correction -INTEGER, SAVE :: NNEADVSV = 0 ! negative correction -INTEGER, SAVE :: NNECONSV = 0 ! negative correction -INTEGER, SAVE :: NNEGA2SV = 0 ! negative correction -! -! Allowed processes for the budget of electric charge carried by water vapor -INTEGER, SAVE :: NDRIFTQV = 0 -INTEGER, SAVE :: NCORAYQV = 0 -INTEGER, SAVE :: NDEPSQV = 0 -INTEGER, SAVE :: NDEPGQV = 0 -INTEGER, SAVE :: NREVAQV = 0 -INTEGER, SAVE :: NCDEPIQV = 0 -INTEGER, SAVE :: NNEUTQV = 0 -! -! Allowed processes for the budget of electric charge carried by cloud droplets -INTEGER, SAVE :: NHONQC = 0 -INTEGER, SAVE :: NAUTOQC = 0 -INTEGER, SAVE :: NACCRQC = 0 -INTEGER, SAVE :: NRIMQC = 0 -INTEGER, SAVE :: NWETGQC = 0 -INTEGER, SAVE :: NDRYGQC = 0 -INTEGER, SAVE :: NINCGQC = 0 -INTEGER, SAVE :: NWETHQC = 0 -INTEGER, SAVE :: NIMLTQC = 0 -INTEGER, SAVE :: NBERFIQC = 0 -INTEGER, SAVE :: NSEDIQC = 0 -INTEGER, SAVE :: NCDEPIQC = 0 -INTEGER, SAVE :: NNEUTQC = 0 -! -! Allowed processes for the budget of electric charge carried by rain drops -INTEGER, SAVE :: NSFRQR = 0 -INTEGER, SAVE :: NAUTOQR = 0 -INTEGER, SAVE :: NACCRQR = 0 -INTEGER, SAVE :: NREVAQR = 0 -INTEGER, SAVE :: NACCQR = 0 -INTEGER, SAVE :: NCFRZQR = 0 -INTEGER, SAVE :: NWETGQR = 0 -INTEGER, SAVE :: NDRYGQR = 0 -INTEGER, SAVE :: NGMLTQR = 0 -INTEGER, SAVE :: NWETHQR = 0 -INTEGER, SAVE :: NHMLTQR = 0 -INTEGER, SAVE :: NSEDIQR = 0 -INTEGER, SAVE :: NNEUTQR = 0 -! -! Allowed processes for the budget of electric charge carried by ice crystals -INTEGER, SAVE :: NHONQI = 0 -INTEGER, SAVE :: NAGGSQI = 0 -INTEGER, SAVE :: NAUTSQI = 0 -INTEGER, SAVE :: NCFRZQI = 0 -INTEGER, SAVE :: NWETGQI = 0 -INTEGER, SAVE :: NDRYGQI = 0 -INTEGER, SAVE :: NWETHQI = 0 -INTEGER, SAVE :: NIMLTQI = 0 -INTEGER, SAVE :: NBERFIQI = 0 -INTEGER, SAVE :: NNIISQI = 0 ! non-inductive I-S -INTEGER, SAVE :: NSEDIQI = 0 -INTEGER, SAVE :: NCDEPIQI = 0 -INTEGER, SAVE :: NNEUTQI = 0 -! -! Allowed processes for the budget of electric charge carried by snow -INTEGER, SAVE :: NDEPSQS = 0 -INTEGER, SAVE :: NAGGSQS = 0 -INTEGER, SAVE :: NAUTSQS = 0 -INTEGER, SAVE :: NRIMQS = 0 -INTEGER, SAVE :: NACCQS = 0 -INTEGER, SAVE :: NCMELQS = 0 -INTEGER, SAVE :: NWETGQS = 0 -INTEGER, SAVE :: NDRYGQS = 0 -INTEGER, SAVE :: NNIISQS = 0 ! non-inductive I-S -INTEGER, SAVE :: NWETHQS = 0 -INTEGER, SAVE :: NSEDIQS = 0 -INTEGER, SAVE :: NNEUTQS = 0 -! -! Allowed processes for the budget of electric charge carried by graupel -INTEGER, SAVE :: NSFRQG = 0 -INTEGER, SAVE :: NDEPGQG = 0 -INTEGER, SAVE :: NRIMQG = 0 -INTEGER, SAVE :: NACCQG = 0 -INTEGER, SAVE :: NCMELQG = 0 -INTEGER, SAVE :: NCFRZQG = 0 -INTEGER, SAVE :: NWETGQG = 0 -INTEGER, SAVE :: NDRYGQG = 0 -INTEGER, SAVE :: NINCGQG = 0 -INTEGER, SAVE :: NGMLTQG = 0 -INTEGER, SAVE :: NWETHQG = 0 -INTEGER, SAVE :: NSEDIQG = 0 -INTEGER, SAVE :: NNEUTQG = 0 -! -! Allowed processes for the budget of electric charge carried by hail -INTEGER, SAVE :: NWETGQH = 0 -INTEGER, SAVE :: NWETHQH = 0 -INTEGER, SAVE :: NHMLTQH = 0 -INTEGER, SAVE :: NSEDIQH = 0 -INTEGER, SAVE :: NNEUTQH = 0 -! -! Allowed processes for the budget of electric charge carried by negative ions -INTEGER, SAVE :: NDRIFTNI = 0 -INTEGER, SAVE :: NCORAYNI = 0 -INTEGER, SAVE :: NDEPSNI = 0 -INTEGER, SAVE :: NDEPGNI = 0 -INTEGER, SAVE :: NREVANI = 0 -INTEGER, SAVE :: NCDEPINI = 0 -INTEGER, SAVE :: NNEUTNI = 0 +CHARACTER(LEN=NBULISTMAXLEN), DIMENSION(NBULISTMAXLINES), SAVE :: CBULIST_RSV = '' ! ! REAL :: XTIME_BU ! budget time in this time-step diff --git a/src/MNH/modn_budget.f90 b/src/MNH/modn_budget.f90 index 0c698002d79314670ac41437a6d7cc2a5c839f4b..1cfc6d39117b4f0a1a1647dea57a35204cfaceec 100644 --- a/src/MNH/modn_budget.f90 +++ b/src/MNH/modn_budget.f90 @@ -215,21 +215,7 @@ !! MODIFICATIONS !! ------------- !! Original 01/03/95 -!! J. Stein 29/06/95 new processes' list -!! J.-P. Pinty 11/01/97 add several SVx -!! J.-P. Pinty 18/02/97 add forcing and ice -!! J.-P. Pinty 25/09/00 add budget terms for C2R2 -!! D. Gazen 22/01/01 add NCHEMSV -!! C.Lac 04/2016 negative contribution to the budget split between advection, turbulence and microphysics for KHKO/C2R2 -!! C. Barthe /16 add budget terms for LIMA -!! C.Lac 10/2016 Add droplet deposition -!! S. Riette 11/2016 New budgets for ICE3/ICE4 -! P. Wautelet 28/01/2020: add missing budgets for viscosity -! B. Vie 03/02/2020: LIMA negativity checks after turbulence, advection and microphysics budgets -! P. Wautelet 09/03/2020: add missing budgets for electricity -! P. Wautelet 30/06/2020: add NNETURSV, NNEADVSV and NNECONSV variables -! P. Wautelet 02/03/2021: budgets: add terms for blowing snow -! P. Wautelet 04/03/2021: add terms for drag due to buildings +! P. Wautelet 17/03/2021: choose source terms for budgets with character strings instead of multiple integer variables !------------------------------------------------------------------------------- ! !* 0. DECLARATIONS @@ -242,87 +228,30 @@ IMPLICIT NONE NAMELIST/NAM_BUDGET/CBUTYPE, NBUMOD, XBULEN, NBUKL, NBUKH, LBU_KCP, XBUWRI, & NBUIL, NBUIH, NBUJL, NBUJH, LBU_ICP, LBU_JCP, NBUMASK ! -NAMELIST/NAM_BU_RU/LBU_RU, NASSEU, NNESTU, NADVU, NFRCU, NNUDU, & - NCURVU, NCORU, NDIFU, NRELU, NDRAGU, NDRAGBU, NHTURBU, NVTURBU, NMAFLU, NPRESU, NVISCU +NAMELIST/NAM_BU_RU/LBU_RU, CBULIST_RU ! -NAMELIST/NAM_BU_RV/LBU_RV, NASSEV, NNESTV, NADVV, NFRCV, NNUDV, & - NCURVV, NCORV, NDIFV, NRELV, NDRAGV, NDRAGBV, NHTURBV, NVTURBV, NMAFLV, NPRESV, NVISCV +NAMELIST/NAM_BU_RV/LBU_RV, CBULIST_RV -NAMELIST/NAM_BU_RW/LBU_RW, NASSEW, NNESTW, NADVW, NFRCW, NNUDW, & - NCURVW, NCORW, NGRAVW, NDIFW, NRELW, NHTURBW, NVTURBW, NPRESW, NVISCW +NAMELIST/NAM_BU_RW/LBU_RW, CBULIST_RW ! -NAMELIST/NAM_BU_RTH/LBU_RTH, NASSETH, NNESTTH, NADVTH, NFRCTH, & - NNUDTH, NPREFTH, NDIFTH, NRELTH, NRADTH, NDCONVTH, NHTURBTH, & - NVTURBTH, NDISSHTH, NNEGATH, NREVATH, NCONDTH, NHENUTH, NHONTH, & - NSFRTH, NDEPSTH, NDEPGTH,NRIMTH, NACCTH, NCFRZTH, NWETGTH, & - NDRYGTH, NGMLTTH, NIMLTTH, NBERFITH, NCDEPITH, NWETHTH, NHMLTTH, & - NMAFLTH, NSNSUBTH, NNETURTH, NNEADVTH,NNECONTH, NDRYHTH, NADJUTH, NCORRTH, & - NHINDTH, NHINCTH, NHONHTH, NHONCTH, NHONRTH, NCEDSTH, NSEDITH, NVISCTH +NAMELIST/NAM_BU_RTH/LBU_RTH, CBULIST_RTH ! -NAMELIST/NAM_BU_RTKE/LBU_RTKE, NASSETKE, NADVTKE, & - NFRCTKE, NDIFTKE, NRELTKE, NDRAGTKE, NDRAGBTKE, & - NDPTKE, NTPTKE, NDISSTKE, NTRTKE +NAMELIST/NAM_BU_RTKE/LBU_RTKE, CBULIST_RTKE ! -NAMELIST/NAM_BU_RRV/LBU_RRV, NASSERV, NNESTRV, NADVRV, NFRCRV, & - NNUDRV, NDIFRV, NRELRV, NDCONVRV, NHTURBRV, NVTURBRV, NNEGARV, & - NREVARV, NCONDRV, NHENURV, NDEPSRV, NDEPGRV, NCDEPIRV, NMAFLRV, NSNSUBRV, & - NNETURRV, NNEADVRV,NNECONRV, NADJURV, NCORRRV, NHINDRV, NHONHRV, NCEDSRV, NVISCRV +NAMELIST/NAM_BU_RRV/LBU_RRV, CBULIST_RRV ! -NAMELIST/NAM_BU_RRC/LBU_RRC, NASSERC, NNESTRC, NADVRC, NFRCRC, & - NDIFRC, NRELRC, NDCONVRC, NHTURBRC, NVTURBRC, NNEGARC, NACCRRC, & - NAUTORC, NCONDRC, NHONRC, NRIMRC, NWETGRC, NDRYGRC, NIMLTRC, & - NBERFIRC, NCDEPIRC, NHENURC, NSEDIRC, NWETHRC, NNETURRC, & - NNEADVRC,NNECONRC, NDRYHRC, NADJURC, NCORRRC, NCMELRC, & - NHINCRC, NHONCRC, NCEDSRC, NREVARC, NDEPORC,NDEPOTRRC, & - NCORRRC, NR2C1RC, NCVRCRC, NVISCRC +NAMELIST/NAM_BU_RRC/LBU_RRC, CBULIST_RRC ! -NAMELIST/NAM_BU_RRR/LBU_RRR, NASSERR, NNESTRR, NADVRR, NFRCRR, & - NDIFRR, NRELRR, NNEGARR, NACCRRR, NAUTORR, NREVARR, NSEDIRR, & - NSFRRR, NACCRR, NCFRZRR, NWETGRR, NDRYGRR, NGMLTRR, NWETHRR, & - NHMLTRR, NDRYHRR, NCORRRR, NCMELRR,NHONRRR, NCORRRR, NR2C1RR, NCVRCRR, & - NNETURRR, NNEADVRR, NNECONRR, NVISCRR +NAMELIST/NAM_BU_RRR/LBU_RRR, CBULIST_RRR ! -NAMELIST/NAM_BU_RRI/LBU_RRI, NASSERI, NNESTRI, NADVRI, NFRCRI, & - NDIFRI, NRELRI, NDCONVRI, NHTURBRI, NVTURBRI, NNEGARI, NSEDIRI, & - NHENURI, NHONRI, NAGGSRI, NAUTSRI, NCFRZRI, NWETGRI, NDRYGRI, & - NIMLTRI, NBERFIRI, NCDEPIRI, NWETHRI, NDRYHRI, NADJURI, NCORRRI, & - NHINDRI, NHINCRI, NHONHRI, NHONCRI, NCNVIRI, NCNVSRI, & - NHMSRI, NHMGRI, NCEDSRI, NCORRRI, & - NNETURRI, NNEADVRI, NNECONRI, NVISCRI +NAMELIST/NAM_BU_RRI/LBU_RRI, CBULIST_RRI ! -NAMELIST/NAM_BU_RRS/LBU_RRS, NASSERS, NNESTRS, NADVRS, NFRCRS, & - NDIFRS, NRELRS, NNEGARS, NSEDIRS, NDEPSRS, NAGGSRS, NAUTSRS, & - NRIMRS, NACCRS, NCMELRS, NWETGRS, NDRYGRS, NWETHRS, NDRYHRS, & - NCORRRS, NCNVIRS, NCNVSRS, NHMSRS, NCORRRS, & - NNETURRS, NNEADVRS, NNECONRS, NVISCRS +NAMELIST/NAM_BU_RRS/LBU_RRS, CBULIST_RRS ! -NAMELIST/NAM_BU_RRG/LBU_RRG, NASSERG, NNESTRG, NADVRG, NFRCRG, & - NDIFRG, NRELRG, NNEGARG, NSEDIRG, NSFRRG, NDEPGRG, NRIMRG, NACCRG, & - NCMELRG, NCFRZRG, NWETGRG, NDRYGRG, NGMLTRG, NWETHRG, & - NDRYHRG, NCORRRG, NHGCVRG, NGHCVRG,NHONRRG, NHMGRG, NCOHGRG, & - NNETURRG, NNEADVRG, NNECONRG, NVISCRG +NAMELIST/NAM_BU_RRG/LBU_RRG, CBULIST_RRG ! -NAMELIST/NAM_BU_RRH/LBU_RRH, NASSERH, NNESTRH, NADVRH, NFRCRH, & - NDIFRH, NRELRH, NNEGARH, NSEDIRH, NWETGRH, NWETHRH, NDRYHRH, NHMLTRH, & - NCORRRH, NHGCVRH, NGHCVRH, NCOHGRH, NHMLTRH, & - NNETURRH, NNEADVRH, NNECONRH, NVISCRH -! -NAMELIST/NAM_BU_RSV/ LBU_RSV, NASSESV, NNESTSV, NADVSV, NFRCSV, & - NDIFSV, NRELSV, NDCONVSV, NVTURBSV, NHTURBSV, NCHEMSV, NMAFLSV, & - NVISCSV, NSNSUBSV, NSNSEDSV, NNEGASV, NNETURSV, NNEADVSV, NNECONSV, NNEGA2SV, & - NDRIFTQV, NCORAYQV, NDEPSQV, NDEPGQV, NREVAQV, NCDEPIQV, NNEUTQV, & - NHONQC, NAUTOQC, NACCRQC, NRIMQC, NWETGQC, NDRYGQC, NINCGQC, NWETHQC, & - NIMLTQC, NBERFIQC, NSEDIQC, NCDEPIQC, NNEUTQC, & - NSFRQR, NAUTOQR, NACCRQR, NREVAQR, NACCQR, NCFRZQR, NWETGQR, NDRYGQR, & - NGMLTQR, NWETHQR, NHMLTQR, NSEDIQR, NNEUTQR, & - NHONQI, NAGGSQI, NAUTSQI, NCFRZQI, NWETGQI, NDRYGQI, NWETHQI, & - NIMLTQI, NBERFIQI, NNIISQI, NSEDIQI, NCDEPIQI, NNEUTQI, & - NDEPSQS, NAGGSQS, NAUTSQS, NRIMQS, NACCQS, NCMELQS, NWETGQS, & - NDRYGQS, NNIISQS, NWETHQS, NSEDIQS, NNEUTQS, & - NSFRQG, NDEPGQG, NRIMQG, NACCQG, NCMELQG, NCFRZQG, NWETGQG, NDRYGQG, & - NINCGQG, NGMLTQG, NWETHQG, NSEDIQG, NNEUTQG, & - NWETGQH, NWETHQH, NHMLTQH, NSEDIQH, NNEUTQH, & - NDRIFTNI, NCORAYNI, NDEPSNI, NDEPGNI, NREVANI, NCDEPINI, NNEUTNI, & - NDEPOTRSV +NAMELIST/NAM_BU_RRH/LBU_RRH, CBULIST_RRH +! +NAMELIST/NAM_BU_RSV/ LBU_RSV, CBULIST_RSV ! END MODULE MODN_BUDGET