Line data Source code
1 : !=======================================================================
2 : !
3 : ! Main driver for time stepping of Icepack
4 : !
5 : ! authors Elizabeth C. Hunke, LANL
6 :
7 : module icedrv_RunMod
8 :
9 : use icedrv_kinds
10 : use icedrv_constants, only: c0, c1, nu_diag
11 : use icepack_intfc, only: icepack_warnings_flush
12 : use icepack_intfc, only: icepack_warnings_aborted
13 : use icepack_intfc, only: icepack_query_parameters
14 : use icepack_intfc, only: icepack_query_tracer_flags
15 : use icepack_intfc, only: icepack_query_tracer_sizes
16 : use icedrv_system, only: icedrv_system_abort, icedrv_system_flush
17 :
18 : implicit none
19 : private
20 : public :: icedrv_run, ice_step
21 :
22 : !=======================================================================
23 :
24 : contains
25 :
26 : !=======================================================================
27 : !
28 : ! This is the main driver routine for advancing CICE forward in time.
29 : !
30 : ! author Elizabeth C. Hunke, LANL
31 :
32 83 : subroutine icedrv_run
33 :
34 : use icedrv_calendar, only: istep, istep1, time, dt, stop_now, calendar
35 : use icedrv_forcing, only: get_forcing, get_wave_spec
36 : use icedrv_forcing_bgc, only: faero_default, fiso_default, get_forcing_bgc
37 : use icedrv_flux, only: init_flux_atm_ocn
38 : use icedrv_history, only: history_format, history_close
39 :
40 : logical (kind=log_kind) :: skl_bgc, z_tracers, tr_aero, tr_zaero, &
41 : wave_spec, tr_fsd, tr_iso
42 :
43 : character(len=*), parameter :: subname='(icedrv_run)'
44 :
45 : !--------------------------------------------------------------------
46 : ! timestep loop
47 : !--------------------------------------------------------------------
48 :
49 : call icepack_query_tracer_flags(tr_aero_out=tr_aero, tr_zaero_out=tr_zaero, &
50 83 : tr_fsd_out=tr_fsd, tr_iso_out=tr_iso)
51 83 : call icepack_warnings_flush(nu_diag)
52 83 : if (icepack_warnings_aborted()) call icedrv_system_abort(string=subname, &
53 0 : file=__FILE__,line= __LINE__)
54 :
55 657289 : timeLoop: do
56 :
57 657372 : call ice_step
58 :
59 657372 : istep = istep + 1 ! update time step counters
60 657372 : istep1 = istep1 + 1
61 657372 : time = time + dt ! determine the time and date
62 :
63 657372 : call calendar(time) ! at the end of the timestep
64 :
65 657372 : if (stop_now >= 1) then
66 83 : if (history_format == 'nc') call history_close()
67 83 : exit timeLoop
68 : endif
69 :
70 : call icepack_query_parameters(skl_bgc_out=skl_bgc, z_tracers_out=z_tracers,&
71 657289 : wave_spec_out=wave_spec)
72 657289 : call icepack_warnings_flush(nu_diag)
73 657289 : if (icepack_warnings_aborted()) call icedrv_system_abort(string=subname, &
74 0 : file=__FILE__,line= __LINE__)
75 :
76 657289 : if (tr_fsd .and. wave_spec) call get_wave_spec ! wave spectrum in ice
77 657289 : call get_forcing(istep1) ! get forcing from data arrays
78 :
79 : ! biogeochemistry forcing
80 657289 : if (tr_iso) call fiso_default ! default values
81 657289 : if (tr_aero .or. tr_zaero) call faero_default ! default values
82 657289 : if (skl_bgc .or. z_tracers) call get_forcing_bgc ! biogeochemistry
83 :
84 657289 : call init_flux_atm_ocn ! initialize atmosphere, ocean fluxes
85 :
86 657289 : call icedrv_system_flush(nu_diag)
87 :
88 : enddo timeLoop
89 :
90 83 : end subroutine icedrv_run
91 :
92 : !=======================================================================
93 : !
94 : ! Calls drivers for physics components, some initialization, and output
95 : !
96 : ! author Elizabeth C. Hunke, LANL
97 :
98 1972116 : subroutine ice_step
99 :
100 : use icedrv_calendar, only: dt, dt_dyn, ndtd, diagfreq, write_restart, istep
101 : use icedrv_diagnostics, only: runtime_diags, init_mass_diags
102 : ! use icedrv_diagnostics, only: icedrv_diagnostics_debug
103 : use icedrv_diagnostics_bgc, only: hbrine_diags, bgc_diags
104 : use icedrv_flux, only: init_history_therm, init_history_bgc, &
105 : daidtt, daidtd, dvidtt, dvidtd, dagedtt, dagedtd, init_history_dyn
106 : use icedrv_history, only: history_format, history_write
107 : use icedrv_restart, only: dumpfile, final_restart
108 : use icedrv_restart_bgc, only: write_restart_bgc
109 : use icedrv_step, only: prep_radiation, step_therm1, step_therm2, &
110 : update_state, step_dyn_ridge, step_snow, step_radiation, &
111 : biogeochemistry, step_dyn_wave, step_lateral_flux_scm
112 :
113 : integer (kind=int_kind) :: &
114 : k ! dynamics supercycling index
115 :
116 : logical (kind=log_kind) :: &
117 : calc_Tsfc, skl_bgc, z_tracers, tr_brine, & ! from icepack
118 : tr_fsd, wave_spec, tr_snow
119 :
120 : real (kind=dbl_kind) :: &
121 : offset ! d(age)/dt time offset
122 :
123 : character(len=*), parameter :: subname='(ice_step)'
124 :
125 : ! call icedrv_diagnostics_debug ('beginning time step')
126 :
127 : !-----------------------------------------------------------------
128 : ! query Icepack values
129 : !-----------------------------------------------------------------
130 :
131 657372 : call icepack_query_parameters(skl_bgc_out=skl_bgc, z_tracers_out=z_tracers)
132 : call icepack_query_parameters(calc_Tsfc_out=calc_Tsfc, &
133 657372 : wave_spec_out=wave_spec)
134 : call icepack_query_tracer_flags(tr_brine_out=tr_brine,tr_fsd_out=tr_fsd, &
135 657372 : tr_snow_out=tr_snow)
136 657372 : call icepack_warnings_flush(nu_diag)
137 657372 : if (icepack_warnings_aborted()) call icedrv_system_abort(string=subname, &
138 0 : file=__FILE__,line= __LINE__)
139 :
140 : !-----------------------------------------------------------------
141 : ! initialize diagnostics
142 : !-----------------------------------------------------------------
143 :
144 657372 : call init_mass_diags ! diagnostics per timestep
145 657372 : call init_history_therm
146 657372 : call init_history_bgc
147 :
148 : !-----------------------------------------------------------------
149 : ! Scale radiation fields
150 : !-----------------------------------------------------------------
151 :
152 657372 : if (calc_Tsfc) call prep_radiation ()
153 :
154 : ! call icedrv_diagnostics_debug ('post prep_radiation')
155 :
156 : !-----------------------------------------------------------------
157 : ! thermodynamics and biogeochemistry
158 : !-----------------------------------------------------------------
159 :
160 657372 : call step_therm1 (dt) ! vertical thermodynamics
161 657372 : call biogeochemistry (dt) ! biogeochemistry
162 657372 : call step_therm2 (dt) ! ice thickness distribution thermo
163 :
164 : ! clean up, update tendency diagnostics
165 657372 : offset = dt
166 657372 : call update_state (dt, daidtt, dvidtt, dagedtt, offset)
167 :
168 : ! call icedrv_diagnostics_debug ('post thermo')
169 :
170 : !-----------------------------------------------------------------
171 : ! dynamics, transport, ridging
172 : !-----------------------------------------------------------------
173 :
174 657372 : call init_history_dyn
175 :
176 : ! wave fracture of the floe size distribution
177 : ! note this is called outside of the dynamics subcycling loop
178 657372 : if (tr_fsd .and. wave_spec) call step_dyn_wave(dt)
179 :
180 1347636 : do k = 1, ndtd
181 :
182 : ! horizontal advection of ice or open water into the single column
183 690264 : call step_lateral_flux_scm(dt_dyn)
184 :
185 : ! ridging
186 690264 : call step_dyn_ridge (dt_dyn, ndtd)
187 :
188 : ! clean up, update tendency diagnostics
189 690264 : offset = c0
190 1347636 : call update_state (dt_dyn, daidtd, dvidtd, dagedtd, offset)
191 :
192 : enddo
193 :
194 : ! call icedrv_diagnostics_debug ('post dynamics')
195 :
196 : !-----------------------------------------------------------------
197 : ! snow redistribution and metamorphosis
198 : !-----------------------------------------------------------------
199 :
200 657372 : if (tr_snow) then
201 84816 : call step_snow (dt)
202 84816 : call update_state (dt) ! clean up
203 : endif
204 :
205 : ! call icedrv_diagnostics_debug ('post snow redistribution')
206 :
207 : !-----------------------------------------------------------------
208 : ! albedo, shortwave radiation
209 : !-----------------------------------------------------------------
210 :
211 657372 : call step_radiation (dt)
212 :
213 : !-----------------------------------------------------------------
214 : ! get ready for coupling and the next time step
215 : !-----------------------------------------------------------------
216 :
217 657372 : call coupling_prep
218 :
219 : ! call icedrv_diagnostics_debug ('post step_rad, cpl')
220 :
221 : !-----------------------------------------------------------------
222 : ! write data
223 : !-----------------------------------------------------------------
224 :
225 657372 : if (mod(istep,diagfreq) == 0) then
226 84084 : call runtime_diags(dt) ! log file
227 84084 : if (skl_bgc .or. z_tracers) call bgc_diags
228 84084 : if (tr_brine) call hbrine_diags
229 : endif
230 :
231 657372 : if (history_format == 'nc') then
232 48264 : call history_write()
233 : endif
234 :
235 657372 : if (write_restart == 1) then
236 1231 : call dumpfile ! core variables for restarting
237 1231 : if (skl_bgc .or. z_tracers) &
238 67 : call write_restart_bgc ! biogeochemistry
239 1231 : call final_restart
240 : endif
241 :
242 657372 : end subroutine ice_step
243 :
244 : !=======================================================================
245 : !
246 : ! Prepare for coupling
247 : !
248 : ! authors: Elizabeth C. Hunke, LANL
249 :
250 1314744 : subroutine coupling_prep
251 :
252 : use icedrv_arrays_column, only: alvdfn, alidfn, alvdrn, alidrn, &
253 : albicen, albsnon, albpndn, apeffn, snowfracn
254 : use icedrv_calendar, only: dt
255 : use icedrv_domain_size, only: ncat, nx
256 : use icedrv_flux, only: alvdf, alidf, alvdr, alidr, albice, albsno, &
257 : albpnd, apeff_ai, fpond, fresh, l_mpond_fresh, &
258 : alvdf_ai, alidf_ai, alvdr_ai, alidr_ai, fhocn_ai, &
259 : fresh_ai, fsalt_ai, fsalt, &
260 : fswthru_ai, fhocn, fswthru, scale_factor, snowfrac, &
261 : swvdr, swidr, swvdf, swidf, &
262 : frzmlt_init, frzmlt, &
263 : flux_bio, flux_bio_ai
264 : use icedrv_forcing, only: oceanmixed_ice
265 : use icedrv_state, only: aicen
266 : use icedrv_step, only: ocean_mixed_layer
267 :
268 : ! local variables
269 :
270 : integer (kind=int_kind) :: &
271 : n , & ! thickness category index
272 : i , & ! horizontal index
273 : k , & ! tracer index
274 : nbtrcr
275 :
276 : real (kind=dbl_kind) :: &
277 : netsw, & ! flag for shortwave radiation presence
278 : rhofresh, & !
279 : puny !
280 :
281 : character(len=*), parameter :: subname='(coupling_prep)'
282 :
283 : !-----------------------------------------------------------------
284 : ! Save current value of frzmlt for diagnostics.
285 : ! Update mixed layer with heat and radiation from ice.
286 : !-----------------------------------------------------------------
287 :
288 657372 : call icepack_query_parameters(puny_out=puny, rhofresh_out=rhofresh)
289 657372 : call icepack_query_tracer_sizes(nbtrcr_out=nbtrcr)
290 657372 : call icepack_warnings_flush(nu_diag)
291 657372 : if (icepack_warnings_aborted()) call icedrv_system_abort(string=subname, &
292 0 : file=__FILE__,line= __LINE__)
293 :
294 3286860 : do i = 1, nx
295 3286860 : frzmlt_init (i) = frzmlt(i)
296 : enddo
297 :
298 657372 : if (oceanmixed_ice) &
299 657372 : call ocean_mixed_layer (dt) ! ocean surface fluxes and sst
300 :
301 : !-----------------------------------------------------------------
302 : ! Aggregate albedos
303 : !-----------------------------------------------------------------
304 :
305 3286860 : do i = 1, nx
306 2629488 : alvdf(i) = c0
307 2629488 : alidf(i) = c0
308 2629488 : alvdr(i) = c0
309 2629488 : alidr(i) = c0
310 :
311 2629488 : albice(i) = c0
312 2629488 : albsno(i) = c0
313 2629488 : albpnd(i) = c0
314 2629488 : apeff_ai(i) = c0
315 3286860 : snowfrac(i) = c0
316 : enddo
317 3847704 : do n = 1, ncat
318 16609032 : do i = 1, nx
319 15951660 : if (aicen(i,n) > puny) then
320 :
321 8778375 : alvdf(i) = alvdf(i) + alvdfn(i,n)*aicen(i,n)
322 8778375 : alidf(i) = alidf(i) + alidfn(i,n)*aicen(i,n)
323 8778375 : alvdr(i) = alvdr(i) + alvdrn(i,n)*aicen(i,n)
324 8778375 : alidr(i) = alidr(i) + alidrn(i,n)*aicen(i,n)
325 :
326 8778375 : netsw = swvdr(i) + swidr(i) + swvdf(i) + swidf(i)
327 8778375 : if (netsw > puny) then ! sun above horizon
328 6970415 : albice(i) = albice(i) + albicen(i,n)*aicen(i,n)
329 6970415 : albsno(i) = albsno(i) + albsnon(i,n)*aicen(i,n)
330 6970415 : albpnd(i) = albpnd(i) + albpndn(i,n)*aicen(i,n)
331 : endif
332 :
333 8778375 : apeff_ai(i) = apeff_ai(i) + apeffn(i,n)*aicen(i,n) ! for history
334 8778375 : snowfrac(i) = snowfrac(i) + snowfracn(i,n)*aicen(i,n) ! for history
335 :
336 : endif ! aicen > puny
337 : enddo
338 : enddo
339 :
340 3286860 : do i = 1, nx
341 :
342 : !-----------------------------------------------------------------
343 : ! reduce fresh by fpond for coupling
344 : !-----------------------------------------------------------------
345 :
346 2629488 : if (l_mpond_fresh) then
347 96528 : fpond(i) = fpond(i) * rhofresh/dt
348 96528 : fresh(i) = fresh(i) - fpond(i)
349 : endif
350 :
351 : !----------------------------------------------------------------
352 : ! Store grid box mean albedos and fluxes before scaling by aice
353 : !----------------------------------------------------------------
354 :
355 2629488 : alvdf_ai (i) = alvdf (i)
356 2629488 : alidf_ai (i) = alidf (i)
357 2629488 : alvdr_ai (i) = alvdr (i)
358 2629488 : alidr_ai (i) = alidr (i)
359 2629488 : fresh_ai (i) = fresh (i)
360 2629488 : fsalt_ai (i) = fsalt (i)
361 2629488 : fhocn_ai (i) = fhocn (i)
362 2629488 : fswthru_ai(i) = fswthru(i)
363 :
364 2629488 : if (nbtrcr > 0) then
365 3698256 : do k = 1, nbtrcr
366 3698256 : flux_bio_ai (i,k) = flux_bio (i,k)
367 : enddo
368 : endif
369 :
370 : !-----------------------------------------------------------------
371 : ! Save net shortwave for scaling factor in scale_factor
372 : !-----------------------------------------------------------------
373 : scale_factor(i) = &
374 : swvdr(i)*(c1 - alvdr_ai(i)) &
375 : + swvdf(i)*(c1 - alvdf_ai(i)) &
376 : + swidr(i)*(c1 - alidr_ai(i)) &
377 3286860 : + swidf(i)*(c1 - alidf_ai(i))
378 : enddo
379 :
380 657372 : end subroutine coupling_prep
381 :
382 : !=======================================================================
383 :
384 : end module icedrv_RunMod
385 :
386 : !=======================================================================
|