SOCA
soca_mom6.F90
Go to the documentation of this file.
1 ! (C) Copyright 2017-2021 UCAR
2 !
3 ! This software is licensed under the terms of the Apache Licence Version 2.0
4 ! which can be obtained at http://www.apache.org/licenses/LICENSE-2.0.
5 
6 module soca_mom6
7 
8 use fckit_mpi_module, only: fckit_mpi_comm
9 use mpp_mod, only : mpp_init
10 use fms_io_mod, only : fms_io_init, fms_io_exit
11 use fms_mod, only : read_data, write_data, fms_init, fms_end
12 use time_interp_external_mod, only : time_interp_external_init
13 use time_manager_mod, only: time_type
14 
15 use kinds, only: kind_real
16 
17 use mom, only : initialize_mom, step_mom, mom_control_struct, mom_end, &
18  extract_surface_state, finish_mom_initialization, &
19  get_mom_state_elements
20 use mom_diag_mediator, only : diag_ctrl
21 use mom_domains, only : mom_infra_init, mom_infra_end, &
22  mom_domains_init, clone_mom_domain, mom_domain_type
23 use mom_error_handler, only : mom_error, mom_mesg, warning, fatal, is_root_pe
24 use mom_file_parser, only : get_param, param_file_type, close_param_file
25 use mom_forcing_type, only : forcing, mech_forcing, forcing_diagnostics, &
26  mech_forcing_diags, mom_forcing_chksum, &
27  mom_mech_forcing_chksum
28 use mom_get_input, only : directories, get_mom_input, directories
29 use mom_grid, only : ocean_grid_type, mom_grid_init
30 use mom_io, only : open_file, close_file, &
31  check_nml_error, io_infra_init, io_infra_end, &
32  ascii_file, readonly_file
33 use mom_restart, only : mom_restart_cs
34 use mom_string_functions,only : uppercase
35 use mom_surface_forcing, only : set_forcing, forcing_save_restart, &
36  surface_forcing_init, surface_forcing_cs
37 use mom_time_manager, only : time_type, set_date, get_date, &
38  real_to_time, time_type_to_real, &
39  operator(+), operator(-), operator(*), operator(/), &
40  operator(>), operator(<), operator(>=), &
41  increment_date, set_calendar_type, month_name, &
42  julian, gregorian, noleap, thirty_day_months, &
43  no_calendar
44 use mom_tracer_flow_control, only : tracer_flow_control_cs
45 use mom_unit_scaling, only : unit_scale_type
46 use mom_variables, only : surface
47 use mom_verticalgrid, only : verticalgrid_type, &
48  verticalgridinit, verticalgridend
49 
50 implicit none
51 
52 private
53 public :: soca_geomdomain_init, &
55 
56 !> Data structure neccessary to initialize/run mom6
58  type(mech_forcing) :: forces !< Driving mechanical surface forces
59  type(forcing) :: fluxes !< Pointers to the thermodynamic forcing fields
60  !< at the ocean surface.
61  type(surface) :: sfc_state !< Pointers to the ocean surface state fields.
62  real :: dt_forcing !< Coupling time step in seconds.
63  type(time_type) :: time_step_ocean !< time_type version of dt_forcing
64  type(directories) :: dirs !< Relevant dirs/path
65  type(time_type) :: time !< Model's time before call to step_MOM.
66  type(unit_scale_type), pointer :: scaling !< Unit conversion factors
67  type(ocean_grid_type), pointer :: grid !< Grid metrics
68  type(verticalgrid_type), pointer :: gv !< Vertical grid
69  type(mom_control_struct), pointer :: mom_csp !< Tracer flow control structure.
70  type(mom_restart_cs), pointer :: restart_csp !< A pointer to the restart control structure
71  type(surface_forcing_cs), pointer :: surface_forcing_csp => null()
72  type(fckit_mpi_comm) :: f_comm
73  type(param_file_type) :: param_file
74 end type soca_mom6_config
75 
76 contains
77 
78 ! ------------------------------------------------------------------------------
79 !> Initialize mom6's domain
80 subroutine soca_geomdomain_init(Domain, nk, f_comm)
81  type(mom_domain_type), pointer, intent(in) :: domain !< Ocean model domain
82  integer, intent(out) :: nk
83  type(fckit_mpi_comm), intent(in) :: f_comm
84 
85  type(param_file_type) :: param_file !< Structure to parse for run-time parameters
86  type(directories) :: dirs !< Structure containing several relevant directory paths
87  character(len=40) :: mod_name = "soca_mom6" ! This module's name.
88 
89  call mpp_init(localcomm=f_comm%communicator())
90 
91  ! Initialize fms
92  call fms_init()
93 
94  ! Initialize fms io
95  call fms_io_init()
96 
97  ! Parse grid inputs
98  call get_mom_input(param_file, dirs)
99 
100  ! Domain decomposition/Inintialize mpp domains
101  call mom_domains_init(domain, param_file)
102 
103  ! Get number of levels
104  call get_param(param_file, mod_name, "NK", nk, fail_if_missing=.true.)
105 
106  call close_param_file(param_file)
107  call fms_io_exit()
108 
109 end subroutine soca_geomdomain_init
110 
111 ! ------------------------------------------------------------------------------
112 !> Setup/initialize/prepare mom6 for time integration
113 subroutine soca_mom6_init(mom6_config, partial_init)
114  type(soca_mom6_config), intent(out) :: mom6_config
115  logical, optional, intent(in) :: partial_init
116 
117  type(time_type) :: start_time ! The start time of the simulation.
118  type(time_type) :: time_in !
119  real :: dt ! The baroclinic dynamics time step, in seconds.
120  integer :: date_init(6)=0 ! The start date of the whole simulation.
121  integer :: years=0, months=0, days=0 ! These may determine the segment run
122  integer :: hours=0, minutes=0, seconds=0 ! length, if read from a namelist.
123  type(param_file_type) :: param_file ! The structure indicating the file(s)
124  ! containing all run-time parameters.
125  character(len=16) :: calendar = 'julian'
126  integer :: calendar_type=-1
127  integer :: unit, io_status, ierr
128  logical :: offline_tracer_mode = .false.
129 
130  type(tracer_flow_control_cs), pointer :: tracer_flow_csp => null()
131  type(diag_ctrl), pointer :: diag => null() !< Diagnostic structure
132  character(len=4), parameter :: vers_num = 'v2.0'
133  character(len=40) :: mod_name = "soca_mom6" ! This module's name.
134  integer :: ocean_nthreads = 1
135  integer :: ncores_per_node = 1
136  logical :: use_hyper_thread = .false.
137  !integer :: omp_get_num_threads,omp_get_thread_num,get_cpu_affinity,adder,base_cpu
138  namelist /ocean_solo_nml/ date_init, calendar, months, days, hours, minutes, seconds,&
139  ocean_nthreads, ncores_per_node, use_hyper_thread
140  integer :: param_int
141  logical :: a_partial_init = .false.
142 
143  ! Check if partial mom6 init is requiered
144  if (present(partial_init)) a_partial_init = partial_init
145 
146  call mom_infra_init(localcomm=mom6_config%f_comm%communicator())
147  call io_infra_init()
148 
149  ! Provide for namelist specification of the run length and calendar data.
150  call open_file(unit, 'input.nml', form=ascii_file, action=readonly_file)
151  read(unit, ocean_solo_nml, iostat=io_status)
152  call close_file(unit)
153  ierr = check_nml_error(io_status,'ocean_solo_nml')
154  if (years+months+days+hours+minutes+seconds > 0) then
155  if (is_root_pe()) write(*,ocean_solo_nml)
156  endif
157  calendar = uppercase(calendar)
158  if (calendar(1:6) == 'JULIAN') then ; calendar_type = julian
159  elseif (calendar(1:9) == 'GREGORIAN') then ; calendar_type = gregorian
160  elseif (calendar(1:6) == 'NOLEAP') then ; calendar_type = noleap
161  elseif (calendar(1:10)=='THIRTY_DAY') then ; calendar_type = thirty_day_months
162  elseif (calendar(1:11)=='NO_CALENDAR') then; calendar_type = no_calendar
163  elseif (calendar(1:1) /= ' ') then
164  call mom_error(fatal,'MOM_driver: Invalid namelist value '//trim(calendar)//' for calendar')
165  else
166  call mom_error(fatal,'MOM_driver: No namelist value for calendar')
167  endif
168  call set_calendar_type(calendar_type)
169 
170  start_time = set_date(date_init(1),date_init(2), date_init(3), &
171  date_init(4),date_init(5),date_init(6))
172 
173  call time_interp_external_init
174 
175  ! Nullify mom6_config pointers
176  mom6_config%MOM_CSp => null()
177  mom6_config%restart_CSp => null()
178  mom6_config%grid => null()
179  mom6_config%GV => null()
180 
181  ! Set mom6_config%Time to time parsed from mom6 config
182  mom6_config%Time = start_time
183 
184  ! Initialize mom6
185  time_in = mom6_config%Time
186 
187  call initialize_mom(mom6_config%Time, &
188  start_time, &
189  param_file, &
190  mom6_config%dirs, &
191  mom6_config%MOM_CSp, &
192  mom6_config%restart_CSp, &
193  offline_tracer_mode=offline_tracer_mode, diag_ptr=diag, &
194  tracer_flow_csp=tracer_flow_csp, time_in=time_in)
195 
196  !US => mom6_config%scaling
197  ! Continue initialization
198  call get_mom_state_elements(mom6_config%MOM_CSp,&
199  g=mom6_config%grid,&
200  gv=mom6_config%GV,&
201  us=mom6_config%scaling,&
202  c_p=mom6_config%fluxes%C_p)
203 
204  mom6_config%param_file = param_file
205  ! Exit here for partial initialization
206  if (a_partial_init) return
207 
208  ! Setup surface forcing
209  call extract_surface_state(mom6_config%MOM_CSp, mom6_config%sfc_state)
210  call surface_forcing_init(mom6_config%Time,&
211  mom6_config%grid,&
212  mom6_config%scaling,&
213  param_file,&
214  diag,&
215  mom6_config%surface_forcing_CSp,&
216  tracer_flow_csp)
217 
218  ! Get time step from MOM config. TODO: Get DT from DA config
219  call get_param(param_file, mod_name, "DT", param_int, fail_if_missing=.true.)
220  dt = real(param_int)
221  mom6_config%dt_forcing = dt
222  mom6_config%Time_step_ocean = real_to_time(real(mom6_config%dt_forcing, kind=8))
223 
224  ! Finalize file parsing
225  call close_param_file(param_file)
226 
227  ! Set the forcing for the first steps.
228  call set_forcing(mom6_config%sfc_state,&
229  mom6_config%forces,&
230  mom6_config%fluxes,&
231  mom6_config%Time,&
232  mom6_config%Time_step_ocean,&
233  mom6_config%grid, &
234  mom6_config%scaling, &
235  mom6_config%surface_forcing_CSp)
236 
237  ! Do more stuff for mom init ...
238  call finish_mom_initialization(mom6_config%Time,&
239  mom6_config%dirs,&
240  mom6_config%MOM_CSp,&
241  mom6_config%restart_CSp)
242 
243 end subroutine soca_mom6_init
244 
245 ! ------------------------------------------------------------------------------
246 !> Release memory and possibly dump mom6's restart
247 subroutine soca_mom6_end(mom6_config)
248  type(soca_mom6_config), intent(inout) :: mom6_config
249 
250  ! Finalize fms
251  call io_infra_end
252 
253  !! as a temporary workaround to MPI_Finalize() issues, MOM_infra_end is NOT called
254  ! call MOM_infra_end
255 
256  ! Finalize mom6
257  call mom_end(mom6_config%MOM_CSp)
258 
259 end subroutine soca_mom6_end
260 
261 end module soca_mom6
subroutine, public soca_mom6_init(mom6_config, partial_init)
Setup/initialize/prepare mom6 for time integration.
Definition: soca_mom6.F90:114
subroutine, public soca_mom6_end(mom6_config)
Release memory and possibly dump mom6's restart.
Definition: soca_mom6.F90:248
subroutine, public soca_geomdomain_init(Domain, nk, f_comm)
Initialize mom6's domain.
Definition: soca_mom6.F90:81
Data structure neccessary to initialize/run mom6.
Definition: soca_mom6.F90:57