Skip to content

Commit

Permalink
Tracers: read surface flux from tracerdata.inp
Browse files Browse the repository at this point in the history
  • Loading branch information
CasparJungbacker committed Feb 7, 2025
1 parent b13b3e9 commit ad022e7
Show file tree
Hide file tree
Showing 4 changed files with 34 additions and 17 deletions.
5 changes: 2 additions & 3 deletions src/modstartup.f90
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,7 @@ subroutine startup(path)
use modlsm, only : initlsm, kmax_soil
use moddrydeposition, only : initdrydep
use modfields, only : initfields,um,vm,wm,u0,v0,w0,up,vp,wp,rhobf
use modtracers, only : inittracers, allocate_tracers
use modtracers, only : inittracers, allocate_tracers, add_tracer
use modpois, only : initpois,poisson
use modradiation, only : initradiation
use modraddata, only : irad,iradiation,&
Expand Down Expand Up @@ -131,7 +131,7 @@ subroutine startup(path)
xlat,xlon,xyear,xday,xtime,ksp
namelist/PHYSICS/ &
!cstep z0,ustin,wtsurf,wqsurf,wsvsurf,ps,thls,chi_half,lmoist,isurf,lneutraldrag,&
z0,ustin,wtsurf,wqsurf,wsvsurf,ps,thls,lmoist,isurf,chi_half,&
z0,ustin,wtsurf,wqsurf,ps,thls,lmoist,isurf,chi_half,&
lcoriol,lpressgrad,igrw_damp,geodamptime,uvdamprate,lmomsubs,ltimedep,ltimedepuv,ltimedepsv,ntimedep,&
irad,timerad,iradiation,rad_ls,rad_longw,rad_shortw,rad_smoke,useMcICA,&
rka,dlwtop,dlwbot,sw0,gc,reff,isvsmoke,lforce_user,lcloudshading,lrigidlid,unudge,lfast_thermo,lconstexner
Expand Down Expand Up @@ -247,7 +247,6 @@ subroutine startup(path)
!call D_MPI_BCAST(lneutraldrag ,1,0,commwrld,mpierr)
call D_MPI_BCAST(wtsurf ,1,0,commwrld,mpierr)
call D_MPI_BCAST(wqsurf ,1,0,commwrld,mpierr)
call D_MPI_BCAST(wsvsurf(1:nsv),nsv,0,commwrld,mpierr)
call D_MPI_BCAST(ps ,1,0,commwrld,mpierr)
call D_MPI_BCAST(thls ,1,0,commwrld,mpierr)
call D_MPI_BCAST(chi_half ,1,0,commwrld,mpierr)
Expand Down
17 changes: 13 additions & 4 deletions src/modsurface.f90
Original file line number Diff line number Diff line change
Expand Up @@ -74,11 +74,12 @@ subroutine initsurface
use modglobal, only : i1, j1, i2, j2, itot, jtot,imax,jmax, nsv, ifnamopt, fname_options, ifinput, cexpnr, checknamelisterror, handle_err
use modraddata, only : iradiation,rad_shortw,irad_par,irad_user,irad_rrtmg,irad_rte_rrtmgp
use modmpi, only : myid, myidx, myidy, comm3d, mpierr, D_MPI_BCAST
use modtracers, only : tracer_prop
use netcdf

implicit none

integer :: i,j,k, landindex, ierr, defined_landtypes, landtype_0 = -1
integer :: i,j,k, landindex, ierr, defined_landtypes, landtype_0 = -1, isv
integer :: tempx,tempy
integer :: VARID,STATUS,NCID,timeID
character(len = nf90_max_name) :: RecordDimName
Expand All @@ -91,7 +92,7 @@ subroutine initsurface
! Jarvis-Steward related variables
rsminav, rssoilminav, LAIav, gDav, &
! Prescribed values for isurf 2, 3, 4
z0, thls, ps, ustin, wtsurf, wqsurf, wsvsurf, &
z0, thls, ps, ustin, wtsurf, wqsurf, &
! Heterogeneous variables
lhetero, xpatches, ypatches, land_use, loldtable, &
! AGS variables
Expand Down Expand Up @@ -151,7 +152,6 @@ subroutine initsurface
call D_MPI_BCAST(ustin ,1,0,comm3d,mpierr)
call D_MPI_BCAST(wtsurf ,1,0,comm3d,mpierr)
call D_MPI_BCAST(wqsurf ,1,0,comm3d,mpierr)
call D_MPI_BCAST(wsvsurf(1:nsv),nsv,0,comm3d,mpierr)
call D_MPI_BCAST(ps ,1,0,comm3d,mpierr)
call D_MPI_BCAST(thls ,1,0,comm3d,mpierr)

Expand Down Expand Up @@ -194,6 +194,14 @@ subroutine initsurface
lsplitleaf = .false.
endif

allocate(wsvsurf(nsv))

wsvsurf(1:nsv) = 0

do isv = 1, nsv
wsvsurf(isv) = tracer_prop(isv)%wsvsurf
end do

if(lrsAgs) then
select case (planttype)
case (3) !< C3 plants based on standard settings; R10, T2gm and Q10gm can be altered in the namelist
Expand Down Expand Up @@ -510,7 +518,8 @@ subroutine initsurface
ustin = 0
wtsurf = 0
wqsurf = 0
wsvsurf(1:nsv) = 0


if (.not. loldtable) then
albedoav = 0
endif
Expand Down
2 changes: 1 addition & 1 deletion src/modsurfdata.f90
Original file line number Diff line number Diff line change
Expand Up @@ -240,7 +240,7 @@ module modsurfdata
real :: ustin = -1 !< Prescribed friction velocity [m/s]
real :: wtsurf = -1e20 !< Prescribed kinematic temperature flux [K m/s]
real :: wqsurf = -1e20 !< Prescribed kinematic moisture flux [kg/kg m/s]
real :: wsvsurf(100) = 0 !< Prescribed surface scalar(n) flux [- m/s]
real(field_r), allocatable :: wsvsurf(:) !< Prescribed surface scalar(n) flux [- m/s]
integer :: i_expemis = -1 !< Scalar index for which the exponential emission should be applied [-]
real :: expemis0 = 0.0 !< Maximum exponential emission [ppb m/s]
real :: expemis1 = 0.0 !< Time of maximum exponential emission [s]
Expand Down
27 changes: 18 additions & 9 deletions src/modtracers.f90
Original file line number Diff line number Diff line change
Expand Up @@ -61,6 +61,7 @@ module modtracers
logical :: ldep = .false. !< Boolean if tracer is deposited
logical :: lags = .false. !< Boolean if in A-gs
logical :: lmicro = .false. !< Boolean if in cloud microphysics
real(field_r) :: wsvsurf = 0 !< Kinematic surface flux (- m/s)
end type T_tracer

integer, protected :: nsv_user !< Number of user-provided tracers
Expand Down Expand Up @@ -110,10 +111,10 @@ end subroutine inittracers
!! \param ldep Tracer is deposited.
!! \param lags Tracer is photosynthesized.
!! \param lmicro Tracer is involved in cloud microphysics.
!! \param laero Tracer is involved in aerosol microphyiscs.
!! \param wsvsurf Kinematic surface flux (- m/s).
!! \note All tracers should be added before readinitfiles is called!
subroutine add_tracer(name, long_name, unit, molar_mass, lemis, lreact, &
ldep, lags, lmicro, isv)
ldep, lags, lmicro, wsvsurf, isv)
character(len=*), intent(in) :: name
character(len=*), intent(in), optional :: long_name
character(len=*), intent(in), optional :: unit
Expand All @@ -123,6 +124,7 @@ subroutine add_tracer(name, long_name, unit, molar_mass, lemis, lreact, &
logical, intent(in), optional :: ldep
logical, intent(in), optional :: lags
logical, intent(in), optional :: lmicro
real(field_r), intent(in), optional :: wsvsurf
integer, intent(out), optional :: isv

character(len=*), parameter :: routine = modname//'::add_tracer'
Expand Down Expand Up @@ -179,6 +181,7 @@ subroutine add_tracer(name, long_name, unit, molar_mass, lemis, lreact, &
if (present(ldep)) tracer_prop(nsv) % ldep = ldep
if (present(lags)) tracer_prop(nsv) % lags = lags
if (present(lmicro)) tracer_prop(nsv) % lmicro = lmicro
if (present(wsvsurf)) tracer_prop(nsv) % wsvsurf = wsvsurf

if (present(isv)) isv = nsv

Expand All @@ -193,23 +196,25 @@ subroutine allocate_tracers

! Print tracer properties
if (myid == 0) then
write(6, '(a17,a17,a7,a9,a10,a11)') &
write(6, '(a17,a17,a7,a9,a10,a11,a11)') &
'Tracer ', &
'Unit ', &
'Index ', &
'Emitted ', &
'Reactive ', &
'Deposited '
write(6, '(a)') repeat('-', 70)
'Deposited ', &
'Surf. Flux '
write(6, '(a)') repeat('-', 81)
do isv = 1, nsv
tracer = tracer_prop(isv)
write(6, '(a,x,a,x,i3,4x,l3,6x,l3,7x,l3,8x)'), & ! Ugh
write(6, '(a,x,a,x,i3,4x,l3,6x,l3,7x,l3,8x,e10.4,x)') & ! Ugh
tracer%tracname, &
tracer%unit, &
tracer%trac_idx, &
tracer%lemis, &
tracer%lreact, &
tracer%ldep
tracer%ldep, &
tracer%wsvsurf
end do
end if

Expand Down Expand Up @@ -275,6 +280,7 @@ subroutine tracer_props_from_ascii(file_profiles, file_properties)
logical :: tracer_is_deposited(max_tracs) = .false.
logical :: tracer_is_photosynth(max_tracs) = .false.
logical :: tracer_is_microphys(max_tracs) = .false.
real(field_r) :: wsvsurf(max_tracs) = 0.0

open(1, file=file_profiles, status='old', iostat=ierr)

Expand Down Expand Up @@ -319,7 +325,8 @@ subroutine tracer_props_from_ascii(file_profiles, file_properties)
tracer_is_reactive(isv), &
tracer_is_deposited(isv), &
tracer_is_photosynth(isv), &
tracer_is_microphys(isv)
tracer_is_microphys(isv), &
wsvsurf(isv)
end if
end if
end do
Expand All @@ -345,7 +352,9 @@ subroutine tracer_props_from_ascii(file_profiles, file_properties)
lags=findval(headers(n), tracname_short, &
tracer_is_photosynth, defltvalue=.false.), & ! Default is False
lmicro=findval(headers(n), tracname_short, &
tracer_is_microphys, defltvalue=.false.) & ! Default is False
tracer_is_microphys, defltvalue=.false.), & ! Default is False
wsvsurf=findval(headers(n), tracname_short, &
wsvsurf, defltvalue=0.0_field_r) &
)
end do

Expand Down

0 comments on commit ad022e7

Please sign in to comment.