ROMS
Loading...
Searching...
No Matches
rp_initial.F File Reference
#include "cppdefs.h"
Include dependency graph for rp_initial.F:

Go to the source code of this file.

Functions/Subroutines

subroutine rp_initial (ng)
 

Function/Subroutine Documentation

◆ rp_initial()

subroutine rp_initial ( integer, intent(in) ng)

Definition at line 3 of file rp_initial.F.

4!
5!git $Id$
6!================================================== Hernan G. Arango ===
7! Copyright (c) 2002-2025 The ROMS Group !
8! Licensed under a MIT/X style license !
9! See License_ROMS.md !
10!=======================================================================
11! !
12! This routine initializes representers tangent linear model. !
13! !
14!=======================================================================
15!
16 USE mod_param
17 USE mod_parallel
18# ifdef BBL_MODEL_NOT_YET
19 USE mod_bbl
20# endif
21 USE mod_boundary
22# ifdef SOLVE3D
23 USE mod_coupling
24# endif
25# ifdef FOUR_DVAR
26 USE mod_fourdvar
27# endif
28 USE mod_grid
29 USE mod_forces
30 USE mod_iounits
31 USE mod_ncparam
32# ifdef SOLVE3D
33 USE mod_mixing
34# endif
35 USE mod_ocean
36 USE mod_scalars
37 USE mod_stepping
38!
40 USE close_io_mod, ONLY : close_inp
41 USE dateclock_mod, ONLY : time_string
42# ifdef DISTRIBUTE
43 USE distribute_mod, ONLY : mp_bcasti
44# endif
45 USE get_state_mod, ONLY : get_state
46# ifdef WET_DRY
47 USE get_wetdry_mod, ONLY : get_wetdry
48# endif
49# ifdef TLM_CHECK
51# endif
53# if defined WAV_COUPLING_NOT_YET && defined MCT_LIB
54 USE mct_coupler_mod, ONLY : ocn2wav_coupling
55# endif
56# if !(defined SEDIMENT_NOT_YET && defined SED_MORPH_NOT_YET)
57 USE rp_set_depth_mod, ONLY : rp_bath
58# endif
59# ifdef SOLVE3D
61 USE rp_omega_mod, ONLY : rp_omega
62 USE rp_rho_eos_mod, ONLY : rp_rho_eos
64 USE set_depth_mod, ONLY : set_depth
65 USE omega_mod, ONLY : omega
66 USE rho_eos_mod, ONLY : rho_eos
68# endif
69# ifdef OBSERVATIONS
71# endif
72# ifdef WEAK_CONSTRAINT
73 USE rp_def_ini_mod, ONLY : rp_def_ini
74# endif
75# ifdef MASKING
76 USE set_masks_mod, ONLY : set_masks
77# endif
78 USE stiffness_mod, ONLY : stiffness
79 USE strings_mod, ONLY : founderror
80# ifdef WET_DRY
81 USE wetdry_mod, ONLY : wetdry
82# endif
83# if defined PROPAGATOR || \
84 (defined masking && (defined read_water || defined write_water))
85 USE wpoints_mod, ONLY : wpoints
86# endif
87!
88 implicit none
89!
90! Imported variable declarations.
91!
92 integer, intent(in) :: ng
93!
94! Local variable declarations.
95!
96 logical :: update = .false.
97!
98 integer :: LBi, UBi, LBj, UBj
99 integer :: Fcount, IniRec, Tindex
100 integer :: thread, tile
101!
102 real(dp) :: my_dstart
103!
104 character (len=*), parameter :: MyFile = &
105 & __FILE__
106!
107!=======================================================================
108! Initialize model variables.
109!=======================================================================
110!
111 IF (master) THEN
112# if defined PERTURBATION
113 WRITE (stdout,10) nrun
114 10 FORMAT (/,' <<<< Ensemble/Perturbation Run: ',i5.5,' >>>>',/)
115# elif defined R4DVAR || defined R4DVAR_ANA_SENSITIVITY || \
116 defined tl_r4dvar
117 WRITE (stdout,10) outer, inner
118 10 FORMAT (/,' <<<< 4D Variational Data Assimilation, ', &
119 & 'Outer = ',i3.3, ', Inner = ',i3.3,' >>>>',/)
120# endif
121 WRITE (stdout,20) 'RP_INITIAL: Configuring and ', &
122 & 'initializing representer model ...'
123 20 FORMAT (/,1x,a,a,/)
124 END IF
125!
126!-----------------------------------------------------------------------
127! Initialize time stepping indices and counters.
128!-----------------------------------------------------------------------
129!
130 iif(ng)=1
131 indx1(ng)=1
132 next_kstp(ng)=1
133 kstp(ng)=1
134 krhs(ng)=1
135 knew(ng)=1
136 predictor_2d_step(ng)=.false.
137!
138 iic(ng)=0
139 nstp(ng)=1
140 nrhs(ng)=1
141 nnew(ng)=1
142# ifdef FLOATS_NOT_YET
143 nf(ng)=0
144 nfp1(ng)=1
145 nfm1(ng)=4
146 nfm2(ng)=3
147 nfm3(ng)=2
148# endif
149!
150 synchro_flag(ng)=.true.
151 first_time(ng)=0
152
153# ifdef GENERIC_DSTART
154!
155! Rarely, the tangent linear model is initialized from a NetCDF file,
156! so we do not know its actual initialization time. Usually, it is
157! computed from DSTART, implying that its value is correct in the ROMS
158! input script. Therefore, the user needs to check and update its value
159! to every time that ROMS is executed. Alternatively, if available, we
160! can use the initialization time from the nonlinear model, INItime.
161! This variable is assigned when computing or processing the basic
162! state trajectory needed to linearize the adjoint model.
163!
164 IF (initime(ng).lt.0.0_dp) THEN
165 my_dstart=dstart ! ROMS input script
166 ELSE
167 my_dstart=initime(ng)/86400.0_dp ! NLM IC time is known
168 END IF
169 tdays(ng)=my_dstart
170# else
171 tdays(ng)=dstart
172# endif
173 time(ng)=tdays(ng)*day2sec
174 ntstart(ng)=int((time(ng)-dstart*day2sec)/dt(ng))+1
175 ntend(ng)=ntstart(ng)+ntimes(ng)-1
176 ntfirst(ng)=ntstart(ng)
177
178 CALL time_string (time(ng), time_code(ng))
179
180 inirec=nrrec(ng)
181 tindex=1
182
183 lbi=lbound(grid(ng)%h,dim=1)
184 ubi=ubound(grid(ng)%h,dim=1)
185 lbj=lbound(grid(ng)%h,dim=2)
186 ubj=ubound(grid(ng)%h,dim=2)
187!
188! Initialize global diagnostics variables.
189!
190 avgke=0.0_dp
191 avgpe=0.0_dp
192 avgkp=0.0_dp
193 volume=0.0_dp
194
195# ifdef PROFILE
196!
197!-----------------------------------------------------------------------
198! Start time wall clocks.
199!-----------------------------------------------------------------------
200!
201 DO thread=thread_range
202 CALL wclock_on (ng, irpm, 2, __line__, myfile)
203 END DO
204# endif
205
206# ifdef WEAK_CONSTRAINT
207!
208!-----------------------------------------------------------------------
209! If weak constraint variational data assimilation, reset several IO
210! switches and variables.
211!-----------------------------------------------------------------------
212!
213! Set switch to create (TRUE) representer model initial conditions
214! NetCDF file or append (FALSE) to existing NetCDF files.
215!
216 IF (nrun.eq.erstr) THEN
217# ifdef ANA_INITIAL
218 ldefirp(ng)=.true.
219# endif
220 CALL rp_def_ini (ng)
221 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
222 END IF
223 inirec=irp(ng)%Rindex
224
225# ifdef ADJUST_BOUNDARY
226!
227! Initialize open boundary counter for storage arrays.
228!
229 obccount(ng)=0
230# endif
231# if defined ADJUST_STFLUX || defined ADJUST_WSTRESS
232!
233! Initialize surface forcing counter for storage arrays.
234!
235 sfcount(ng)=0
236# endif
237!
238! Reset representer model history time record counters. These
239! counters are reset in every iteration pass but the NetCDF is
240! created on the first iteration pass.
241!
242 lcycletlm(ng)=.false.
243 tlm(ng)%Rindex=0
244 fcount=tlm(ng)%Fcount
245 tlm(ng)%Nrec(fcount)=0
246# endif
247!
248!-----------------------------------------------------------------------
249! Set application grid, metrics, and associated variables and
250! parameters.
251!-----------------------------------------------------------------------
252!
253 IF (setgridconfig(ng)) THEN
254 CALL set_grid (ng, itlm)
255 setgridconfig(ng)=.false.
256 END IF
257!
258!-----------------------------------------------------------------------
259! Initialize horizontal mixing coefficients. If applicable, scale
260! mixing coefficients according to the grid size (smallest area).
261# ifndef ANA_SPONGE
262! Also increase their values in sponge areas using the "visc_factor"
263! and/or "diff_factor" read from input Grid NetCDF file.
264# endif
265!-----------------------------------------------------------------------
266!
267 DO tile=first_tile(ng),last_tile(ng),+1
268 CALL ini_hmixcoef (ng, tile, irpm)
269 END DO
270
271# ifdef ANA_SPONGE
272!
273!-----------------------------------------------------------------------
274! Increase horizontal mixing coefficients in sponge areas using
275! analytical functions.
276!-----------------------------------------------------------------------
277!
278 IF (lsponge(ng)) THEN
279 DO tile=first_tile(ng),last_tile(ng),+1
280 CALL ana_sponge (ng, tile, irpm)
281 END DO
282 END IF
283# endif
284!
285!=======================================================================
286! Initialize model state variables and forcing. This part is
287! executed for each ensemble/perturbation/iteration pass.
288!=======================================================================
289
290# if defined PICARD_TEST || defined WEAK_CONSTRAINT
291!
292! Clear nonlinear (background) and tangent linear state variables.
293!
294 DO tile=first_tile(ng),last_tile(ng),+1
295 CALL initialize_ocean (ng, tile, inlm)
296 CALL initialize_ocean (ng, tile, irpm)
297# ifdef SOLVE3D
298 CALL initialize_coupling (ng, tile, 0)
299 CALL initialize_mixing (ng, tile, irpm)
300# endif
301!! CALL initialize_boundary (ng, tile, iRPM)
302 CALL initialize_forces (ng, tile, iadm)
303 CALL initialize_forces (ng, tile, inlm)
304 CALL initialize_forces (ng, tile, irpm)
305 END DO
306# endif
307
308# if defined SOLVE3D && !defined INI_FILE
309!
310!-----------------------------------------------------------------------
311! If analytical initial conditions, compute initial time-evolving
312! depths with zero free-surface.
313!-----------------------------------------------------------------------
314!
315 DO tile=first_tile(ng),last_tile(ng),+1
316 CALL set_depth (ng, tile, irpm)
317 END DO
318# endif
319
320# if !(defined SEDIMENT_NOT_YET && defined SED_MORPH_NOT_YET)
321!
322!-----------------------------------------------------------------------
323! Initialize tangent linear bathymetry tl_h(i,j) to h(i,j) so some of
324! the terms are cancelled in the barotropic pressure gradient.
325!-----------------------------------------------------------------------
326!
327 DO tile=first_tile(ng),last_tile(ng),+1
328 CALL rp_bath (ng, tile)
329 END DO
330# endif
331!
332!-----------------------------------------------------------------------
333! Set primitive variables initial conditions. Use analytical
334! functions or read from an initial or restart NetCDF file.
335!-----------------------------------------------------------------------
336
337# ifdef ANA_INITIAL
338!
339 IF (nrrec(ng).eq.0) THEN
340 DO tile=first_tile(ng),last_tile(ng),+1
341 CALL ana_initial (ng, tile, irpm)
342 END DO
343 END IF
344# endif
345
346# if defined ANA_PASSIVE && defined SOLVE3D
347!
348! Analytical initial conditions for inert passive tracers
349!
350 IF (nrrec(ng).eq.0) THEN
351 DO tile=first_tile(ng),last_tile(ng),+1
352 CALL ana_passive (ng, tile, irpm)
353 END DO
354 END IF
355# endif
356
357# if defined ANA_BIOLOGY && defined SOLVE3D
358!
359! Analytical initial conditions for biology tracers.
360!
361 IF (nrrec(ng).eq.0) THEN
362 DO tile=first_tile(ng),last_tile(ng),+1
363 CALL ana_biology (ng, tile, irpm)
364 END DO
365 END IF
366# endif
367
368# if defined ANA_SEDIMENT_NOT_YET && defined SOLVE3D
369!
370! Analytical initial conditions for sediment tracers.
371!
372 IF (nrrec(ng).eq.0) THEN
373 DO tile=first_tile(ng),last_tile(ng),+1
374 CALL ana_sediment (ng, tile, irpm)
375 END DO
376 END IF
377# endif
378!
379! Read in representer model initial conditions.
380!
381# ifdef INI_FILE
382 CALL get_state (ng, irpm, 1, irp(ng), inirec, tindex)
383 time(ng)=io_time ! needed for shared-memory
384# else
385 IF (nrrec(ng).ne.0) THEN
386 CALL get_state (ng, irpm, 1, irp(ng), inirec, tindex)
387 time(ng)=io_time ! needed for shared-memory
388# ifdef DISTRIBUTE
389 CALL mp_bcasti (ng, inlm, exit_flag)
390# endif
391 END IF
392# endif
393 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
394
395# ifdef WET_DRY
396!
397!-----------------------------------------------------------------------
398! Process initial wet/dry masks.
399!-----------------------------------------------------------------------
400!
401! If restart, read in wet/dry masks.
402!
403 IF (nrrec(ng).ne.0) THEN
404# ifdef DISTRIBUTE
405 CALL get_wetdry (ng, myrank, irpm, inirec(ng))
406 CALL mp_bcasti (ng, irpm, exit_flag)
407# else
408 CALL get_wetdry (ng, -1, irpm, inirec(ng))
409# endif
410 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
411 ELSE
412 DO tile=first_tile(ng),last_tile(ng),+1
413 CALL wetdry (ng, tile, tindex(ng), .true.)
414 END DO
415 END IF
416# endif
417
418# ifdef OBSERVATIONS
419!
420!-----------------------------------------------------------------------
421! Open observations NetCDF file and initialize various variables
422! needed for processing the tangent linear state solution at
423! observation locations. Need to be done after processing initial
424! conditions since the correct initial time is needed to determine
425! the first "ObsTime" to process.
426!-----------------------------------------------------------------------
427!
428 CALL obs_initial (ng, irpm, .false.)
429 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
430# endif
431
432# if defined ANA_PERTURB && defined SANITY_CHECK
433!
434!-----------------------------------------------------------------------
435! Perturb tangent linear initial conditions with analitical
436! expressions.
437!-----------------------------------------------------------------------
438!
439 DO tile=first_tile(ng),last_tile(ng),+1
440 CALL ana_perturb (ng, tile, irpm)
441 END DO
442# endif
443
444# ifdef SOLVE3D
445!
446!-----------------------------------------------------------------------
447! Compute initial time-evolving depths.
448!-----------------------------------------------------------------------
449!
450 DO tile=first_tile(ng),last_tile(ng),+1
451 CALL set_depth (ng, tile, irpm)
452 CALL rp_set_depth (ng, tile, irpm)
453 END DO
454!
455!-----------------------------------------------------------------------
456! Compute initial horizontal mass fluxes, Hz*u/n and Hz*v/m.
457!-----------------------------------------------------------------------
458!
459 DO tile=first_tile(ng),last_tile(ng),+1
460 CALL rp_set_massflux (ng, tile, irpm)
461 CALL set_massflux (ng, tile, irpm)
462 END DO
463!
464!-----------------------------------------------------------------------
465! Compute initial representer tangent linear and basic state
466! S-coordinates vertical velocity.
467!-----------------------------------------------------------------------
468!
469 DO tile=first_tile(ng),last_tile(ng),+1
470 CALL rp_omega (ng, tile, irpm)
471 CALL omega (ng, tile, irpm)
472 END DO
473# endif
474
475#ifdef ANA_PSOURCE
476!
477!-----------------------------------------------------------------------
478! Set point Sources/Sinks position, direction, special flag, and mass
479! transport nondimensional shape profile with analytcal expressions.
480! Point sources are at U- and V-points. We need to get their positions
481! to process internal Land/Sea masking arrays during initialization.
482!-----------------------------------------------------------------------
483!
484 IF (luvsrc(ng).or.lwsrc(ng).or.any(ltracersrc(:,ng))) THEN
485 DO tile=first_tile(ng),last_tile(ng),+1
486 CALL ana_psource (ng, tile, irpm)
487 END DO
488 END IF
489#endif
490!
491!-----------------------------------------------------------------------
492! If applicable, close all input boundary, climatology, and forcing
493! NetCDF files and set associated parameters to the closed state. This
494! step is essential in iterative algorithms that run the full TLM
495! repetitively. Then, Initialize several parameters in their file
496! structure, so the appropriate input single or multi-file is selected
497! during initialization/restart.
498!-----------------------------------------------------------------------
499!
500 CALL close_inp (ng, irpm)
501 CALL check_multifile (ng, irpm)
502# ifdef DISTRIBUTE
503 CALL mp_bcasti (ng, irpm, exit_flag)
504# endif
505 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
506!
507!-----------------------------------------------------------------------
508! Read in initial forcing, climatology and assimilation data from
509! input NetCDF files. It loads the first relevant data record for
510! the time-interpolation between snapshots.
511!-----------------------------------------------------------------------
512!
513 CALL rp_get_idata (ng)
514 CALL rp_get_data (ng)
515 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
516
517# ifdef MASKING
518!
519!-----------------------------------------------------------------------
520! Set internal I/O mask arrays.
521!-----------------------------------------------------------------------
522!
523 DO tile=first_tile(ng),last_tile(ng),+1
524 CALL set_masks (ng, tile, irpm)
525 END DO
526# endif
527
528# if defined PROPAGATOR || \
529 (defined masking && (defined read_water || defined write_water ))
530!
531!-----------------------------------------------------------------------
532! Set variables associated with the processing water points and/or
533! size of packed state arrays.
534!-----------------------------------------------------------------------
535!
536 DO tile=first_tile(ng),last_tile(ng),+1
537 CALL wpoints (ng, tile, irpm)
538 END DO
539# endif
540
541# ifdef SOLVE3D
542!-----------------------------------------------------------------------
543! Compute initial representer tangent linear and basic state equation
544! of state related quantities.
545!-----------------------------------------------------------------------
546!
547 DO tile=first_tile(ng),last_tile(ng),+1
548 CALL rp_rho_eos (ng, tile, irpm)
549 CALL rho_eos (ng, tile, irpm)
550 END DO
551# endif
552
553# if defined ANA_DRAG && defined UV_DRAG_GRID
554!
555!-----------------------------------------------------------------------
556! Set analytical spatially varying bottom friction parameter.
557!-----------------------------------------------------------------------
558!
559 IF (nrun.eq.erstr) THEN
560 DO tile=first_tile(ng),last_tile(ng),+1
561 CALL ana_drag (ng, tile, irpm)
562 END DO
563 END IF
564# endif
565!
566!-----------------------------------------------------------------------
567! Compute grid stiffness.
568!-----------------------------------------------------------------------
569!
570 IF (lstiffness) THEN
571 lstiffness=.false.
572 DO tile=first_tile(ng),last_tile(ng),+1
573 CALL stiffness (ng, tile, irpm)
574 END DO
575 END IF
576
577# if defined FLOATS_NOT_YET || defined STATIONS
578!
579!-----------------------------------------------------------------------
580! If applicable, convert initial locations to fractional grid
581! coordinates.
582!-----------------------------------------------------------------------
583!
584 CALL grid_coords (ng, irpm)
585# endif
586
587# if defined WAV_COUPLING_NOT_YET && defined MCT_LIB
588!
589!-----------------------------------------------------------------------
590! Read in initial forcing from coupled wave model.
591!-----------------------------------------------------------------------
592!
593 DO tile=first_tile(ng),last_tile(ng),+1
594 CALL ocn2wav_coupling (ng, tile)
595 END DO
596# endif
597!
598!-----------------------------------------------------------------------
599! Initialize time-stepping counter and clock.
600!-----------------------------------------------------------------------
601!
602! Subsract one time unit to avoid special case due to initialization
603! in the main time-stepping routine.
604!
605 iic(ng)=ntstart(ng)-1
606 time(ng)=time(ng)-dt(ng)
607
608# ifdef PROFILE
609!
610!-----------------------------------------------------------------------
611! Turn off initiialization time wall clock.
612!-----------------------------------------------------------------------
613!
614 DO thread=thread_range
615 CALL wclock_off (ng, irpm, 2, __line__, myfile)
616 END DO
617# endif
618!
619 RETURN
subroutine check_multifile(ng, model)
subroutine grid_coords(ng, model)
Definition grid_coords.F:4
subroutine ana_sediment(ng, tile, model)
Definition ana_sediment.h:3
subroutine ana_initial(ng, tile, model)
Definition ana_initial.h:3
subroutine ana_sponge(ng, tile, model)
Definition ana_hmixcoef.h:3
subroutine ana_drag(ng, tile, model)
Definition ana_drag.h:3
subroutine ana_psource(ng, tile, model)
Definition ana_psource.h:3
subroutine ana_perturb(ng, tile, model)
Definition ana_perturb.h:3
subroutine ana_biology(ng, tile, model)
Definition ana_biology.h:3
subroutine ana_passive(ng, tile, model)
Definition ana_passive.h:3
subroutine, public close_inp(ng, model)
Definition close_io.F:92
subroutine, public time_string(mytime, date_string)
Definition dateclock.F:1272
subroutine, public get_state(ng, model, msg, s, inirec, tindex)
Definition get_state.F:90
subroutine, public get_wetdry(ng, tile, model, inirec)
Definition get_wetdry.F:45
subroutine, public tl_ini_perturb(ng, tile, linp, lout)
subroutine, public ini_hmixcoef(ng, tile, model)
subroutine, public initialize_coupling(ng, tile, model)
subroutine, public initialize_forces(ng, tile, model)
type(t_grid), dimension(:), allocatable grid
Definition mod_grid.F:365
type(t_io), dimension(:), allocatable irp
type(t_io), dimension(:), allocatable tlm
integer stdout
subroutine, public initialize_mixing(ng, tile, model)
subroutine, public initialize_ocean(ng, tile, model)
Definition mod_ocean.F:1526
integer, dimension(:), allocatable first_tile
logical master
integer, dimension(:), allocatable last_tile
integer, parameter inlm
Definition mod_param.F:662
integer, parameter irpm
Definition mod_param.F:664
integer, parameter iadm
Definition mod_param.F:665
integer, parameter itlm
Definition mod_param.F:663
logical, dimension(:), allocatable luvsrc
real(dp), parameter day2sec
integer, dimension(:), allocatable obccount
integer, dimension(:), allocatable nrrec
logical, dimension(:,:), allocatable ltracersrc
integer, dimension(:), allocatable ntimes
integer, dimension(:), allocatable iic
real(dp), dimension(:), allocatable dt
logical, dimension(:), allocatable lsponge
logical, dimension(:), allocatable setgridconfig
logical lstiffness
real(dp) avgke
real(dp) avgpe
integer, dimension(:), allocatable next_kstp
logical, dimension(:), allocatable synchro_flag
logical, dimension(:), allocatable predictor_2d_step
real(dp), dimension(:), allocatable tdays
real(dp) dstart
logical, dimension(:), allocatable lwsrc
integer, dimension(:), allocatable ntend
logical, dimension(:), allocatable lcycletlm
logical, dimension(:), allocatable ldefirp
real(dp) volume
integer, dimension(:), allocatable first_time
character(len=22), dimension(:), allocatable time_code
integer exit_flag
integer, dimension(:), allocatable indx1
integer, dimension(:), allocatable sfcount
integer erstr
real(dp) avgkp
integer, dimension(:), allocatable ntfirst
real(dp), dimension(:), allocatable time
integer, dimension(:), allocatable ntstart
integer nrun
integer inner
integer, dimension(:), allocatable iif
real(dp) io_time
real(dp), dimension(:), allocatable initime
integer noerror
integer outer
integer, dimension(:), allocatable nfm2
integer, dimension(:), allocatable kstp
integer, dimension(:), allocatable knew
integer, dimension(:), allocatable nfm1
integer, dimension(:), allocatable nrhs
integer, dimension(:), allocatable nf
integer, dimension(:), allocatable nfm3
integer, dimension(:), allocatable nnew
integer, dimension(:), allocatable nfp1
integer, dimension(:), allocatable krhs
integer, dimension(:), allocatable nstp
subroutine, public obs_initial(ng, model, backward)
Definition obs_initial.F:41
subroutine, public omega(ng, tile, model)
Definition omega.F:42
subroutine, public rho_eos(ng, tile, model)
Definition rho_eos.F:48
subroutine, public rp_def_ini(ng)
Definition rp_def_ini.F:41
subroutine, public rp_omega(ng, tile, model)
Definition rp_omega.F:35
subroutine, public rp_rho_eos(ng, tile, model)
Definition rp_rho_eos.F:48
subroutine, public rp_set_depth(ng, tile, model)
subroutine, public rp_bath(ng, tile)
subroutine, public rp_set_massflux(ng, tile, model)
subroutine, public set_depth(ng, tile, model)
Definition set_depth.F:34
subroutine, public set_masks(ng, tile, model)
Definition set_masks.F:44
subroutine, public set_massflux(ng, tile, model)
subroutine, public stiffness(ng, tile, model)
Definition stiffness.F:32
logical function, public founderror(flag, noerr, line, routine)
Definition strings.F:52
subroutine wetdry(ng, tile, tindex, linitialize)
Definition wetdry.F:22
subroutine rp_get_data(ng)
Definition rp_get_data.F:4
subroutine rp_get_idata(ng)
Definition rp_get_idata.F:4
subroutine set_grid(ng, model)
Definition set_grid.F:3
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
subroutine wpoints(ng, tile, model)
Definition wpoints.F:40

