ROMS
Loading...
Searching...
No Matches
split_i4dvar_roms.h
Go to the documentation of this file.
1 MODULE roms_kernel_mod
2!
3!git $Id$
4!================================================== Hernan G. Arango ===
5! Copyright (c) 2002-2025 The ROMS Group Andrew M. Moore !
6! Licensed under a MIT/X style license !
7! See License_ROMS.md !
8!=======================================================================
9! !
10! ROMS Strong Constraint Split 4-Dimensional Variational Data !
11! Assimilation Driver, Incremental Approach (I4D-Var) !
12! !
13! This driver is used for the primal formulation (model space) strong !
14! constraint, incremental 4D-Var where the only errors considered are !
15! those for the observations. The model is assumed to be perfect. !
16! !
17! The i4D-Var algorithm is split into multiple executables to !
18! facilitate various configurations: !
19! !
20! (1) Executable A computes ROMS nonlinear trajectory used to !
21! linearize the tangent linear and adjoint models used in !
22! the iterations of the inner loop for the minimization of !
23! the cost function. It allows the nonlinear trajectory to !
24! be part of a coupling system and or include nested grids. !
25! It calls either the I4D-Var "background" or "analysis" !
26! routines. !
27! !
28! (2) Executable B calls either I4D-Var "increment" or !
29! "posterior_analysis". The I4D-Var increment is obtained !
30! by minimizing the cost function over Ninner loops. It is !
31! possible to use a coarser grid resolution in the inner !
32! loop. If so, the finer background trajectory needs to !
33! be interpolated into the coarser grid. Then, at the end !
34! of inner loops, the coarse grid increment needs to be !
35! interpolated to the finer grid. The increment phase !
36! may be run at a lower precision. !
37! !
38! The routines in this driver control the initialization, time- !
39! stepping, and finalization of ROMS model following ESMF/NUOPC !
40! conventions: !
41! !
42! ROMS_initialize !
43! ROMS_run !
44! ROMS_finalize !
45! !
46! References: !
47! !
48! Moore, A.M., H.G. Arango, G. Broquet, B.S. Powell, A.T. Weaver, !
49! and J. Zavala-Garay, 2011: The Regional Ocean Modeling System !
50! (ROMS) 4-dimensional variational data assimilations systems, !
51! Part I - System overview and formulation, Prog. Oceanogr., 91, !
52! 34-49, doi:10.1016/j.pocean.2011.05.004. !
53! !
54! Moore, A.M., H.G. Arango, G. Broquet, C. Edward, M. Veneziani, !
55! B. Powell, D. Foley, J.D. Doyle, D. Costa, and P. Robinson, !
56! 2011: The Regional Ocean Modeling System (ROMS) 4-dimensional !
57! variational data assimilations systems, Part II - Performance !
58! and application to the California Current System, Prog. !
59! Oceanogr., 91, 50-73, doi:10.1016/j.pocean.2011.05.003. !
60! !
61!=======================================================================
62!
63 USE mod_param
64 USE mod_parallel
65 USE mod_arrays
66 USE mod_fourdvar
67 USE mod_iounits
68 USE mod_ncparam
69 USE mod_scalars
70 USE mod_stepping
71!
72 USE i4dvar_mod
73!
75 USE def_dai_mod, ONLY : def_dai
76 USE inp_par_mod, ONLY : inp_par
77#ifdef MCT_LIB
78# ifdef ATM_COUPLING
79 USE mct_coupler_mod, ONLY : initialize_ocn2atm_coupling
80# endif
81# ifdef WAV_COUPLING
82 USE mct_coupler_mod, ONLY : initialize_ocn2wav_coupling
83# endif
84#endif
86 USE stdinp_mod, ONLY : getpar_i, getpar_s
89 USE wrt_dai_mod, ONLY : wrt_dai
90 USE wrt_rst_mod, ONLY : wrt_rst
91!
92 implicit none
93!
94 PUBLIC :: roms_initialize
95 PUBLIC :: roms_run
96 PUBLIC :: roms_finalize
97!
98 CONTAINS
99!
100 SUBROUTINE roms_initialize (first, mpiCOMM)
101!
102!=======================================================================
103! !
104! This routine allocates and initializes ROMS state variables and !
105! and internal parameters. It reads standard input parameters. !
106! !
107!=======================================================================
108!
109! Imported variable declarations.
110!
111 logical, intent(inout) :: first
112
113 integer, intent(in), optional :: mpiCOMM
114!
115! Local variable declarations.
116!
117 logical :: allocate_vars = .true.
118!
119 integer :: my_outer
120
121#ifdef DISTRIBUTE
122 integer :: MyError, MySize
123#endif
124 integer :: chunk_size, ng, thread
125#ifdef _OPENMP
126 integer :: my_threadnum
127#endif
128!
129 character (len=*), parameter :: MyFile = &
130 & __FILE__//", ROMS_initialize"
131
132#ifdef DISTRIBUTE
133!
134!-----------------------------------------------------------------------
135! Set distribute-memory (mpi) world communictor.
136!-----------------------------------------------------------------------
137!
138 IF (PRESENT(mpicomm)) THEN
139 ocn_comm_world=mpicomm
140 ELSE
141 ocn_comm_world=mpi_comm_world
142 END IF
143 CALL mpi_comm_rank (ocn_comm_world, myrank, myerror)
144 CALL mpi_comm_size (ocn_comm_world, mysize, myerror)
145#endif
146!
147!-----------------------------------------------------------------------
148! On first pass, initialize model parameters a variables for all
149! nested/composed grids. Notice that the logical switch "first"
150! is used to allow multiple calls to this routine during ensemble
151! configurations.
152!-----------------------------------------------------------------------
153!
154 IF (first) THEN
155 first=.false.
156!
157! Initialize parallel control switches. These scalars switches are
158! independent from standard input parameters.
159!
161!
162! Set the ROMS standard output unit to write verbose execution info.
163! Notice that the default standard out unit in Fortran is 6.
164!
165! In some applications like coupling or disjointed mpi-communications,
166! it is advantageous to write standard output to a specific filename
167! instead of the default Fortran standard output unit 6. If that is
168! the case, it opens such formatted file for writing.
169!
170 IF (set_stdoutunit) THEN
172 set_stdoutunit=.false.
173 END IF
174!
175! Get 4D-Var phase from APARNAM input script file.
176!
177 CALL getpar_s (master, aparnam, 'APARNAM')
178 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
179!
180 CALL getpar_s (master, phase4dvar, 'Phase4DVAR', &
181 & inpname = aparnam)
182 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
183!
184 CALL getpar_i (master, my_outer, 'OuterLoop', &
185 & inpname = aparnam)
186 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
187!
188! Determine ROMS standard output append switch. It is only relevant if
189! "ROMS_STDINP" is activated. The standard output is created in the
190! "background" phase and open to append in the other phases. Set
191! switch so the "stiffness" routine is only called in the "background"
192! phase.
193!
194 IF (index(trim(uppercase(phase4dvar)),'BACKG').ne.0) THEN
195 lappend=.false.
196 lstiffness=.true.
197 ELSE
198 lappend=.true.
199 lstiffness=.false.
200 END IF
201!
202! Read in model tunable parameters from standard input. Allocate and
203! initialize variables in several modules after the number of nested
204! grids and dimension parameters are known.
205!
206 CALL inp_par (inlm)
207 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
208!
209! Initialize counters. The 'Nrun' counter will be recomputed in the
210! RBL4D-Var phases to process the obervation operator correctly.
211!
212 nrun=1 ! run counter
213 erstr=1 ! ensemble start counter
214 erend=nouter ! ensemble end counter
215!
216! Set domain decomposition tile partition range. This range is
217! computed only once since the "first_tile" and "last_tile" values
218! are private for each parallel thread/node.
219!
220#if defined _OPENMP
221 mythread=my_threadnum()
222#elif defined DISTRIBUTE
224#else
225 mythread=0
226#endif
227 DO ng=1,ngrids
228 chunk_size=(ntilex(ng)*ntilee(ng)+numthreads-1)/numthreads
229 first_tile(ng)=mythread*chunk_size
230 last_tile(ng)=first_tile(ng)+chunk_size-1
231 END DO
232!
233! Initialize internal wall clocks. Notice that the timings does not
234! includes processing standard input because several parameters are
235! needed to allocate clock variables.
236!
237 IF (master) THEN
238 WRITE (stdout,10)
239 10 FORMAT (/,' Process Information:',/)
240 END IF
241!
242 DO ng=1,ngrids
243 DO thread=thread_range
244 CALL wclock_on (ng, inlm, 0, __line__, myfile)
245 END DO
246 END DO
247!
248! Allocate and initialize modules variables.
249!
250 CALL roms_allocate_arrays (allocate_vars)
252 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
253
254 END IF
255
256#if defined MCT_LIB && (defined ATM_COUPLING || defined WAV_COUPLING)
257!
258!-----------------------------------------------------------------------
259! Initialize coupling streams between model(s).
260!-----------------------------------------------------------------------
261!
262 DO ng=1,ngrids
263# ifdef ATM_COUPLING
264 CALL initialize_ocn2atm_coupling (ng, myrank)
265# endif
266# ifdef WAV_COUPLING
267 CALL initialize_ocn2wav_coupling (ng, myrank)
268# endif
269 END DO
270#endif
271!
272!-----------------------------------------------------------------------
273! Set application grid, metrics, and associated variables. Then,
274! proccess background prior error covariance standard deviations
275! and normalization coefficients.
276#if defined MODEL_COUPLING && defined ESMF_LIB
277! In ESM couppling applications that use generic methods for
278! 'initialize', 'run', and 'finalize', the initialization of the
279! nonlinear model kernel is separated from the 'background' and
280! 'analysis' 4D-Var phases.
281#endif
282!-----------------------------------------------------------------------
283!
284 lgetstd=.false.
285 lgetnrm=.false.
286
287 SELECT CASE (uppercase(phase4dvar(1:6)))
288 CASE ('BACKGR')
289 lgetstd=.true.
290
291#if defined MODEL_COUPLING && defined ESMF_LIB
292 my_outer=outerloop
293 outer=0
294 inner=0
295
296 lold(1:ngrids)=1
297 lnew(1:ngrids)=2
298
299 CALL background_initialize (my_outer)
300 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
301#endif
302 CASE ('POST_A')
303 lgetstd=.true.
304
305#if defined MODEL_COUPLING && defined ESMF_LIB
306 my_outer=outerloop
307 outer=0
308 inner=0
309
310 lold(1:ngrids)=1
311 lnew(1:ngrids)=2
312
314 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
315#endif
316 CASE ('ANALYS', 'INCREM')
317 lgetstd=.true.
318 lgetnrm=.true.
319 END SELECT
320!
321 DO ng=1,ngrids
322#ifdef STD_MODEL
323 lwrtstd(ng)=.true.
324 IF (index(trim(uppercase(phase4dvar)),'BACKG').ne.0) THEN
325 ldefstd(ng)=.true.
326 lreadstd(ng)=.false.
327 ELSE
328 ldefstd(ng)=.false.
329 lreadstd(ng)=.true.
330 END IF
331#else
332 lreadstd(ng)=.true.
333#endif
334 CALL prior_error (ng)
335 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
336 setgridconfig(ng)=.false.
337 END DO
338!
339 RETURN
340 END SUBROUTINE roms_initialize
341!
342 SUBROUTINE roms_run (RunInterval)
343!
344!=======================================================================
345! !
346! This routine runs the incremental, strong constraint I4D-Var data !
347! assimilation algorithm. It time-steps ROMS nonlinear, tangent !
348! linear, and adjoint kernels. !
349! !
350! On Input: !
351! !
352! RunInterval Execution time stepping window (seconds) !
353! !
354!=======================================================================
355!
356! Imported variable declarations
357!
358 real(dp), intent(in) :: RunInterval
359!
360! Local variable declarations.
361!
362 integer :: my_outer, ng
363!
364 character (len=*), parameter :: MyFile = &
365 & __FILE__//", ROMS_run"
366!
367!=======================================================================
368! Run I4D-Var algorithm (primal formulation).
369!=======================================================================
370!
371! Initialize relevant parameters.
372!
373 DO ng=1,ngrids
374#if defined ADJUST_BOUNDARY || defined ADJUST_STFLUX || \
375 defined adjust_wstress
376 lfinp(ng)=1 ! forcing index for input
377 lfout(ng)=1 ! forcing index for output history files
378#endif
379#ifdef ADJUST_BOUNDARY
380 lbinp(ng)=1 ! boundary index for input
381 lbout(ng)=1 ! boundary index for output history files
382#endif
383 lold(ng)=1 ! old minimization time index
384 lnew(ng)=2 ! new minimization time index
385 END DO
386!
387 ldone=.false. ! 4D-Var cycle finish switch
388!
389! Select I4D-Var phase to execute.
390!
391 SELECT CASE (uppercase(phase4dvar(1:6)))
392!
393! Compute nonlinear background state trajectory, Xb(t)|n-1. Interpolate
394! the background at the observation locations, and compute the quality
395! control accept/reject flag, ObsScale. The background state is used
396! to linearize the tangent linear and adjoint models during the
397! minimization.
398!
399 CASE ('BACKGR')
400
401 my_outer=outerloop
403 inner=0
404
405 CALL background (my_outer, runinterval)
406 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
407!
408! Compute 4D-Var data assimilation increment, dXa, by iterating over
409! the inner loops, and minimizing the cost function.
410!
411 CASE ('INCREM')
412
413 my_outer=outerloop
415 inner=0
416
417 CALL increment (my_outer, runinterval)
418 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
419!
420! Compute 4D-Var data assimilation analysis, Xa = Xb + dXa. Set
421! nonlinear model initial conditions for next outer loop.
422!
423 CASE ('ANALYS')
424
425 my_outer=outerloop
428
429 CALL analysis (my_outer, runinterval)
430 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
431!
432! Initialize the nonlinear model with the estimated 4D-Var state and
433! interpolate the solution at observation locations for posterior
434! analysis.
435!
436 CASE ('POST_A')
437
438 CALL posterior_analysis (runinterval)
439 ldone=.true.
440 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
441!
442! Issue an error if incorrect 4D-Var phase.
443!
444 CASE DEFAULT
445
446 IF (master) THEN
447 WRITE (stdout,10) trim(phase4dvar)
448 10 FORMAT (' ROMS_run - illegal 4D-Var phase: ''',a,'''')
449 END IF
450 exit_flag=5
451 RETURN
452
453 END SELECT
454!
455 RETURN
456 END SUBROUTINE roms_run
457!
458 SUBROUTINE roms_finalize
459!
460!=======================================================================
461! !
462! This routine terminates ROMS I4D-Var execution. !
463! !
464!=======================================================================
465!
466! Local variable declarations.
467!
468 integer :: Fcount, ng, thread
469!
470 character (len=*), parameter :: MyFile = &
471 & __FILE__//", ROMS_finalize"
472!
473!-----------------------------------------------------------------------
474! Write out 4D-Var analysis fields that used as initial conditions for
475! the next data assimilation cycle.
476!-----------------------------------------------------------------------
477!
478 IF (ldone.and.(exit_flag.eq.noerror)) THEN
479 DO ng=1,ngrids
480 ldefdai(ng)=.true.
481 CALL def_dai (ng)
482 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
483!
484#ifdef DISTRIBUTE
485 CALL wrt_dai (ng, myrank)
486#else
487 CALL wrt_dai (ng, -1)
488#endif
489 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
490 END DO
491 END IF
492!
493!-----------------------------------------------------------------------
494! Compute and report model-observation comparison statistics.
495!-----------------------------------------------------------------------
496!
497 IF (ldone.or.(exit_flag.eq.1)) THEN
498 DO ng=1,ngrids
499#ifdef DISTRIBUTE
500 CALL stats_modobs (ng, myrank)
501#else
502 CALL stats_modobs (ng, -1)
503#endif
504 END DO
505 END IF
506!
507!-----------------------------------------------------------------------
508! If blowing-up, save latest model state into RESTART NetCDF file.
509!-----------------------------------------------------------------------
510!
511! If cycling restart records, write solution into record 3.
512!
513 IF (exit_flag.eq.1) THEN
514 DO ng=1,ngrids
515 IF (lwrtrst(ng)) THEN
516 IF (master) WRITE (stdout,10)
517 10 FORMAT (/,' Blowing-up: Saving latest model state into ', &
518 & ' RESTART file',/)
519 fcount=rst(ng)%load
520 IF (lcyclerst(ng).and.(rst(ng)%Nrec(fcount).ge.2)) THEN
521 rst(ng)%Rindex=2
522 lcyclerst(ng)=.false.
523 END IF
526#ifdef DISTRIBUTE
527 CALL wrt_rst (ng, myrank)
528#else
529 CALL wrt_rst (ng, -1)
530#endif
531 END IF
532 END DO
533 END IF
534!
535!-----------------------------------------------------------------------
536! Stop model and time profiling clocks, report memory requirements,
537! and close output NetCDF files.
538!-----------------------------------------------------------------------
539!
540! Stop time clocks.
541!
542 IF (master) THEN
543 WRITE (stdout,20)
544 20 FORMAT (/,'Elapsed wall CPU time for each process (seconds):',/)
545 END IF
546!
547 DO ng=1,ngrids
548 DO thread=thread_range
549 CALL wclock_off (ng, inlm, 0, __line__, myfile)
550 END DO
551 END DO
552!
553! Report dynamic memory and automatic memory requirements.
554!
555 CALL memory
556!
557! Close IO files.
558!
559 DO ng=1,ngrids
560 CALL close_inp (ng, inlm)
561 END DO
562 CALL close_out
563!
564 RETURN
565 END SUBROUTINE roms_finalize
566!
567 END MODULE roms_kernel_mod
subroutine memory
Definition memory.F:3
subroutine, public close_out
Definition close_io.F:175
subroutine, public close_inp(ng, model)
Definition close_io.F:92
subroutine, public def_dai(ng)
Definition def_dai.F:52
logical lgetnrm
Definition i4dvar.F:166
subroutine, public prior_error(ng)
Definition i4dvar.F:2470
logical ldone
Definition i4dvar.F:169
subroutine, public increment(my_outer, runinterval)
Definition i4dvar.F:767
subroutine, public background_initialize(my_outer)
Definition i4dvar.F:190
logical lgetstd
Definition i4dvar.F:167
subroutine, public background(my_outer, runinterval)
Definition i4dvar.F:548
subroutine, public posterior_analysis(runinterval)
Definition i4dvar.F:2255
subroutine, public analysis(my_outer, runinterval)
Definition i4dvar.F:1702
subroutine, public posterior_analysis_initialize
Definition i4dvar.F:1985
subroutine, public inp_par(model)
Definition inp_par.F:56
subroutine, public roms_initialize_arrays
Definition mod_arrays.F:351
subroutine, public roms_allocate_arrays(allocate_vars)
Definition mod_arrays.F:114
character(len=256) aparnam
type(t_io), dimension(:), allocatable rst
integer stdout
subroutine, public initialize_parallel
integer numthreads
integer, dimension(:), allocatable first_tile
integer mythread
logical master
integer, dimension(:), allocatable last_tile
integer ocn_comm_world
integer, parameter inlm
Definition mod_param.F:662
integer, dimension(:), allocatable ntilex
Definition mod_param.F:685
integer ngrids
Definition mod_param.F:113
integer, dimension(:), allocatable ntilee
Definition mod_param.F:686
integer ninner
integer nouter
logical, dimension(:), allocatable lreadstd
logical lappend
logical, dimension(:), allocatable setgridconfig
logical lstiffness
integer blowup
integer outerloop
integer erend
integer exit_flag
integer erstr
character(len=20) phase4dvar
logical, dimension(:), allocatable lwrtrst
integer nrun
logical, dimension(:), allocatable ldefdai
integer inner
integer noerror
logical, dimension(:), allocatable lcyclerst
integer outer
integer, dimension(:), allocatable lold
integer, dimension(:), allocatable lbout
integer, dimension(:), allocatable lfinp
integer, dimension(:), allocatable lbinp
integer, dimension(:), allocatable lnew
integer, dimension(:), allocatable lfout
subroutine, public roms_finalize
Definition ad_roms.h:283
subroutine, public roms_run(runinterval)
Definition ad_roms.h:239
subroutine, public roms_initialize(first, mpicomm)
Definition ad_roms.h:52
subroutine, public stats_modobs(ng, tile)
integer function, public stdout_unit(mymaster)
Definition stdout_mod.F:48
logical, save set_stdoutunit
Definition stdout_mod.F:41
character(len(sinp)) function, public uppercase(sinp)
Definition strings.F:582
logical function, public founderror(flag, noerr, line, routine)
Definition strings.F:52
subroutine, public wrt_dai(ng, tile)
Definition wrt_dai.F:46
subroutine, public wrt_rst(ng, tile)
Definition wrt_rst.F:63
recursive subroutine wclock_off(ng, model, region, line, routine)
Definition timers.F:148
recursive subroutine wclock_on(ng, model, region, line, routine)
Definition timers.F:3