SOCA
soca_model_mod.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 !> Structure holding configuration variables for the model
7 
9 
10 use datetime_mod, only: datetime, datetime_to_string
11 use kinds, only: kind_real
12 
13 ! mom6/fms modules
14 use fms_io_mod, only : fms_io_init, fms_io_exit
15 use mom_restart, only : save_restart
16 use mom_surface_forcing, only : set_forcing
17 use mom_time_manager, only : operator(+)
18 use mom_time_manager, only : real_to_time, time_type_to_real
19 use mom, only : step_mom
20 use mpp_domains_mod, only : mpp_update_domains
21 use time_manager_mod, only : time_type, set_date
22 
23 ! soca modules
24 use soca_fields_mod, only: soca_field
25 use soca_geom_mod, only: soca_geom
27 use soca_state_mod, only: soca_state
28 use soca_utils, only: soca_str2int
29 
30 implicit none
31 private
32 
33 
34 !> Fortran derived type to hold configuration data for the model
35 type, public :: soca_model
36  integer :: advance_mom6 !< call mom6 step if true
37  real(kind=kind_real) :: dt0 !< dimensional time (seconds)
38  type(soca_mom6_config) :: mom6_config !< MOM6 data structure
39  real(kind_real), dimension(2) :: tocn_minmax, socn_minmax !< min, max values
40 
41 contains
42 
43  !> \name constructor/destructor
44  !! \{
45 
46  !> \copybrief soca_model_setup \see soca_model_setup
47  procedure :: setup => soca_model_setup
48 
49  !> \copybrief soca_model_delete \see soca_model_delete
50  procedure :: delete => soca_model_delete
51 
52  !> \}
53 
54  !> \name model run steps
55  !! \{
56 
57  !> \copybrief soca_model_init \see soca_model_init
58  procedure :: init => soca_model_init
59 
60  !> \copybrief soca_model_propagate \see soca_model_propagate
61  procedure :: propagate => soca_model_propagate
62 
63  !> \copybrief soca_model_finalize \see soca_model_finalize
64  procedure :: finalize => soca_model_finalize
65 
66  !> \}
67 
68 end type soca_model
69 
70 
71 ! ------------------------------------------------------------------------------
72 contains
73 ! ------------------------------------------------------------------------------
74 
75 
76 ! ------------------------------------------------------------------------------
77 !> Initialize model's data structure
78 !!
79 !! \relates soca_model_mod::soca_model
80 subroutine soca_model_setup(self, geom)
81  class(soca_model), intent(inout) :: self
82  type(soca_geom), intent(in) :: geom !< model geometry
83 
84  self%mom6_config%f_comm = geom%f_comm
85  call soca_mom6_init(self%mom6_config)
86 
87 end subroutine soca_model_setup
88 
89 
90 ! ------------------------------------------------------------------------------
91 !> Prepare MOM6 integration
92 !!
93 !! \relates soca_model_mod::soca_model
94 subroutine soca_model_init(self, flds)
95  class(soca_model), intent(inout) :: self
96  type(soca_state), intent(inout) :: flds !< initial condition
97 
98  type(soca_field), pointer :: field
99  integer :: i
100 
101  ! for each field
102  do i=1,size(flds%fields)
103  call flds%get(flds%fields(i)%name, field)
104 
105  ! Update halos
106  call mpp_update_domains(field%val, flds%geom%Domain%mpp_domain)
107 
108  ! impose bounds, and set MOM6 state
109  select case (field%name)
110  case ("tocn")
111  if ( self%tocn_minmax(1) /= real(-999., kind=8) ) &
112  where( field%val < self%tocn_minmax(1) ) field%val = self%tocn_minmax(1)
113  if ( self%tocn_minmax(2) /= real(-999., kind=8) ) &
114  where( field%val > self%tocn_minmax(2) ) field%val = self%tocn_minmax(2)
115  self%mom6_config%MOM_CSp%T = real(field%val, kind=8)
116  case ("socn")
117  if ( self%socn_minmax(1) /= real(-999., kind=8) ) &
118  where( field%val < self%socn_minmax(1) ) field%val = self%socn_minmax(1)
119  if ( self%socn_minmax(2) /= real(-999., kind=8) ) &
120  where( field%val > self%socn_minmax(2) ) field%val = self%socn_minmax(2)
121  self%mom6_config%MOM_CSp%S = real(field%val, kind=8)
122  case ("uocn")
123  self%mom6_config%MOM_CSp%u = real(field%val, kind=8)
124  case ("vocn")
125  self%mom6_config%MOM_CSp%v = real(field%val, kind=8)
126  end select
127 
128  ! update forcing
129  select case(field%name)
130  case ("sw")
131  field%val(:,:,1) = - real(self%mom6_config%fluxes%sw, kind=kind_real)
132  case ("lw")
133  field%val(:,:,1) = - real(self%mom6_config%fluxes%lw, kind=kind_real)
134  case ("lhf")
135  field%val(:,:,1) = - real(self%mom6_config%fluxes%latent, kind=kind_real)
136  case ("shf")
137  field%val(:,:,1) = - real(self%mom6_config%fluxes%sens, kind=kind_real)
138  case ("us")
139  field%val(:,:,1) = real(self%mom6_config%fluxes%ustar, kind=kind_real)
140  end select
141  end do
142 end subroutine soca_model_init
143 
144 
145 ! ------------------------------------------------------------------------------
146 !> Advance MOM6 one baroclinic time step
147 !!
148 !! \relates soca_model_mod::soca_model
149 subroutine soca_model_propagate(self, flds, fldsdate)
150  class(soca_model), intent(inout) :: self
151  type(soca_state), intent(inout) :: flds
152  type(datetime), intent(in) :: fldsdate
153 
154  type(soca_field), pointer :: field
155  type(time_type) :: ocean_time ! The ocean model's clock.
156  integer :: year, month, day, hour, minute, second, i
157  character(len=20) :: strdate
158 
159  ! Set ocean clock
160  call datetime_to_string(fldsdate, strdate)
161  call soca_str2int(strdate(1:4), year)
162  call soca_str2int(strdate(6:7), month)
163  call soca_str2int(strdate(9:10), day)
164  call soca_str2int(strdate(12:13), hour)
165  call soca_str2int(strdate(15:16), minute)
166  call soca_str2int(strdate(18:19), second)
167  self%mom6_config%Time = set_date(year, month, day, hour, minute, second)
168  ocean_time = self%mom6_config%Time
169 
170  if (self%advance_mom6==1) then
171  ! Set the forcing for the next steps.
172  call fms_io_init()
173  call set_forcing(self%mom6_config%sfc_state,&
174  self%mom6_config%forces,&
175  self%mom6_config%fluxes,&
176  self%mom6_config%Time,&
177  self%mom6_config%Time_step_ocean,&
178  self%mom6_config%grid, &
179  self%mom6_config%scaling, &
180  self%mom6_config%surface_forcing_CSp)
181  call fms_io_exit()
182 
183  ! Advance MOM in a single step call (advance dyna and thermo)
184  call step_mom(self%mom6_config%forces, &
185  self%mom6_config%fluxes, &
186  self%mom6_config%sfc_state, &
187  self%mom6_config%Time, &
188  real(self%mom6_config%dt_forcing, kind=8), &
189  self%mom6_config%MOM_CSp,&
190  start_cycle=.false.,&
191  cycle_length=self%mom6_config%MOM_CSp%dt)
192  end if
193 
194  ! Update ocean clock
195  ocean_time = ocean_time + real_to_time(self%mom6_config%MOM_CSp%dt)
196  self%mom6_config%Time = ocean_time
197 
198  ! Update soca fields
199  do i=1,size(flds%fields)
200  field => flds%fields(i)
201  select case(field%name)
202  case ("tocn")
203  field%val = real(self%mom6_config%MOM_CSp%T, kind=kind_real)
204  case ("socn")
205  field%val = real(self%mom6_config%MOM_CSp%S, kind=kind_real)
206  case ("hocn")
207  field%val = real(self%mom6_config%MOM_CSp%h, kind=kind_real)
208  case ("ssh")
209  field%val(:,:,1) = real(self%mom6_config%MOM_CSp%ave_ssh_ibc, kind=kind_real)
210  case ("uocn")
211  field%val = real(self%mom6_config%MOM_CSp%u, kind=kind_real)
212  case ("vocn")
213  field%val = real(self%mom6_config%MOM_CSp%v, kind=kind_real)
214  case ("sw")
215  field%val(:,:,1) = - real(self%mom6_config%fluxes%sw, kind=kind_real)
216  case ("lw")
217  field%val(:,:,1) = - real(self%mom6_config%fluxes%lw, kind=kind_real)
218  case ("lhf")
219  field%val(:,:,1) = - real(self%mom6_config%fluxes%latent, kind=kind_real)
220  case ("shf")
221  field%val(:,:,1) = - real(self%mom6_config%fluxes%sens, kind=kind_real)
222  case ("us")
223  field%val(:,:,1) = real(self%mom6_config%fluxes%ustar, kind=kind_real)
224  end select
225  end do
226 end subroutine soca_model_propagate
227 
228 
229 ! ------------------------------------------------------------------------------
230 !> Finalize MOM6 integration: Update mom6's state and checkpoint
231 !!
232 !! \relates soca_model_mod::soca_model
233 subroutine soca_model_finalize(self, flds)
234  class(soca_model), intent(inout) :: self
235  type(soca_state), intent(inout) :: flds
236 
237  type(soca_field), pointer :: field
238  integer :: i
239 
240  ! for each field
241  do i=1,size(flds%fields)
242  field => flds%fields(i)
243 
244  ! update halos
245  call mpp_update_domains(field%val, flds%geom%Domain%mpp_domain)
246 
247  ! impose bounds and update MOM6
248  select case(field%name)
249  case ("tocn")
250  if ( self%tocn_minmax(1) /= real(-999., kind=8) ) &
251  where( field%val < self%tocn_minmax(1) ) field%val = self%tocn_minmax(1)
252  if ( self%tocn_minmax(2) /= real(-999., kind=8) ) &
253  where( field%val > self%tocn_minmax(2) ) field%val = self%tocn_minmax(2)
254  self%mom6_config%MOM_CSp%T = real(field%val, kind=8)
255  case ("socn")
256  if ( self%socn_minmax(1) /= real(-999., kind=8) ) &
257  where( field%val < self%socn_minmax(1) ) field%val = self%socn_minmax(1)
258  if ( self%socn_minmax(2) /= real(-999., kind=8) ) &
259  where( field%val > self%socn_minmax(2) ) field%val = self%socn_minmax(2)
260  self%mom6_config%MOM_CSp%S = real(field%val, kind=8)
261  case ("uocn")
262  self%mom6_config%MOM_CSp%u = real(field%val, kind=8)
263  case ("vocn")
264  self%mom6_config%MOM_CSp%v = real(field%val, kind=8)
265  end select
266  end do
267 
268  ! Save MOM restarts with updated SOCA fields
269  call save_restart(self%mom6_config%dirs%restart_output_dir, &
270  self%mom6_config%Time, &
271  self%mom6_config%grid, &
272  self%mom6_config%restart_CSp, &
273  gv=self%mom6_config%GV)
274 
275 end subroutine soca_model_finalize
276 
277 
278 ! ------------------------------------------------------------------------------
279 !> Release memory
280 !!
281 !! \relates soca_model_mod::soca_model
282 subroutine soca_model_delete(self)
283  class(soca_model), intent(inout) :: self
284 
285  call soca_mom6_end(self%mom6_config)
286 
287 end subroutine soca_model_delete
288 
289 end module soca_model_mod
Handle fields for the model.
Geometry module.
Structure holding configuration variables for the model.
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
State fields.
various utility functions
Definition: soca_utils.F90:7
subroutine, public soca_str2int(str, int)
Definition: soca_utils.F90:179
Holds all data and metadata related to a single field variable.
Geometry data structure.
Fortran derived type to hold configuration data for the model.
Data structure neccessary to initialize/run mom6.
Definition: soca_mom6.F90:57