SUBROUTINE initial ! !git $Id$ !svn $Id: initial.F 1180 2023-07-13 02:42:10Z arango $ !================================================== Hernan G. Arango === ! Copyright (c) 2002-2023 The ROMS/TOMS Group ! ! Licensed under a MIT/X style license ! ! See License_ROMS.md ! !======================================================================= ! ! ! This routine initializes all model variables. ! ! ! !======================================================================= ! USE mod_param USE mod_parallel USE mod_fourdvar USE mod_grid USE mod_iounits USE mod_ncparam USE mod_ocean USE mod_scalars USE mod_stepping ! USE analytical_mod USE close_io_mod, ONLY : close_inp USE dateclock_mod, ONLY : time_string USE def_ini_mod, ONLY : def_ini USE distribute_mod, ONLY : mp_bcasti USE get_state_mod, ONLY : get_state USE ini_hmixcoef_mod, ONLY : ini_hmixcoef USE set_depth_mod, ONLY : set_depth0, set_depth USE omega_mod, ONLY : omega USE rho_eos_mod, ONLY : rho_eos USE set_massflux_mod, ONLY : set_massflux USE obs_initial_mod, ONLY : obs_initial USE set_masks_mod, ONLY : set_masks USE stiffness_mod, ONLY : stiffness USE strings_mod, ONLY : FoundError ! implicit none ! ! Local variable declarations. ! logical :: update = .FALSE. ! integer :: Fcount integer :: ng, thread, tile integer, dimension(Ngrids) :: IniRec, Tindex ! ! character (len=*), parameter :: MyFile = & & "ROMS/Nonlinear/initial.F" ! !======================================================================= ! Initialize model variables. !======================================================================= ! !$OMP MASTER IF (Master) THEN WRITE (stdout,10) outer, inner 10 FORMAT (/,' <<<< 4D Variational Data Assimilation, ', & & 'Outer = ',i3.3, ', Inner = ',i3.3,' >>>>',/) WRITE (stdout,20) 'INITIAL: Configuring and initializing ', & & 'forward nonlinear model ...' 20 FORMAT (/,1x,a,a,/,1x,'*******') END IF !$OMP END MASTER ! !----------------------------------------------------------------------- ! Initialize time stepping indices and counters. !----------------------------------------------------------------------- ! DO ng=1,Ngrids iif(ng)=1 indx1(ng)=1 next_kstp(ng)=1 kstp(ng)=1 krhs(ng)=1 knew(ng)=1 PREDICTOR_2D_STEP(ng)=.FALSE. ! iic(ng)=0 nstp(ng)=1 nrhs(ng)=1 nnew(ng)=1 ! IniRec(ng)=nrrec(ng) Tindex(ng)=1 ! synchro_flag(ng)=.TRUE. first_time(ng)=0 tdays(ng)=dstart time(ng)=tdays(ng)*day2sec !$OMP MASTER ntstart(ng)=INT((time(ng)-dstart*day2sec)/dt(ng))+1 ntend(ng)=ntstart(ng)+ntimes(ng)-1 ntfirst(ng)=ntstart(ng) !$OMP END MASTER !$OMP BARRIER step_counter(ng)=0 END DO ! ! Initialize global diagnostics variables. ! avgke=0.0_dp avgpe=0.0_dp avgkp=0.0_dp volume=0.0_dp ! !----------------------------------------------------------------------- ! Start time wall clocks. !----------------------------------------------------------------------- ! DO ng=1,Ngrids DO thread=MyRank,MyRank CALL wclock_on (ng, iNLM, 2, 193, MyFile) END DO END DO !$OMP BARRIER ! !----------------------------------------------------------------------- ! If variational data assimilation, reset several IO switches and ! variables. !----------------------------------------------------------------------- ! ! Set initial conditions record to process. If applicable open existing ! nonlinear model initial conditions NetCDF file and, if needed, define ! new variables. Then, inquire about available variables. ! DO ng=1,Ngrids IF (LdefINI(ng)) THEN LdefINI(ng)=.FALSE. ! needed to inquire variables IDs CALL def_ini (ng) CALL mp_bcasti (ng, iNLM, exit_flag) IF (FoundError(exit_flag, NoError, 219, MyFile)) RETURN IniRec(ng)=nrrec(ng) INI(ng)%Rindex=IniRec(ng) ELSE IniRec(ng)=INI(ng)%Rindex END IF END DO ! ! Reset nonlinear history time record counters. These counters are ! reset on every iteration pass. This file is created on the first ! iteration pass. ! DO ng=1,Ngrids HIS(ng)%Rindex=0 Fcount=HIS(ng)%Fcount HIS(ng)%Nrec(Fcount)=0 END DO !$OMP BARRIER ! !----------------------------------------------------------------------- ! Set application grid, metrics, and associated variables and ! parameters. !----------------------------------------------------------------------- ! DO ng=1,Ngrids IF (SetGridConfig(ng)) THEN CALL set_grid (ng, iNLM) SetGridConfig(ng)=.FALSE. END IF END DO ! !----------------------------------------------------------------------- ! Initialize horizontal mixing coefficients. If applicable, scale ! mixing coefficients according to the grid size (smallest area). ! Also increase their values in sponge areas using the "visc_factor" ! and/or "diff_factor" read from input Grid NetCDF file. !----------------------------------------------------------------------- ! DO ng=1,Ngrids DO tile=first_tile(ng),last_tile(ng),+1 CALL ini_hmixcoef (ng, tile, iNLM) END DO !$OMP BARRIER END DO ! !======================================================================= ! Initialize model state variables and forcing. This part is ! executed for each ensemble/perturbation/iteration run. !======================================================================= ! !----------------------------------------------------------------------- ! Set primitive variables initial conditions. !----------------------------------------------------------------------- ! ! Read in initial conditions from initial NetCDF file. ! DO ng=1,Ngrids !$OMP MASTER CALL get_state (ng, iNLM, 1, INI(ng), IniRec(ng), Tindex(ng)) !$OMP END MASTER CALL mp_bcasti (ng, iNLM, exit_flag) !$OMP BARRIER IF (FoundError(exit_flag, NoError, 418, MyFile)) RETURN time(ng)=io_time ! needed for shared-memory END DO ! !----------------------------------------------------------------------- ! Open observations NetCDF file and initialize various variables ! needed for processing the nonlinear state solution at observation ! locations. Need to be done after processing initial conditions since ! the correct initial time is needed to determine the first "ObsTime" ! to process. !----------------------------------------------------------------------- ! DO ng=1,Ngrids !$OMP MASTER CALL obs_initial (ng, iNLM, .FALSE.) !$OMP END MASTER IF (FoundError(exit_flag, NoError, 486, MyFile)) RETURN END DO !$OMP BARRIER ! !----------------------------------------------------------------------- ! Compute time independent (Zt_avg1=0) anf initial time dependent ! depths and level thicknesses. !----------------------------------------------------------------------- ! DO ng=1,Ngrids DO tile=first_tile(ng),last_tile(ng),+1 CALL set_depth0 (ng, tile, iNLM) CALL set_depth (ng, tile, iNLM) END DO !$OMP BARRIER END DO ! !----------------------------------------------------------------------- ! Compute initial horizontal mass fluxes, Hz*u/n and Hz*v/m. !----------------------------------------------------------------------- ! DO ng=1,Ngrids DO tile=first_tile(ng),last_tile(ng),+1 CALL set_massflux (ng, tile, iNLM) END DO !$OMP BARRIER END DO ! !----------------------------------------------------------------------- ! Compute initial S-coordinates vertical velocity. Compute initial ! density anomaly from potential temperature and salinity via equation ! of state for seawater. Also compute other equation of state related ! quatities. !----------------------------------------------------------------------- ! DO ng=1,Ngrids DO tile=first_tile(ng),last_tile(ng),+1 CALL omega (ng, tile, iNLM) CALL rho_eos (ng, tile, iNLM) END DO !$OMP BARRIER END DO ! !----------------------------------------------------------------------- ! Read in initial forcing, climatology and assimilation data from ! input NetCDF files. It loads the first relevant data record for ! the time-interpolation between snapshots. !----------------------------------------------------------------------- ! ! If applicable, close all input boundary, climatology, and forcing ! NetCDF files and set associated parameters to the closed state. This ! step is essential in iterative algorithms that run the full TLM ! repetitively. Then, Initialize several parameters in their file ! structure, so the appropriate input single or multi-file is selected ! during initialization/restart. ! DO ng=1,Ngrids !$OMP MASTER CALL close_inp (ng, iNLM) CALL check_multifile (ng, iNLM) !$OMP END MASTER CALL mp_bcasti (ng, iNLM, exit_flag) !$OMP BARRIER IF (FoundError(exit_flag, NoError, 658, MyFile)) RETURN END DO ! ! If applicable, read in input data. ! DO ng=1,Ngrids !$OMP MASTER CALL get_idata (ng) CALL get_data (ng) !$OMP END MASTER CALL mp_bcasti (ng, iNLM, exit_flag) !$OMP BARRIER IF (FoundError(exit_flag, NoError, 672, MyFile)) RETURN END DO ! !----------------------------------------------------------------------- ! Set internal I/O mask arrays. !----------------------------------------------------------------------- ! DO ng=1,Ngrids DO tile=first_tile(ng),last_tile(ng),+1 CALL set_masks (ng, tile, iNLM) END DO !$OMP BARRIER END DO ! !----------------------------------------------------------------------- ! Read in convolved adjoint impulse forcing (first record) and its ! application time. !----------------------------------------------------------------------- ! DO ng=1,Ngrids IF (SporadicImpulse(ng)) THEN FrcRec(ng)=1 !$OMP MASTER CALL get_state (ng, 7, 7, TLF(ng), FrcRec(ng), 1) !$OMP END MASTER !$OMP BARRIER CALL mp_bcasti (ng, iTLM, exit_flag) IF (FoundError(exit_flag, NoError, 785, MyFile)) RETURN END IF END DO ! !----------------------------------------------------------------------- ! Compute grid stiffness. !----------------------------------------------------------------------- ! IF (Lstiffness) THEN Lstiffness=.FALSE. DO ng=1,Ngrids DO tile=first_tile(ng),last_tile(ng),+1 CALL stiffness (ng, tile, iNLM) END DO !$OMP BARRIER END DO END IF ! !----------------------------------------------------------------------- ! Initialize time-stepping counter and date/time string. Save NLM ! initial conditions time. !----------------------------------------------------------------------- ! DO ng=1,Ngrids INItime(ng)=time(ng) iic(ng)=ntstart(ng) CALL time_string (time(ng), time_code(ng)) END DO ! !----------------------------------------------------------------------- ! Turn off initialization time wall clock. !----------------------------------------------------------------------- ! DO ng=1,Ngrids DO thread=MyRank,MyRank CALL wclock_off (ng, iNLM, 2, 869, MyFile) END DO !$OMP BARRIER END DO ! RETURN END SUBROUTINE initial