80 implicit none ;
private 82 #include <MOM_memory.h> 92 real,
dimension(:,:,:),
pointer :: p => null()
97 logical :: coupled_tracers = .false.
101 character(len=200) :: ic_file
104 type(time_type),
pointer :: time
106 real,
pointer :: tr(:,:,:,:) => null()
108 real,
pointer :: tr_aux(:,:,:,:) => null()
110 type(
p3d),
dimension(NTR_MAX) :: &
115 real,
dimension(NTR_MAX) :: &
123 logical :: mask_tracers
124 logical :: tracers_may_reinit
129 integer,
dimension(NTR_MAX) :: &
132 id_tracer = -1, id_tr_adx = -1, id_tr_ady = -1, &
133 id_tr_dfx = -1, id_tr_dfy = -1
163 #include "version_variable.h" 164 character(len=40) :: mdl =
"ideal_age_example" 165 character(len=200) :: inputdir
166 character(len=48) :: var_name
167 real,
pointer :: tr_ptr(:,:,:) => null()
168 logical :: register_ideal_age_tracer
169 logical :: do_ideal_age, do_vintage, do_ideal_age_dated
170 integer :: isd, ied, jsd, jed, nz, m
171 isd = hi%isd ; ied = hi%ied ; jsd = hi%jsd ; jed = hi%jed ; nz = gv%ke
173 if (
associated(cs))
then 174 call mom_error(warning,
"register_ideal_age_tracer called with an "// &
175 "associated control structure.")
182 call get_param(param_file, mdl,
"DO_IDEAL_AGE", do_ideal_age, &
183 "If true, use an ideal age tracer that is set to 0 age \n"//&
184 "in the mixed layer and ages at unit rate in the interior.", &
186 call get_param(param_file, mdl,
"DO_IDEAL_VINTAGE", do_vintage, &
187 "If true, use an ideal vintage tracer that is set to an \n"//&
188 "exponentially increasing value in the mixed layer and \n"//&
189 "is conserved thereafter.", default=.false.)
190 call get_param(param_file, mdl,
"DO_IDEAL_AGE_DATED", do_ideal_age_dated, &
191 "If true, use an ideal age tracer that is everywhere 0 \n"//&
192 "before IDEAL_AGE_DATED_START_YEAR, but the behaves like \n"//&
193 "the standard ideal age tracer - i.e. is set to 0 age in \n"//&
194 "the mixed layer and ages at unit rate in the interior.", &
198 call get_param(param_file, mdl,
"AGE_IC_FILE", cs%IC_file, &
199 "The file in which the age-tracer initial values can be \n"//&
200 "found, or an empty string for internal initialization.", &
202 if ((len_trim(cs%IC_file) > 0) .and. (scan(cs%IC_file,
'/') == 0))
then 204 call get_param(param_file, mdl,
"INPUTDIR", inputdir, default=
".")
205 cs%IC_file = trim(slasher(inputdir))//trim(cs%IC_file)
206 call log_param(param_file, mdl,
"INPUTDIR/AGE_IC_FILE", cs%IC_file)
208 call get_param(param_file, mdl,
"AGE_IC_FILE_IS_Z", cs%Z_IC_file, &
209 "If true, AGE_IC_FILE is in depth space, not layer space", &
211 call get_param(param_file, mdl,
"MASK_MASSLESS_TRACERS", cs%mask_tracers, &
212 "If true, the tracers are masked out in massless layer. \n"//&
213 "This can be a problem with time-averages.", default=.false.)
214 call get_param(param_file, mdl,
"TRACERS_MAY_REINIT", cs%tracers_may_reinit, &
215 "If true, tracers may go through the initialization code \n"//&
216 "if they are not found in the restart files. Otherwise \n"//&
217 "it is a fatal error if the tracers are not found in the \n"//&
218 "restart files of a restarted run.", default=.false.)
221 if (do_ideal_age)
then 222 cs%ntr = cs%ntr + 1 ; m = cs%ntr
223 cs%tr_desc(m) =
var_desc(
"age",
"years",
"Ideal Age Tracer", cmor_field_name=
"agessc", caller=mdl)
224 cs%tracer_ages(m) = .true. ; cs%sfc_growth_rate(m) = 0.0
225 cs%IC_val(m) = 0.0 ; cs%young_val(m) = 0.0 ; cs%tracer_start_year(m) = 0.0
229 cs%ntr = cs%ntr + 1 ; m = cs%ntr
230 cs%tr_desc(m) =
var_desc(
"vintage",
"years",
"Exponential Vintage Tracer", &
232 cs%tracer_ages(m) = .false. ; cs%sfc_growth_rate(m) = 1.0/30.0
233 cs%IC_val(m) = 0.0 ; cs%young_val(m) = 1e-20 ; cs%tracer_start_year(m) = 0.0
234 call get_param(param_file, mdl,
"IDEAL_VINTAGE_START_YEAR", cs%tracer_start_year(m), &
235 "The date at which the ideal vintage tracer starts.", &
236 units=
"years", default=0.0)
239 if (do_ideal_age_dated)
then 240 cs%ntr = cs%ntr + 1 ; m = cs%ntr
241 cs%tr_desc(m) =
var_desc(
"age_dated",
"years",
"Ideal Age Tracer with a Start Date",&
243 cs%tracer_ages(m) = .true. ; cs%sfc_growth_rate(m) = 0.0
244 cs%IC_val(m) = 0.0 ; cs%young_val(m) = 0.0 ; cs%tracer_start_year(m) = 0.0
245 call get_param(param_file, mdl,
"IDEAL_AGE_DATED_START_YEAR", cs%tracer_start_year(m), &
246 "The date at which the dated ideal age tracer starts.", &
247 units=
"years", default=0.0)
250 allocate(cs%tr(isd:ied,jsd:jed,nz,cs%ntr)) ; cs%tr(:,:,:,:) = 0.0
251 if (cs%mask_tracers)
then 252 allocate(cs%tr_aux(isd:ied,jsd:jed,nz,cs%ntr)) ; cs%tr_aux(:,:,:,:) = 0.0
258 tr_ptr => cs%tr(:,:,:,m)
260 caller=
"register_ideal_age_tracer")
263 .not.cs%tracers_may_reinit, restart_cs)
265 call register_tracer(tr_ptr, cs%tr_desc(m), param_file, hi, gv, tr_reg, &
266 tr_desc_ptr=cs%tr_desc(m))
271 if (cs%coupled_tracers) &
273 flux_type=
' ', implementation=
' ', caller=
"register_ideal_age_tracer")
277 cs%restart_CSp => restart_cs
278 register_ideal_age_tracer = .true.
282 sponge_CSp, diag_to_Z_CSp)
283 logical,
intent(in) :: restart
284 type(time_type),
target,
intent(in) :: day
287 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: h
288 type(
diag_ctrl),
target,
intent(in) :: diag
311 character(len=24) :: name
312 character(len=72) :: longname
313 character(len=48) :: units
314 character(len=48) :: flux_units
316 character(len=72) :: cmorname
318 integer :: i, j, k, is, ie, js, je, isd, ied, jsd, jed, nz, m
319 integer :: IsdB, IedB, JsdB, JedB
321 if (.not.
associated(cs))
return 322 if (cs%ntr < 1)
return 323 is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = gv%ke
324 isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
325 isdb = g%IsdB ; iedb = g%IedB ; jsdb = g%JsdB ; jedb = g%JedB
329 cs%nkml = max(gv%nkml,1)
333 caller=
"initialize_ideal_age_tracer")
334 if ((.not.restart) .or. (cs%tracers_may_reinit .and. .not. &
337 if (len_trim(cs%IC_file) > 0)
then 340 call mom_error(fatal,
"initialize_ideal_age_tracer: "// &
341 "Unable to open "//cs%IC_file)
343 if (cs%Z_IC_file)
then 348 trim(name), g, -1e34, 0.0)
349 if (.not.ok)
call mom_error(fatal,
"initialize_ideal_age_tracer: "//&
350 "Unable to read "//trim(name)//
" from "//&
351 trim(cs%IC_file)//
".")
354 call read_data(cs%IC_file, trim(name), cs%tr(:,:,:,m), &
355 domain=g%Domain%mpp_domain)
358 do k=1,nz ;
do j=js,je ;
do i=is,ie
359 if (g%mask2dT(i,j) < 0.5)
then 360 cs%tr(i,j,k,m) = cs%land_val(m)
362 cs%tr(i,j,k,m) = cs%IC_val(m)
364 enddo ;
enddo ;
enddo 370 if (
associated(obc))
then 379 if (gv%Boussinesq)
then ; flux_units =
"years m3 s-1" 380 else ; flux_units =
"years kg s-1" ;
endif 383 call query_vardesc(cs%tr_desc(m), name, units=units, longname=longname, &
384 cmor_field_name=cmorname, caller=
"initialize_ideal_age_tracer")
385 if (len_trim(cmorname)==0)
then 386 cs%id_tracer(m) = register_diag_field(
"ocean_model", trim(name), cs%diag%axesTL, &
387 day, trim(longname) , trim(units))
389 cs%id_tracer(m) = register_diag_field(
"ocean_model", trim(name), cs%diag%axesTL, &
390 day, trim(longname) , trim(units), cmor_field_name=cmorname)
392 cs%id_tr_adx(m) = register_diag_field(
"ocean_model", trim(name)//
"_adx", &
393 cs%diag%axesCuL, day, trim(longname)//
" advective zonal flux" , &
395 cs%id_tr_ady(m) = register_diag_field(
"ocean_model", trim(name)//
"_ady", &
396 cs%diag%axesCvL, day, trim(longname)//
" advective meridional flux" , &
398 cs%id_tr_dfx(m) = register_diag_field(
"ocean_model", trim(name)//
"_dfx", &
399 cs%diag%axesCuL, day, trim(longname)//
" diffusive zonal flux" , &
401 cs%id_tr_dfy(m) = register_diag_field(
"ocean_model", trim(name)//
"_dfy", &
402 cs%diag%axesCvL, day, trim(longname)//
" diffusive zonal flux" , &
404 if (cs%id_tr_adx(m) > 0)
call safe_alloc_ptr(cs%tr_adx(m)%p,isdb,iedb,jsd,jed,nz)
405 if (cs%id_tr_ady(m) > 0)
call safe_alloc_ptr(cs%tr_ady(m)%p,isd,ied,jsdb,jedb,nz)
406 if (cs%id_tr_dfx(m) > 0)
call safe_alloc_ptr(cs%tr_dfx(m)%p,isdb,iedb,jsd,jed,nz)
407 if (cs%id_tr_dfy(m) > 0)
call safe_alloc_ptr(cs%tr_dfy(m)%p,isd,ied,jsdb,jedb,nz)
410 if ((cs%id_tr_adx(m) > 0) .or. (cs%id_tr_ady(m) > 0) .or. &
411 (cs%id_tr_dfx(m) > 0) .or. (cs%id_tr_dfy(m) > 0)) &
413 cs%tr_ady(m)%p,cs%tr_dfx(m)%p,cs%tr_dfy(m)%p)
416 day, g, diag_to_z_csp)
422 evap_CFL_limit, minimum_forcing_depth)
425 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: h_old, h_new, ea, eb
426 type(
forcing),
intent(in) :: fluxes
427 real,
intent(in) :: dt
429 real,
optional,
intent(in) :: evap_CFL_limit
430 real,
optional,
intent(in) :: minimum_forcing_depth
453 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)) :: h_work
455 real :: Isecs_per_year
457 integer :: secs, days
458 integer :: i, j, k, is, ie, js, je, nz, m
459 is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = gv%ke
461 if (.not.
associated(cs))
return 462 if (cs%ntr < 1)
return 464 if (
present(evap_cfl_limit) .and.
present(minimum_forcing_depth))
then 466 do k=1,nz ;
do j=js,je ;
do i=is,ie
467 h_work(i,j,k) = h_old(i,j,k)
468 enddo ;
enddo ; enddo;
470 evap_cfl_limit, minimum_forcing_depth)
479 isecs_per_year = 1.0 / (365.0*86400.0)
482 call get_time(cs%Time, secs, days)
483 year = (86400.0*days +
real(secs)) * isecs_per_year
486 if (cs%sfc_growth_rate(m) == 0.0)
then 487 sfc_val = cs%young_val(m)
489 sfc_val = cs%young_val(m) * &
490 exp((year-cs%tracer_start_year(m)) * cs%sfc_growth_rate(m))
492 do k=1,cs%nkml ;
do j=js,je ;
do i=is,ie
493 if (g%mask2dT(i,j) > 0.5)
then 494 cs%tr(i,j,k,m) = sfc_val
496 cs%tr(i,j,k,m) = cs%land_val(m)
498 enddo ;
enddo ;
enddo 500 do m=1,cs%ntr ;
if (cs%tracer_ages(m) .and. &
501 (year>=cs%tracer_start_year(m)))
then 503 do k=cs%nkml+1,nz ;
do j=js,je ;
do i=is,ie
504 cs%tr(i,j,k,m) = cs%tr(i,j,k,m) + g%mask2dT(i,j)*dt*isecs_per_year
505 enddo ;
enddo ;
enddo 508 if (cs%mask_tracers)
then 509 do m=1,cs%ntr ;
if (cs%id_tracer(m) > 0)
then 510 do k=1,nz ;
do j=js,je ;
do i=is,ie
511 if (h_new(i,j,k) < 1.1*gv%Angstrom)
then 512 cs%tr_aux(i,j,k,m) = cs%land_val(m)
514 cs%tr_aux(i,j,k,m) = cs%tr(i,j,k,m)
516 enddo ;
enddo ;
enddo 521 if (cs%mask_tracers)
then 522 if (cs%id_tracer(m)>0) &
523 call post_data(cs%id_tracer(m),cs%tr_aux(:,:,:,m),cs%diag)
525 if (cs%id_tracer(m)>0) &
526 call post_data(cs%id_tracer(m),cs%tr(:,:,:,m),cs%diag)
528 if (cs%id_tr_adx(m)>0) &
529 call post_data(cs%id_tr_adx(m),cs%tr_adx(m)%p(:,:,:),cs%diag)
530 if (cs%id_tr_ady(m)>0) &
531 call post_data(cs%id_tr_ady(m),cs%tr_ady(m)%p(:,:,:),cs%diag)
532 if (cs%id_tr_dfx(m)>0) &
533 call post_data(cs%id_tr_dfx(m),cs%tr_dfx(m)%p(:,:,:),cs%diag)
534 if (cs%id_tr_dfy(m)>0) &
535 call post_data(cs%id_tr_dfy(m),cs%tr_dfy(m)%p(:,:,:),cs%diag)
540 function ideal_age_stock(h, stocks, G, GV, CS, names, units, stock_index)
542 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: h
543 real,
dimension(:),
intent(out) :: stocks
546 character(len=*),
dimension(:),
intent(out) :: names
547 character(len=*),
dimension(:),
intent(out) :: units
548 integer,
optional,
intent(in) :: stock_index
549 integer :: ideal_age_stock
566 integer :: i, j, k, is, ie, js, je, nz, m
567 is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = gv%ke
570 if (.not.
associated(cs))
return 571 if (cs%ntr < 1)
return 573 if (
present(stock_index))
then ;
if (stock_index > 0)
then 581 call query_vardesc(cs%tr_desc(m), name=names(m), units=units(m), caller=
"ideal_age_stock")
582 units(m) = trim(units(m))//
" kg" 584 do k=1,nz ;
do j=js,je ;
do i=is,ie
585 stocks(m) = stocks(m) + cs%tr(i,j,k,m) * &
586 (g%mask2dT(i,j) * g%areaT(i,j) * h(i,j,k))
587 enddo ;
enddo ;
enddo 588 stocks(m) = gv%H_to_kg_m2 * stocks(m)
590 ideal_age_stock = cs%ntr
596 type(
surface),
intent(inout) :: state
597 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: h
607 integer :: i, j, m, is, ie, js, je
608 is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
610 if (.not.
associated(cs))
return 612 if (cs%coupled_tracers)
then 617 ind_csurf, is, ie, js, je)
627 if (
associated(cs))
then 628 if (
associated(cs%tr))
deallocate(cs%tr)
629 if (
associated(cs%tr_aux))
deallocate(cs%tr_aux)
631 if (
associated(cs%tr_adx(m)%p))
deallocate(cs%tr_adx(m)%p)
632 if (
associated(cs%tr_ady(m)%p))
deallocate(cs%tr_ady(m)%p)
633 if (
associated(cs%tr_dfx(m)%p))
deallocate(cs%tr_dfx(m)%p)
634 if (
associated(cs%tr_dfy(m)%p))
deallocate(cs%tr_dfy(m)%p)
The following structure contains pointers to various fields which may be used describe the surface st...
subroutine, public ideal_age_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, G, GV, CS, evap_CFL_limit, minimum_forcing_depth)
type(vardesc) function, public var_desc(name, units, longname, hor_grid, z_grid, t_grid, cmor_field_name, cmor_units, conversion, caller)
Returns a vardesc type whose elements have been filled with the provided fields. The argument name is...
subroutine, public ideal_age_tracer_surface_state(state, h, G, CS)
This module implements boundary forcing for MOM6.
integer function, public aof_set_coupler_flux(name, flux_type, implementation, atm_tr_index, param, flag, ice_restart_file, ocean_restart_file, units, caller)
subroutine, public initialize_ideal_age_tracer(restart, day, G, GV, h, diag, OBC, CS, sponge_CSp, diag_to_Z_CSp)
logical function, public tracer_z_init(tr, h, filename, tr_name, G, missing_val, land_val)
Ocean grid type. See mom_grid for details.
subroutine, public ideal_age_example_end(CS)
Provides the ocean grid type.
This module contains I/O framework code.
Defines the horizontal index type (hor_index_type) used for providing index ranges.
Container for horizontal index ranges for data, computational and global domains. ...
subroutine, public register_tracer(tr1, tr_desc, param_file, HI, GV, Reg, tr_desc_ptr, ad_x, ad_y, df_x, df_y, OBC_inflow, OBC_in_u, OBC_in_v, ad_2d_x, ad_2d_y, df_2d_x, df_2d_y, advection_xy)
This subroutine registers a tracer to be advected and laterally diffused.
This module contains the tracer_registry_type and the subroutines that handle registration of tracers...
subroutine, public applytracerboundaryfluxesinout(G, GV, Tr, dt, fluxes, h, evap_CFL_limit, minimum_forcing_depth, in_flux_optional, out_flux_optional, update_h_opt)
This routine is modeled after applyBoundaryFluxesInOut in MOM_diabatic_aux.F90 NOTE: Please note that...
subroutine, public set_up_sponge_field(sp_val, f_ptr, G, nlay, CS, sp_val_i_mean)
Type to carry basic tracer information.
This module contains routines that implement physical fluxes of tracers (e.g. due to surface fluxes o...
subroutine, public register_z_tracer(tr_ptr, name, long_name, units, Time, G, CS, standard_name, cmor_field_name, cmor_long_name, cmor_units, cmor_standard_name)
This subroutine registers a tracer to be output in depth space.
subroutine, public add_tracer_obc_values(name, Reg, OBC_inflow, OBC_in_u, OBC_in_v)
This subroutine adds open boundary condition concentrations for a tracer that has previously been reg...
subroutine, public add_tracer_diagnostics(name, Reg, ad_x, ad_y, df_x, df_y, ad_2d_x, ad_2d_y, df_2d_x, df_2d_y, advection_xy)
This subroutine adds diagnostic arrays for a tracer that has previously been registered by a call to ...
Structure that contains pointers to the boundary forcing used to drive the liquid ocean simulated by ...
subroutine, public set_coupler_values(array_in, BC_struc, BC_index, BC_element, is, ie, js, je, conversion)
Type for describing a variable, typically a tracer.
subroutine, public tracer_vertdiff(h_old, ea, eb, dt, tr, G, GV, sfc_flux, btm_flux, btm_reservoir, sink_rate, convert_flux_in)
This subroutine solves a tridiagonal equation for the final tracer concentrations after the dual-entr...
logical function, public register_ideal_age_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)
integer, parameter ntr_max
subroutine, public query_vardesc(vd, name, units, longname, hor_grid, z_grid, t_grid, cmor_field_name, cmor_units, conversion, caller)
This routine queries vardesc.
Controls where open boundary conditions are applied.
subroutine, public mom_error(level, message, all_print)
integer function, public ideal_age_stock(h, stocks, G, GV, CS, names, units, stock_index)