Skip to content

Commit e477283

Browse files
committed
Inline Harmonic Analysis
Update 6: The frequencies of 8 overtides/compound tides (MK3, MN4, M4, MS4, S4, M6, S6, M8) have been added for the harmonic analysis.
1 parent 032488f commit e477283

File tree

5 files changed

+43
-23
lines changed

5 files changed

+43
-23
lines changed

src/core/MOM.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1064,7 +1064,7 @@ subroutine step_MOM(forces_in, fluxes_in, sfc_state, Time_start, time_int_in, CS
10641064
ssh(i,j) = CS%ssh_rint(i,j)*I_wt_ssh
10651065
CS%ave_ssh_ibc(i,j) = ssh(i,j)
10661066
enddo ; enddo
1067-
if (associated(CS%HA_CSp)) call HA_accum('ssh', ssh, Time_local, CS%HA_CSp)
1067+
if (associated(CS%HA_CSp)) call HA_accum('ssh', ssh, Time_local, G, CS%HA_CSp)
10681068
if (do_dyn) then
10691069
call adjust_ssh_for_p_atm(CS%tv, G, GV, US, CS%ave_ssh_ibc, forces%p_surf_SSH, &
10701070
CS%calc_rho_for_sea_lev)

src/core/MOM_barotropic.F90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1935,8 +1935,8 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
19351935
! Accumulator is updated at the end of every baroclinic time step.
19361936
! Harmonic analysis will not be performed of a field that is not registered.
19371937
if (associated(CS%HA_CSp) .and. find_etaav) then
1938-
call HA_accum('ubt', ubt, CS%Time, CS%HA_CSp)
1939-
call HA_accum('vbt', vbt, CS%Time, CS%HA_CSp)
1938+
call HA_accum('ubt', ubt, CS%Time, G, CS%HA_CSp)
1939+
call HA_accum('vbt', vbt, CS%Time, G, CS%HA_CSp)
19401940
endif
19411941

19421942
if (id_clock_calc_post > 0) call cpu_clock_end(id_clock_calc_post)

src/core/MOM_dynamics_split_RK2.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1573,7 +1573,7 @@ subroutine initialize_dyn_split_RK2(u, v, h, tv, uh, vh, eta, Time, G, GV, US, p
15731573
if (CS%calculate_SAL) call SAL_init(h, tv, G, GV, US, param_file, CS%SAL_CSp, restart_CS)
15741574
if (CS%use_tides) call tidal_forcing_init(Time, G, US, param_file, CS%tides_CSp)
15751575
if (CS%use_HA) then
1576-
call HA_init(Time, G, US, param_file, nc, CS%HA_CSp)
1576+
call HA_init(Time, US, param_file, nc, CS%HA_CSp)
15771577
HA_CSp => CS%HA_CSp
15781578
else
15791579
HA_CSp => NULL()

src/core/MOM_dynamics_split_RK2b.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1456,7 +1456,7 @@ subroutine initialize_dyn_split_RK2b(u, v, h, tv, uh, vh, eta, Time, G, GV, US,
14561456
if (CS%calculate_SAL) call SAL_init(h, tv, G, GV, US, param_file, CS%SAL_CSp, restart_CS)
14571457
if (CS%use_tides) call tidal_forcing_init(Time, G, US, param_file, CS%tides_CSp)
14581458
if (CS%use_HA) then
1459-
call HA_init(Time, G, US, param_file, nc, CS%HA_CSp)
1459+
call HA_init(Time, US, param_file, nc, CS%HA_CSp)
14601460
HA_CSp => CS%HA_CSp
14611461
else
14621462
HA_CSp => NULL()

src/diagnostics/MOM_harmonic_analysis.F90

Lines changed: 38 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -1,15 +1,15 @@
11
!> Inline harmonic analysis (conventional)
22
module MOM_harmonic_analysis
33

4-
use MOM_time_manager, only : time_type, real_to_time, time_type_to_real, &
5-
set_date, get_date, increment_date, &
6-
operator(+), operator(-), operator(<), operator(>), operator(>=)
4+
use MOM_time_manager, only : time_type, real_to_time, time_type_to_real
5+
use MOM_time_manager, only : set_date, get_date, increment_date
6+
use MOM_time_manager, only : operator(+), operator(-), operator(<), operator(>), operator(>=)
77
use MOM_grid, only : ocean_grid_type
88
use MOM_unit_scaling, only : unit_scale_type
99
use MOM_file_parser, only : param_file_type, get_param
10-
use MOM_io, only : file_exists, open_ASCII_file, READONLY_FILE, close_file, &
11-
MOM_infra_file, vardesc, MOM_field, &
12-
var_desc, create_MOM_file, SINGLE_FILE, MOM_write_field
10+
use MOM_io, only : file_exists, open_ASCII_file, READONLY_FILE, close_file
11+
use MOM_io, only : MOM_infra_file, vardesc, MOM_field
12+
use MOM_io, only : var_desc, create_MOM_file, SINGLE_FILE, MOM_write_field
1313
use MOM_error_handler, only : MOM_mesg, MOM_error, NOTE
1414
use MOM_tidal_forcing, only : astro_longitudes, astro_longitudes_init, eq_phase, nodal_fu, tidal_frequency
1515

@@ -54,7 +54,6 @@ module MOM_harmonic_analysis
5454
integer :: length !< Number of fields of which harmonic analysis is to be performed
5555
character(len=4), allocatable, dimension(:) :: const_name !< The name of each constituent
5656
character(len=255) :: path !< Path to directory where output will be written
57-
type(ocean_grid_type) :: G !< The ocean's grid structure
5857
type(unit_scale_type) :: US !< A dimensional unit scaling type
5958
type(HA_node), pointer :: list => NULL() !< A linked list for storing the HA info of different fields
6059
end type harmonic_analysis_CS
@@ -63,9 +62,8 @@ module MOM_harmonic_analysis
6362

6463
!> This subroutine sets static variables used by this module and initializes CS%list.
6564
!! THIS MUST BE CALLED AT THE END OF tidal_forcing_init.
66-
subroutine HA_init(Time, G, US, param_file, nc, CS)
65+
subroutine HA_init(Time, US, param_file, nc, CS)
6766
type(time_type), intent(in) :: Time !< The current model time
68-
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
6967
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
7068
type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
7169
integer, intent(in) :: nc !< The number of tidal constituents in use
@@ -164,7 +162,28 @@ subroutine HA_init(Time, G, US, param_file, nc, CS)
164162
CS%freq(c), "Frequency of the "//trim(CS%const_name(c))//&
165163
" constituent. This is used if USE_HA is true and "//trim(CS%const_name(c))//&
166164
" is in HA_CONSTITUENTS.", units="rad s-1", scale=US%T_to_s, default=0.0)
167-
if (CS%freq(c)<=0.0) CS%freq(c) = tidal_frequency(trim(CS%const_name(c)))
165+
if (CS%freq(c)<=0.0) then
166+
select case (trim(CS%const_name(c)))
167+
case ('M4')
168+
CS%freq(c) = tidal_frequency('M2') * 2
169+
case ('M6')
170+
CS%freq(c) = tidal_frequency('M2') * 3
171+
case ('M8')
172+
CS%freq(c) = tidal_frequency('M2') * 4
173+
case ('S4')
174+
CS%freq(c) = tidal_frequency('S2') * 2
175+
case ('S6')
176+
CS%freq(c) = tidal_frequency('S2') * 3
177+
case ('MK3')
178+
CS%freq(c) = tidal_frequency('M2') + tidal_frequency('K1')
179+
case ('MS4')
180+
CS%freq(c) = tidal_frequency('M2') + tidal_frequency('S2')
181+
case ('MN4')
182+
CS%freq(c) = tidal_frequency('M2') + tidal_frequency('N2')
183+
case default
184+
CS%freq(c) = tidal_frequency(trim(CS%const_name(c)))
185+
end select
186+
endif
168187

169188
call get_param(param_file, mdl, "HA_"//trim(CS%const_name(c))//"_PHASE_T0", CS%phase0(c), &
170189
"Phase of the "//trim(CS%const_name(c))//" tidal constituent at time 0. "//&
@@ -236,7 +255,6 @@ subroutine HA_init(Time, G, US, param_file, nc, CS)
236255
! Populate some parameters of the control structure
237256
CS%nc = nc
238257
CS%length = 0
239-
CS%G = G
240258
CS%US = US
241259

242260
! Initialize CS%list
@@ -283,10 +301,11 @@ end subroutine HA_register
283301
!! harmonic constants and write results. The tidal constituents are those used in MOM_tidal_forcing, plus the
284302
!! mean (of zero frequency). For FtF, only the main diagonal and entries below it are calculated, which are needed
285303
!! for Cholesky decomposition.
286-
subroutine HA_accum(key, data, Time, CS)
304+
subroutine HA_accum(key, data, Time, G, CS)
287305
character(len=*), intent(in) :: key !< Name of the current field
288306
real, dimension(:,:), intent(in) :: data !< Input data of which harmonic analysis is to be performed [A]
289307
type(time_type), intent(in) :: Time !< The current model time
308+
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
290309
type(harmonic_analysis_CS), intent(inout) :: CS !< Control structure of the MOM_harmonic_analysis module
291310

292311
! Local variables
@@ -389,7 +408,7 @@ subroutine HA_accum(key, data, Time, CS)
389408
!!! Compute harmonic constants and write output as Time approaches CS%time_end !!!
390409
! This guarantees that HA_write will be called before Time becomes larger than CS%time_end
391410
if (time_type_to_real(CS%time_end - Time) <= dt) then
392-
call HA_write(ha1, Time, CS)
411+
call HA_write(ha1, Time, G, CS)
393412

394413
write(mesg,*) "MOM_harmonic_analysis: harmonic analysis done, key = ", trim(ha1%key)
395414
call MOM_error(NOTE, trim(mesg))
@@ -403,9 +422,10 @@ subroutine HA_accum(key, data, Time, CS)
403422
end subroutine HA_accum
404423

405424
!> This subroutine computes the harmonic constants and write output for the current field
406-
subroutine HA_write(ha1, Time, CS)
425+
subroutine HA_write(ha1, Time, G, CS)
407426
type(HA_type), pointer, intent(in) :: ha1 !< Control structure for the current field
408427
type(time_type), intent(in) :: Time !< The current model time
428+
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
409429
type(harmonic_analysis_CS), intent(in) :: CS !< Control structure of the MOM_harmonic_analysis module
410430

411431
! Local variables
@@ -442,18 +462,18 @@ subroutine HA_write(ha1, Time, CS)
442462

443463
! Create output file
444464
call create_MOM_file(cdf, trim(filename), cdf_vars, &
445-
2*nc+1, cdf_fields, SINGLE_FILE, 86400.0, G=CS%G)
465+
2*nc+1, cdf_fields, SINGLE_FILE, 86400.0, G=G)
446466

447467
! Add the initial field back to the mean state
448468
do j=js,je ; do i=is,ie
449469
FtSSHw(i,j,1) = FtSSHw(i,j,1) + ha1%ref(i,j)
450470
enddo ; enddo
451471

452472
! Write data
453-
call MOM_write_field(cdf, cdf_fields(1), CS%G%domain, FtSSHw(:,:,1), 0.0)
473+
call MOM_write_field(cdf, cdf_fields(1), G%domain, FtSSHw(:,:,1), 0.0)
454474
do k=1,nc
455-
call MOM_write_field(cdf, cdf_fields(2*k ), CS%G%domain, FtSSHw(:,:,2*k ), 0.0)
456-
call MOM_write_field(cdf, cdf_fields(2*k+1), CS%G%domain, FtSSHw(:,:,2*k+1), 0.0)
475+
call MOM_write_field(cdf, cdf_fields(2*k ), G%domain, FtSSHw(:,:,2*k ), 0.0)
476+
call MOM_write_field(cdf, cdf_fields(2*k+1), G%domain, FtSSHw(:,:,2*k+1), 0.0)
457477
enddo
458478

459479
call cdf%flush()

0 commit comments

Comments
 (0)