30 implicit none ;
private 32 #include <MOM_memory.h> 49 Rho_T0_S0, dRho_dT, dRho_dS)
52 real,
intent(in) :: pressure
53 real,
intent(out) :: rho
54 real,
intent(in) :: Rho_T0_S0
55 real,
intent(in) :: dRho_dT
57 real,
intent(in) :: dRho_dS
74 rho = rho_t0_s0 + drho_dt*t + drho_ds*s
82 Rho_T0_S0, dRho_dT, dRho_dS)
83 real,
intent(in),
dimension(:) :: T
85 real,
intent(in),
dimension(:) :: S
86 real,
intent(in),
dimension(:) :: pressure
87 real,
intent(out),
dimension(:) :: rho
88 integer,
intent(in) :: start
89 integer,
intent(in) :: npts
90 real,
intent(in) :: Rho_T0_S0
91 real,
intent(in) :: dRho_dT, dRho_dS
108 real :: al0, p0, lambda
111 do j=start,start+npts-1
112 rho(j) = rho_t0_s0 + drho_dt*t(j) + drho_ds*s(j)
119 drho_dS_out, start, npts, Rho_T0_S0, dRho_dT, dRho_dS)
120 real,
intent(in),
dimension(:) :: T
122 real,
intent(in),
dimension(:) :: S
123 real,
intent(in),
dimension(:) :: pressure
124 real,
intent(out),
dimension(:) :: drho_dT_out
126 real,
intent(out),
dimension(:) :: drho_dS_out
128 integer,
intent(in) :: start
129 integer,
intent(in) :: npts
130 real,
intent(in) :: Rho_T0_S0
131 real,
intent(in) :: dRho_dT, dRho_dS
152 do j=start,start+npts-1
153 drho_dt_out(j) = drho_dt
154 drho_ds_out(j) = drho_ds
161 start, npts, Rho_T0_S0, dRho_dT, dRho_dS)
162 real,
intent(in),
dimension(:) :: T
164 real,
intent(in),
dimension(:) :: S
165 real,
intent(in),
dimension(:) :: pressure
166 real,
intent(out),
dimension(:) :: dSV_dS
168 real,
intent(out),
dimension(:) :: dSV_dT
170 integer,
intent(in) :: start
171 integer,
intent(in) :: npts
172 real,
intent(in) :: Rho_T0_S0
173 real,
intent(in) :: dRho_dT, dRho_dS
189 do j=start,start+npts-1
191 i_rho2 = 1.0 / (rho_t0_s0 + (drho_dt*t(j) + drho_ds*s(j)))**2
192 dsv_dt(j) = -drho_dt * i_rho2
193 dsv_ds(j) = -drho_ds * i_rho2
202 Rho_T0_S0, dRho_dT, dRho_dS)
203 real,
intent(in),
dimension(:) :: T
205 real,
intent(in),
dimension(:) :: S
206 real,
intent(in),
dimension(:) :: pressure
207 real,
intent(out),
dimension(:) :: rho
208 real,
intent(out),
dimension(:) :: drho_dp
211 integer,
intent(in) :: start
212 integer,
intent(in) :: npts
213 real,
intent(in) :: Rho_T0_S0
214 real,
intent(in) :: dRho_dT, dRho_dS
237 do j=start,start+npts-1
238 rho(j) = rho_t0_s0 + drho_dt*t(j) + drho_ds*s(j)
247 Rho_T0_S0, dRho_dT, dRho_dS, dpa, intz_dpa, intx_dpa, inty_dpa)
249 real,
dimension(HII%isd:HII%ied,HII%jsd:HII%jed), &
252 real,
dimension(HII%isd:HII%ied,HII%jsd:HII%jed), &
254 real,
dimension(HII%isd:HII%ied,HII%jsd:HII%jed), &
256 real,
dimension(HII%isd:HII%ied,HII%jsd:HII%jed), &
258 real,
intent(in) :: rho_ref
261 real,
intent(in) :: rho_0_pres
265 real,
intent(in) :: G_e
267 real,
intent(in) :: Rho_T0_S0
268 real,
intent(in) :: dRho_dT
270 real,
intent(in) :: dRho_dS
272 real,
dimension(HIO%isd:HIO%ied,HIO%jsd:HIO%jed), &
275 real,
dimension(HIO%isd:HIO%ied,HIO%jsd:HIO%jed), &
276 optional,
intent(out) :: intz_dpa
279 real,
dimension(HIO%IsdB:HIO%IedB,HIO%jsd:HIO%jed), &
280 optional,
intent(out) :: intx_dpa
283 real,
dimension(HIO%isd:HIO%ied,HIO%JsdB:HIO%JedB), &
284 optional,
intent(out) :: inty_dpa
320 integer :: is, ie, js, je, Isq, Ieq, Jsq, Jeq, i, j, ioff, joff
322 ioff = hio%idg_offset - hii%idg_offset
323 joff = hio%jdg_offset - hii%jdg_offset
327 isq = hio%IscB + ioff ; ieq = hio%IecB + ioff
328 jsq = hio%JscB + joff ; jeq = hio%JecB + joff
329 is = hio%isc + ioff ; ie = hio%iec + ioff
330 js = hio%jsc + joff ; je = hio%jec + joff
333 do j=jsq,jeq+1 ;
do i=isq,ieq+1
334 dz = z_t(i,j) - z_b(i,j)
335 rho_anom = (rho_t0_s0 - rho_ref) + drho_dt*t(i,j) + drho_ds*s(i,j)
336 dpa(i-ioff,j-joff) = g_e*rho_anom*dz
337 if (
present(intz_dpa)) intz_dpa(i-ioff,j-joff) = 0.5*g_e*rho_anom*dz**2
340 if (
present(intx_dpa))
then ;
do j=js,je ;
do i=isq,ieq
341 dzl = z_t(i,j) - z_b(i,j) ; dzr = z_t(i+1,j) - z_b(i+1,j)
342 ral = (rho_t0_s0 - rho_ref) + (drho_dt*t(i,j) + drho_ds*s(i,j))
343 rar = (rho_t0_s0 - rho_ref) + (drho_dt*t(i+1,j) + drho_ds*s(i+1,j))
345 intx_dpa(i-ioff,j-joff) = g_e*c1_6 * (dzl*(2.0*ral + rar) + dzr*(2.0*rar + ral))
346 enddo ;
enddo ;
endif 348 if (
present(inty_dpa))
then ;
do j=jsq,jeq ;
do i=is,ie
349 dzl = z_t(i,j) - z_b(i,j) ; dzr = z_t(i,j+1) - z_b(i,j+1)
350 ral = (rho_t0_s0 - rho_ref) + (drho_dt*t(i,j) + drho_ds*s(i,j))
351 rar = (rho_t0_s0 - rho_ref) + (drho_dt*t(i,j+1) + drho_ds*s(i,j+1))
353 inty_dpa(i-ioff,j-joff) = g_e*c1_6 * (dzl*(2.0*ral + rar) + dzr*(2.0*rar + ral))
354 enddo ;
enddo ;
endif 362 dRho_dT, dRho_dS, dza, intp_dza, intx_dza, inty_dza, halo_size)
364 real,
dimension(HI%isd:HI%ied,HI%jsd:HI%jed), &
367 real,
dimension(HI%isd:HI%ied,HI%jsd:HI%jed), &
369 real,
dimension(HI%isd:HI%ied,HI%jsd:HI%jed), &
371 real,
dimension(HI%isd:HI%ied,HI%jsd:HI%jed), &
373 real,
intent(in) :: alpha_ref
377 real,
intent(in) :: Rho_T0_S0
378 real,
intent(in) :: dRho_dT
380 real,
intent(in) :: dRho_dS
382 real,
dimension(HI%isd:HI%ied,HI%jsd:HI%jed), &
385 real,
dimension(HI%isd:HI%ied,HI%jsd:HI%jed), &
386 optional,
intent(out) :: intp_dza
389 real,
dimension(HI%IsdB:HI%IedB,HI%jsd:HI%jed), &
390 optional,
intent(out) :: intx_dza
394 real,
dimension(HI%isd:HI%ied,HI%JsdB:HI%JedB), &
395 optional,
intent(out) :: inty_dza
399 integer,
optional,
intent(in) :: halo_size
435 integer :: Isq, Ieq, Jsq, Jeq, ish, ieh, jsh, jeh, i, j, halo
437 isq = hi%IscB ; ieq = hi%IecB ; jsq = hi%JscB ; jeq = hi%JecB
438 halo = 0 ;
if (
present(halo_size)) halo = max(halo_size,0)
439 ish = hi%isc-halo ; ieh = hi%iec+halo ; jsh = hi%jsc-halo ; jeh = hi%jec+halo
440 if (
present(intx_dza))
then ; ish = min(isq,ish) ; ieh = max(ieq+1,ieh);
endif 441 if (
present(inty_dza))
then ; jsh = min(jsq,jsh) ; jeh = max(jeq+1,jeh);
endif 444 do j=jsh,jeh ;
do i=ish,ieh
445 dp = p_b(i,j) - p_t(i,j)
446 drho_ts = drho_dt*t(i,j) + drho_ds*s(i,j)
448 alpha_anom = ((1.0-rho_t0_s0*alpha_ref) - drho_ts*alpha_ref) / (rho_t0_s0 + drho_ts)
449 dza(i,j) = alpha_anom*dp
450 if (
present(intp_dza)) intp_dza(i,j) = 0.5*alpha_anom*dp**2
453 if (
present(intx_dza))
then ;
do j=hi%jsc,hi%jec ;
do i=isq,ieq
454 dpl = p_b(i,j) - p_t(i,j) ; dpr = p_b(i+1,j) - p_t(i+1,j)
455 drho_ts = drho_dt*t(i,j) + drho_ds*s(i,j)
456 aal = ((1.0 - rho_t0_s0*alpha_ref) - drho_ts*alpha_ref) / (rho_t0_s0 + drho_ts)
457 drho_ts = drho_dt*t(i+1,j) + drho_ds*s(i+1,j)
458 aar = ((1.0 - rho_t0_s0*alpha_ref) - drho_ts*alpha_ref) / (rho_t0_s0 + drho_ts)
460 intx_dza(i,j) = c1_6 * (2.0*(dpl*aal + dpr*aar) + (dpl*aar + dpr*aal))
461 enddo ;
enddo ;
endif 463 if (
present(inty_dza))
then ;
do j=jsq,jeq ;
do i=hi%isc,hi%iec
464 dpl = p_b(i,j) - p_t(i,j) ; dpr = p_b(i,j+1) - p_t(i,j+1)
465 drho_ts = drho_dt*t(i,j) + drho_ds*s(i,j)
466 aal = ((1.0 - rho_t0_s0*alpha_ref) - drho_ts*alpha_ref) / (rho_t0_s0 + drho_ts)
467 drho_ts = drho_dt*t(i,j+1) + drho_ds*s(i,j+1)
468 aar = ((1.0 - rho_t0_s0*alpha_ref) - drho_ts*alpha_ref) / (rho_t0_s0 + drho_ts)
470 inty_dza(i,j) = c1_6 * (2.0*(dpl*aal + dpr*aar) + (dpl*aar + dpr*aal))
471 enddo ;
enddo ;
endif subroutine, public int_spec_vol_dp_linear(T, S, p_t, p_b, alpha_ref, HI, Rho_T0_S0, dRho_dT, dRho_dS, dza, intp_dza, intx_dza, inty_dza, halo_size)
This subroutine calculates analytical and nearly-analytical integrals in pressure across layers of ge...
subroutine, public calculate_density_scalar_linear(T, S, pressure, rho, Rho_T0_S0, dRho_dT, dRho_dS)
This subroutine computes the density of sea water with a trivial linear equation of state (in kg/m^3)...
Defines the horizontal index type (hor_index_type) used for providing index ranges.
subroutine, public calculate_density_array_linear(T, S, pressure, rho, start, npts, Rho_T0_S0, dRho_dT, dRho_dS)
This subroutine computes the density of sea water with a trivial linear equation of state (in kg/m^3)...
Container for horizontal index ranges for data, computational and global domains. ...
subroutine, public calculate_compress_linear(T, S, pressure, rho, drho_dp, start, npts, Rho_T0_S0, dRho_dT, dRho_dS)
This subroutine computes the in situ density of sea water (rho) and the compressibility (drho/dp == C...
subroutine, public int_density_dz_linear(T, S, z_t, z_b, rho_ref, rho_0_pres, G_e, HII, HIO, Rho_T0_S0, dRho_dT, dRho_dS, dpa, intz_dpa, intx_dpa, inty_dpa)
This subroutine calculates analytical and nearly-analytical integrals of pressure anomalies across la...
subroutine, public calculate_specvol_derivs_linear(T, S, pressure, dSV_dT, dSV_dS, start, npts, Rho_T0_S0, dRho_dT, dRho_dS)
subroutine, public calculate_density_derivs_linear(T, S, pressure, drho_dT_out, drho_dS_out, start, npts, Rho_T0_S0, dRho_dT, dRho_dS)
This subroutine calculates the partial derivatives of density * with potential temperature and salini...