Skip to content

Commit

Permalink
+Add unit_scale_type argument to tracer_Z_init
Browse files Browse the repository at this point in the history
  Use US%m_to_Z in place of 1/G%Zd_to_m to convert units from m to Z in
tracer_Z_init.  This required adding a unit_scale_type argument to tracer_Z_init
and 4 subroutines that used the previous interface to tracer_Z_init.  All
answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed Nov 14, 2018
1 parent 967e470 commit 9ac67cc
Show file tree
Hide file tree
Showing 6 changed files with 33 additions and 23 deletions.
15 changes: 9 additions & 6 deletions src/tracer/MOM_OCMIP2_CFC.F90
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ module MOM_OCMIP2_CFC
use MOM_tracer_registry, only : register_tracer, tracer_registry_type
use MOM_tracer_diabatic, only : tracer_vertdiff, applyTracerBoundaryFluxesInOut
use MOM_tracer_Z_init, only : tracer_Z_init
use MOM_unit_scaling, only : unit_scale_type
use MOM_variables, only : surface
use MOM_verticalGrid, only : verticalGrid_type

Expand Down Expand Up @@ -308,13 +309,14 @@ subroutine flux_init_OCMIP2_CFC(CS, verbosity)
end subroutine flux_init_OCMIP2_CFC

!> Initialize the OCMP2 CFC tracer fields and set up the tracer output.
subroutine initialize_OCMIP2_CFC(restart, day, G, GV, h, diag, OBC, CS, &
subroutine initialize_OCMIP2_CFC(restart, day, G, GV, US, h, diag, OBC, CS, &
sponge_CSp, diag_to_Z_CSp)
logical, intent(in) :: restart !< .true. if the fields have already been
!! read from a restart file.
type(time_type), target, intent(in) :: day !< Time of the start of the run.
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
intent(in) :: h !< Layer thicknesses, in H
!! (usually m or kg m-2).
Expand Down Expand Up @@ -343,12 +345,12 @@ subroutine initialize_OCMIP2_CFC(restart, day, G, GV, h, diag, OBC, CS, &
if (.not.restart .or. (CS%tracers_may_reinit .and. &
.not.query_initialized(CS%CFC11, CS%CFC11_name, CS%restart_CSp))) &
call init_tracer_CFC(h, CS%CFC11, CS%CFC11_name, CS%CFC11_land_val, &
CS%CFC11_IC_val, G, CS)
CS%CFC11_IC_val, G, US, CS)

if (.not.restart .or. (CS%tracers_may_reinit .and. &
.not.query_initialized(CS%CFC12, CS%CFC12_name, CS%restart_CSp))) &
call init_tracer_CFC(h, CS%CFC12, CS%CFC12_name, CS%CFC12_land_val, &
CS%CFC12_IC_val, G, CS)
CS%CFC12_IC_val, G, US, CS)