References analytical_mod::ana_biology(), analytical_mod::ana_drag(), analytical_mod::ana_initial(), analytical_mod::ana_passive(), analytical_mod::ana_perturb(), analytical_mod::ana_psource(), analytical_mod::ana_sediment(), analytical_mod::ana_sponge(), mod_scalars::avgke, mod_scalars::avgkp, mod_scalars::avgpe, check_multifile(), close_io_mod::close_inp(), mod_scalars::day2sec, mod_scalars::dstart, mod_scalars::dt, mod_scalars::erstr, mod_scalars::exit_flag, mod_parallel::first_tile, mod_scalars::first_time, strings_mod::founderror(), get_state_mod::get_state(), get_wetdry_mod::get_wetdry(), mod_grid::grid, grid_coords(), mod_param::iadm, mod_scalars::iic, mod_scalars::iif, mod_scalars::indx1, ini_hmixcoef_mod::ini_hmixcoef(), mod_coupling::initialize_coupling(), mod_forces::initialize_forces(), mod_mixing::initialize_mixing(), mod_ocean::initialize_ocean(), mod_scalars::initime, mod_param::inlm, mod_scalars::inner, mod_scalars::io_time, mod_iounits::irp, mod_param::irpm, mod_param::itlm, mod_stepping::knew, mod_stepping::krhs, mod_stepping::kstp, mod_parallel::last_tile, mod_scalars::lcycletlm, mod_scalars::ldefirp, mod_scalars::lsponge, mod_scalars::lstiffness, mod_scalars::ltracersrc, mod_scalars::luvsrc, mod_scalars::lwsrc, mod_parallel::master, mod_parallel::myrank, mod_scalars::next_kstp, mod_stepping::nf, mod_stepping::nfm1, mod_stepping::nfm2, mod_stepping::nfm3, mod_stepping::nfp1, mod_stepping::nnew, mod_scalars::noerror, mod_stepping::nrhs, mod_scalars::nrrec, mod_scalars::nrun, mod_stepping::nstp, mod_scalars::ntend, mod_scalars::ntfirst, mod_scalars::ntimes, mod_scalars::ntstart, mod_scalars::obccount, obs_initial_mod::obs_initial(), omega_mod::omega(), mod_scalars::outer, mod_scalars::predictor_2d_step, rho_eos_mod::rho_eos(), rp_set_depth_mod::rp_bath(), rp_def_ini_mod::rp_def_ini(), rp_get_data(), rp_get_idata(), rp_omega_mod::rp_omega(), rp_rho_eos_mod::rp_rho_eos(), rp_set_depth_mod::rp_set_depth(), rp_set_massflux_mod::rp_set_massflux(), set_depth_mod::set_depth(), set_grid(), set_masks_mod::set_masks(), set_massflux_mod::set_massflux(), mod_scalars::setgridconfig, mod_scalars::sfcount, mod_iounits::stdout, stiffness_mod::stiffness(), mod_scalars::synchro_flag, mod_scalars::tdays, mod_scalars::time, mod_scalars::time_code, dateclock_mod::time_string(), ini_adjust_mod::tl_ini_perturb(), mod_iounits::tlm, mod_scalars::volume, wclock_off(), wclock_on(), wetdry_mod::wetdry(), and wpoints().

Referenced by r4dvar_mod::analysis(), and r4dvar_mod::increment().

Here is the call graph for this function:
Here is the caller graph for this function: