@@ -86,7 +86,7 @@ module ocean_model_mod
86
86
87
87
! > This type is used for communication with other components via the FMS coupler.
88
88
! ! The element names and types can be changed only with great deliberation, hence
89
- ! ! the persistnce of things like the cutsy element name "avg_kount".
89
+ ! ! the persistence of things like the cutesy element name "avg_kount".
90
90
type, public :: ocean_public_type
91
91
type (domain2d) :: Domain ! < The domain for the surface fields.
92
92
logical :: is_ocean_pe ! < .true. on processors that run the ocean model.
@@ -110,8 +110,8 @@ module ocean_model_mod
110
110
! ! a global max across ocean and non-ocean processors can be
111
111
! ! used to determine its value.
112
112
real , pointer , dimension (:,:) :: &
113
- t_surf = > NULL (), & ! < SST on t-cell ( degrees Kelvin)
114
- s_surf = > NULL (), & ! < SSS on t-cell (psu)
113
+ t_surf = > NULL (), & ! < SST on t-cell [ degrees Kelvin]
114
+ s_surf = > NULL (), & ! < SSS on t-cell [ppt]
115
115
u_surf = > NULL (), & ! < i-velocity at the locations indicated by stagger [m s-1].
116
116
v_surf = > NULL (), & ! < j-velocity at the locations indicated by stagger [m s-1].
117
117
sea_lev = > NULL (), & ! < Sea level in m after correction for surface pressure,
@@ -154,8 +154,8 @@ module ocean_model_mod
154
154
155
155
logical :: icebergs_alter_ocean ! < If true, the icebergs can change ocean the
156
156
! ! ocean dynamics and forcing fluxes.
157
- real :: press_to_z ! < A conversion factor between pressure and ocean
158
- ! ! depth in m, usually 1/(rho_0*g) [m Pa-1].
157
+ real :: press_to_z ! < A conversion factor between pressure and ocean depth,
158
+ ! ! usually 1/(rho_0*g) [Z T2 R-1 L-2 ~> m Pa-1].
159
159
real :: C_p ! < The heat capacity of seawater [J degC-1 kg-1].
160
160
logical :: offline_tracer_mode = .false. ! < If false, use the model in prognostic mode
161
161
! ! with the barotropic and baroclinic dynamics, thermodynamics,
@@ -221,7 +221,7 @@ module ocean_model_mod
221
221
! ! for restarts and reading restart files if appropriate.
222
222
! !
223
223
! ! This subroutine initializes both the ocean state and the ocean surface type.
224
- ! ! Because of the way that indicies and domains are handled, Ocean_sfc must have
224
+ ! ! Because of the way that indices and domains are handled, Ocean_sfc must have
225
225
! ! been used in a previous call to initialize_ocean_type.
226
226
subroutine ocean_model_init (Ocean_sfc , OS , Time_init , Time_in , wind_stagger , gas_fields_ocn )
227
227
type (ocean_public_type), target , &
@@ -242,16 +242,16 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, wind_stagger, gas
242
242
! ! tracer fluxes, and can be used to spawn related
243
243
! ! internal variables in the ice model.
244
244
! Local variables
245
- real :: Rho0 ! The Boussinesq ocean density [kg m-3].
246
- real :: G_Earth ! The gravitational acceleration [m s-2].
247
- real :: HFrz ! < If HFrz > 0 (m) , melt potential will be computed.
245
+ real :: Rho0 ! The Boussinesq ocean density [R ~> kg m-3]
246
+ real :: G_Earth ! The gravitational acceleration [L2 Z-1 T-2 ~> m s-2]
247
+ real :: HFrz ! < If HFrz > 0 [Z ~> m] , melt potential will be computed.
248
248
! ! The actual depth over which melt potential is computed will
249
249
! ! min(HFrz, OBLD), where OBLD is the boundary layer depth.
250
250
! ! If HFrz <= 0 (default), melt potential will not be computed.
251
- logical :: use_melt_pot! < If true, allocate melt_potential array
251
+ logical :: use_melt_pot ! < If true, allocate melt_potential array
252
252
253
- ! This include declares and sets the variable "version".
254
- #include " version_variable.h"
253
+ ! This include declares and sets the variable "version".
254
+ # include " version_variable.h"
255
255
character (len= 40 ) :: mdl = " ocean_model_init" ! This module's name.
256
256
character (len= 48 ) :: stagger ! A string indicating the staggering locations for the
257
257
! surface velocities returned to the coupler.
@@ -331,28 +331,29 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, wind_stagger, gas
331
331
" calculate accelerations and the mass for conservation " // &
332
332
" properties, or with BOUSSINSEQ false to convert some " // &
333
333
" parameters from vertical units of m to kg m-2." , &
334
- units= " kg m-3" , default= 1035.0 )
334
+ units= " kg m-3" , default= 1035.0 , scale = OS % US % kg_m3_to_R )
335
335
call get_param(param_file, mdl, " G_EARTH" , G_Earth, &
336
336
" The gravitational acceleration of the Earth." , &
337
- units= " m s-2" , default = 9.80 )
337
+ units= " m s-2" , default= 9.80 , scale = OS % US % m_s_to_L_T ** 2 * OS % US % Z_to_m )
338
338
339
339
call get_param(param_file, mdl, " ICE_SHELF" , OS% use_ice_shelf, &
340
340
" If true, enables the ice shelf model." , default= .false. )
341
341
342
342
call get_param(param_file, mdl, " ICEBERGS_APPLY_RIGID_BOUNDARY" , OS% icebergs_alter_ocean, &
343
343
" If true, allows icebergs to change boundary condition felt by ocean" , default= .false. )
344
344
345
- OS% press_to_z = 1.0 / (Rho0* G_Earth)
345
+ OS% press_to_z = 1.0 / (Rho0* G_Earth)
346
346
347
347
! Consider using a run-time flag to determine whether to do the diagnostic
348
348
! vertical integrals, since the related 3-d sums are not negligible in cost.
349
349
call get_param(param_file, mdl, " HFREEZE" , HFrz, &
350
350
" If HFREEZE > 0, melt potential will be computed. The actual depth " // &
351
351
" over which melt potential is computed will be min(HFREEZE, OBLD), " // &
352
352
" where OBLD is the boundary layer depth. If HFREEZE <= 0 (default), " // &
353
- " melt potential will not be computed." , units= " m" , default=- 1.0 , do_not_log= .true. )
353
+ " melt potential will not be computed." , &
354
+ units= " m" , default=- 1.0 , scale= OS% US% m_to_Z, do_not_log= .true. )
354
355
355
- if (HFrz .gt. 0.0 ) then
356
+ if (HFrz > 0.0 ) then
356
357
use_melt_pot= .true.
357
358
else
358
359
use_melt_pot= .false.
@@ -655,7 +656,7 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, time_start_upda
655
656
656
657
! Translate state into Ocean.
657
658
! call convert_state_to_ocean_type(OS%sfc_state, Ocean_sfc, OS%grid, OS%US, &
658
- ! Ice_ocean_boundary%p , OS%press_to_z)
659
+ ! OS%fluxes%p_surf_full , OS%press_to_z)
659
660
call convert_state_to_ocean_type(OS% sfc_state, Ocean_sfc, OS% grid, OS% US)
660
661
Time1 = OS% Time ; if (do_dyn) Time1 = OS% Time_dyn
661
662
call coupler_type_send_data(Ocean_sfc% fields, Time1)
@@ -766,7 +767,7 @@ subroutine initialize_ocean_public_type(input_domain, Ocean_sfc, diag, gas_field
766
767
! ! tracer fluxes.
767
768
768
769
integer :: xsz, ysz, layout(2 )
769
- ! ice-ocean-boundary fields are always allocated using absolute indicies
770
+ ! ice-ocean-boundary fields are always allocated using absolute indices
770
771
! and have no halos.
771
772
integer :: isc, iec, jsc, jec
772
773
@@ -806,7 +807,7 @@ end subroutine initialize_ocean_public_type
806
807
! ! surface state variable. This may eventually be folded into the MOM
807
808
! ! code that calculates the surface state in the first place.
808
809
! ! Note the offset in the arrays because the ocean_data_type has no
809
- ! ! halo points in its arrays and always uses absolute indicies .
810
+ ! ! halo points in its arrays and always uses absolute indices .
810
811
subroutine convert_state_to_ocean_type (sfc_state , Ocean_sfc , G , US , patm , press_to_z )
811
812
type (surface), intent (inout ) :: sfc_state ! < A structure containing fields that
812
813
! ! describe the surface state of the ocean.
@@ -816,9 +817,9 @@ subroutine convert_state_to_ocean_type(sfc_state, Ocean_sfc, G, US, patm, press_
816
817
! ! have their data set here.
817
818
type (ocean_grid_type), intent (inout ) :: G ! < The ocean's grid structure
818
819
type (unit_scale_type), intent (in ) :: US ! < A dimensional unit scaling type
819
- real , optional , intent (in ) :: patm(:,:) ! < The pressure at the ocean surface [Pa].
820
- real , optional , intent (in ) :: press_to_z ! < A conversion factor between pressure and
821
- ! ! ocean depth in m , usually 1/(rho_0*g) [m Pa-1].
820
+ real , optional , intent (in ) :: patm(:,:) ! < The pressure at the ocean surface [R L2 T-2 ~> Pa]
821
+ real , optional , intent (in ) :: press_to_z ! < A conversion factor between pressure and ocean
822
+ ! ! depth, usually 1/(rho_0*g) [Z T2 R-1 L-2 ~> m Pa-1]
822
823
! Local variables
823
824
real :: IgR0
824
825
character (len= 48 ) :: val_str
@@ -860,7 +861,7 @@ subroutine convert_state_to_ocean_type(sfc_state, Ocean_sfc, G, US, patm, press_
860
861
861
862
if (present (patm)) then
862
863
do j= jsc_bnd,jec_bnd ; do i= isc_bnd,iec_bnd
863
- Ocean_sfc% sea_lev(i,j) = US% Z_to_m * sfc_state% sea_lev(i+ i0,j+ j0) + patm(i,j) * press_to_z
864
+ Ocean_sfc% sea_lev(i,j) = US% Z_to_m * ( sfc_state% sea_lev(i+ i0,j+ j0) + patm(i,j) * press_to_z)
864
865
Ocean_sfc% area(i,j) = US% L_to_m** 2 * G% areaT(i+ i0,j+ j0)
865
866
enddo ; enddo
866
867
else
@@ -946,7 +947,7 @@ end subroutine ocean_model_init_sfc
946
947
947
948
! > ocean_model_flux_init is used to initialize properties of the air-sea fluxes
948
949
! ! as determined by various run-time parameters. It can be called from
949
- ! ! non-ocean PEs, or PEs that have not yet been initialzed , and it can safely
950
+ ! ! non-ocean PEs, or PEs that have not yet been initialized , and it can safely
950
951
! ! be called multiple times.
951
952
subroutine ocean_model_flux_init (OS , verbosity )
952
953
type (ocean_state_type), optional , pointer :: OS ! < An optional pointer to the ocean state,
0 commit comments