if (associated(OBC)) then
! Steal from updated DOME in the fullness of time.
Expand All @@ -357,8 +359,9 @@ subroutine initialize_OCMIP2_CFC(restart, day, G, GV, h, diag, OBC, CS, &
end subroutine initialize_OCMIP2_CFC

!>This subroutine initializes a tracer array.
subroutine init_tracer_CFC(h, tr, name, land_val, IC_val, G, CS)
subroutine init_tracer_CFC(h, tr, name, land_val, IC_val, G, US, CS)
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thicknesses, in H (usually m or kg m-2)
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(out) :: tr !< The tracer concentration array
character(len=*), intent(in) :: name !< The tracer name
Expand All @@ -378,9 +381,9 @@ subroutine init_tracer_CFC(h, tr, name, land_val, IC_val, G, CS)
if (.not.file_exists(CS%IC_file, G%Domain)) &
call MOM_error(FATAL, "initialize_OCMIP2_CFC: Unable to open "//CS%IC_file)
if (CS%Z_IC_file) then
OK = tracer_Z_init(tr, h, CS%IC_file, name, G)
OK = tracer_Z_init(tr, h, CS%IC_file, name, G, US)
if (.not.OK) then
OK = tracer_Z_init(tr, h, CS%IC_file, trim(name), G)
OK = tracer_Z_init(tr, h, CS%IC_file, trim(name), G, US)
if (.not.OK) call MOM_error(FATAL,"initialize_OCMIP2_CFC: "//&
"Unable to read "//trim(name)//" from "//&
trim(CS%IC_file)//".")
Expand Down
8 changes: 5 additions & 3 deletions src/tracer/MOM_generic_tracer.F90
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@ module MOM_generic_tracer
use MOM_tracer_registry, only : register_tracer, tracer_registry_type
use MOM_tracer_Z_init, only : tracer_Z_init
use MOM_tracer_initialization_from_Z, only : MOM_initialize_tracer_from_Z
use MOM_unit_scaling, only : unit_scale_type
use MOM_variables, only : surface, thermo_var_ptrs
use MOM_open_boundary, only : ocean_OBC_type
use MOM_verticalGrid, only : verticalGrid_type
Expand Down Expand Up @@ -222,13 +223,14 @@ end function register_MOM_generic_tracer
!!
!! This subroutine initializes the NTR tracer fields in tr(:,:,:,:)
!! and it sets up the tracer output.
subroutine initialize_MOM_generic_tracer(restart, day, G, GV, h, param_file, diag, OBC, CS, &
subroutine initialize_MOM_generic_tracer(restart, day, G, GV, US, h, param_file, diag, OBC, CS, &
sponge_CSp, ALE_sponge_CSp,diag_to_Z_CSp)
logical, intent(in) :: restart !< .true. if the fields have already been
!! read from a restart file.
type(time_type), target, intent(in) :: day !< Time of the start of the run.
type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure
type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thicknesses, in H (usually m or kg m-2)
type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
type(diag_ctrl), target, intent(in) :: diag !< Regulates diagnostic output.
Expand Down Expand Up @@ -319,9 +321,9 @@ subroutine initialize_MOM_generic_tracer(restart, day, G, GV, h, param_file, dia
if (.not.file_exists(CS%IC_file)) call MOM_error(FATAL, &
"initialize_MOM_Generic_tracer: Unable to open "//CS%IC_file)
if (CS%Z_IC_file) then
OK = tracer_Z_init(tr_ptr, h, CS%IC_file, g_tracer_name, G)
OK = tracer_Z_init(tr_ptr, h, CS%IC_file, g_tracer_name, G, US)
if (.not.OK) then
OK = tracer_Z_init(tr_ptr, h, CS%IC_file, trim(g_tracer_name), G)
OK = tracer_Z_init(tr_ptr, h, CS%IC_file, trim(g_tracer_name), G, US)
if (.not.OK) call MOM_error(FATAL,"initialize_MOM_Generic_tracer: "//&
"Unable to read "//trim(g_tracer_name)//" from "//&
trim(CS%IC_file)//".")
Expand Down
6 changes: 4 additions & 2 deletions src/tracer/MOM_tracer_Z_init.F90
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ module MOM_tracer_Z_init
! use MOM_file_parser, only : get_param, log_version, param_file_type
use MOM_grid, only : ocean_grid_type
use MOM_io, only : MOM_read_data
use MOM_unit_scaling, only : unit_scale_type

use netcdf

Expand All @@ -21,9 +22,10 @@ module MOM_tracer_Z_init

!> This function initializes a tracer by reading a Z-space file, returning
!! .true. if this appears to have been successful, and false otherwise.
function tracer_Z_init(tr, h, filename, tr_name, G, missing_val, land_val)
function tracer_Z_init(tr, h, filename, tr_name, G, US, missing_val, land_val)
logical :: tracer_Z_init !< A return code indicating if the initialization has been successful
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
intent(out) :: tr !< The tracer to initialize
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
Expand Down Expand Up @@ -82,7 +84,7 @@ function tracer_Z_init(tr, h, filename, tr_name, G, missing_val, land_val)
! Find out the number of input levels and read the depth of the edges,
! also modifying their sign convention to be monotonically decreasing.
call read_Z_edges(filename, tr_name, z_edges, nz_in, has_edges, use_missing, &
missing, scale=1.0/G%Zd_to_m)
missing, scale=US%m_to_Z)
if (nz_in < 1) then
tracer_Z_init = .false.
return
Expand Down
8 changes: 4 additions & 4 deletions src/tracer/MOM_tracer_flow_control.F90
Original file line number Diff line number Diff line change
Expand Up @@ -317,23 +317,23 @@ subroutine tracer_flow_control_init(restart, day, G, GV, US, h, param_file, diag
call initialize_ISOMIP_tracer(restart, day, G, GV, h, diag, OBC, CS%ISOMIP_tracer_CSp, &
ALE_sponge_CSp, diag_to_Z_CSp)
if (CS%use_ideal_age) &
call initialize_ideal_age_tracer(restart, day, G, GV, h, diag, OBC, CS%ideal_age_tracer_CSp, &
call initialize_ideal_age_tracer(restart, day, G, GV, US, h, diag, OBC, CS%ideal_age_tracer_CSp, &
sponge_CSp, diag_to_Z_CSp)
if (CS%use_regional_dyes) &
call initialize_dye_tracer(restart, day, G, GV, h, diag, OBC, CS%dye_tracer_CSp, &
sponge_CSp, diag_to_Z_CSp)
if (CS%use_oil) &
call initialize_oil_tracer(restart, day, G, GV, h, diag, OBC, CS%oil_tracer_CSp, &
call initialize_oil_tracer(restart, day, G, GV, US, h, diag, OBC, CS%oil_tracer_CSp, &
sponge_CSp, diag_to_Z_CSp)
if (CS%use_advection_test_tracer) &
call initialize_advection_test_tracer(restart, day, G, GV, h, diag, OBC, CS%advection_test_tracer_CSp, &
sponge_CSp, diag_to_Z_CSp)
if (CS%use_OCMIP2_CFC) &
call initialize_OCMIP2_CFC(restart, day, G, GV, h, diag, OBC, CS%OCMIP2_CFC_CSp, &
call initialize_OCMIP2_CFC(restart, day, G, GV, US, h, diag, OBC, CS%OCMIP2_CFC_CSp, &
sponge_CSp, diag_to_Z_CSp)
#ifdef _USE_GENERIC_TRACER
if (CS%use_MOM_generic_tracer) &
call initialize_MOM_generic_tracer(restart, day, G, GV, h, param_file, diag, OBC, &
call initialize_MOM_generic_tracer(restart, day, G, GV, US, h, param_file, diag, OBC, &
CS%MOM_generic_tracer_CSp, sponge_CSp, ALE_sponge_CSp, diag_to_Z_CSp)
#endif
if (CS%use_pseudo_salt_tracer) &
Expand Down
8 changes: 5 additions & 3 deletions src/tracer/ideal_age_example.F90
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ module ideal_age_example
use MOM_tracer_registry, only : register_tracer, tracer_registry_type
use MOM_tracer_diabatic, only : tracer_vertdiff, applyTracerBoundaryFluxesInOut
use MOM_tracer_Z_init, only : tracer_Z_init
use MOM_unit_scaling, only : unit_scale_type
use MOM_variables, only : surface
use MOM_verticalGrid, only : verticalGrid_type

Expand Down Expand Up @@ -193,13 +194,14 @@ function register_ideal_age_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)
end function register_ideal_age_tracer

!> Sets the ideal age traces to their initial values and sets up the tracer output
subroutine initialize_ideal_age_tracer(restart, day, G, GV, h, diag, OBC, CS, &
subroutine initialize_ideal_age_tracer(restart, day, G, GV, US, h, diag, OBC, CS, &
sponge_CSp, diag_to_Z_CSp)
logical, intent(in) :: restart !< .true. if the fields have already
!! been read from a restart file.
type(time_type), target, intent(in) :: day !< Time of the start of the run.
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
intent(in) :: h !< Layer thicknesses, in H (usually m or kg m-2)
type(diag_ctrl), target, intent(in) :: diag !< A structure that is used to regulate
Expand Down Expand Up @@ -250,10 +252,10 @@ subroutine initialize_ideal_age_tracer(restart, day, G, GV, h, diag, OBC, CS, &

if (CS%Z_IC_file) then
OK = tracer_Z_init(CS%tr(:,:,:,m), h, CS%IC_file, name,&
G, -1e34, 0.0) ! CS%land_val(m))
G, US, -1e34, 0.0) ! CS%land_val(m))
if (.not.OK) then
OK = tracer_Z_init(CS%tr(:,:,:,m), h, CS%IC_file, &
trim(name), G, -1e34, 0.0) ! CS%land_val(m))
trim(name), G, US, -1e34, 0.0) ! CS%land_val(m))
if (.not.OK) call MOM_error(FATAL,"initialize_ideal_age_tracer: "//&
"Unable to read "//trim(name)//" from "//&
trim(CS%IC_file)//".")
Expand Down
11 changes: 6 additions & 5 deletions src/tracer/oil_tracer.F90
Original file line number Diff line number Diff line change
Expand Up @@ -18,8 +18,8 @@ module oil_tracer
use MOM_tracer_registry, only : register_tracer, tracer_registry_type
use MOM_tracer_diabatic, only : tracer_vertdiff, applyTracerBoundaryFluxesInOut
use MOM_tracer_Z_init, only : tracer_Z_init
use MOM_variables, only : surface
use MOM_variables, only : thermo_var_ptrs
use MOM_unit_scaling, only : unit_scale_type
use MOM_variables, only : surface, thermo_var_ptrs
use MOM_verticalGrid, only : verticalGrid_type

use coupler_types_mod, only : coupler_type_set_data, ind_csurf
Expand Down Expand Up @@ -201,13 +201,14 @@ function register_oil_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)
end function register_oil_tracer

!> Initialize the oil tracers and set up tracer output
subroutine initialize_oil_tracer(restart, day, G, GV, h, diag, OBC, CS, &
subroutine initialize_oil_tracer(restart, day, G, GV, US, h, diag, OBC, CS, &
sponge_CSp, diag_to_Z_CSp)
logical, intent(in) :: restart !< .true. if the fields have already
!! been read from a restart file.
type(time_type), target, intent(in) :: day !< Time of the start of the run.
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
intent(in) :: h !< Layer thicknesses, in H (usually m or kg m-2)
type(diag_ctrl), target, intent(in) :: diag !< A structure that is used to regulate
Expand Down Expand Up @@ -266,10 +267,10 @@ subroutine initialize_oil_tracer(restart, day, G, GV, h, diag, OBC, CS, &

if (CS%Z_IC_file) then
OK = tracer_Z_init(CS%tr(:,:,:,m), h, CS%IC_file, name, &
G, -1e34, 0.0) ! CS%land_val(m))
G, US, -1e34, 0.0) ! CS%land_val(m))
if (.not.OK) then
OK = tracer_Z_init(CS%tr(:,:,:,m), h, CS%IC_file, &
trim(name), G, -1e34, 0.0) ! CS%land_val(m))
trim(name), G, US, -1e34, 0.0) ! CS%land_val(m))
if (.not.OK) call MOM_error(FATAL,"initialize_oil_tracer: "//&
"Unable to read "//trim(name)//" from "//&
trim(CS%IC_file)//".")
Expand Down

0 comments on commit 9ac67cc

Please sign in to comment.