1 | MODULE step |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE step *** |
---|
4 | !! Time-stepping : manager of the ocean, tracer and ice time stepping |
---|
5 | !! version for standalone surface scheme |
---|
6 | !!====================================================================== |
---|
7 | !! History : OPA ! 1991-03 (G. Madec) Original code |
---|
8 | !! . ! . |
---|
9 | !! . ! . |
---|
10 | !! NEMO 3.5 ! 2012-03 (S. Alderson) |
---|
11 | !!---------------------------------------------------------------------- |
---|
12 | |
---|
13 | !!---------------------------------------------------------------------- |
---|
14 | !! stp : OPA system time-stepping |
---|
15 | !!---------------------------------------------------------------------- |
---|
16 | USE oce ! ocean dynamics and tracers variables |
---|
17 | USE dom_oce ! ocean space and time domain variables |
---|
18 | USE daymod ! calendar (day routine) |
---|
19 | USE sbc_oce ! surface boundary condition: fields |
---|
20 | USE sbcmod ! surface boundary condition (sbc routine) |
---|
21 | USE sbcrnf ! surface boundary condition: runoff variables |
---|
22 | USE sbccpl ! surface boundary condition: coupled interface |
---|
23 | USE eosbn2 ! equation of state (eos_bn2 routine) |
---|
24 | USE diawri ! Standard run outputs (dia_wri routine) |
---|
25 | USE bdy_oce , ONLY: ln_bdy |
---|
26 | USE bdydta ! clem: mandatory for LIM3 |
---|
27 | USE stpctl ! time stepping control (stp_ctl routine) |
---|
28 | ! |
---|
29 | USE in_out_manager ! I/O manager |
---|
30 | USE prtctl ! Print control (prt_ctl routine) |
---|
31 | USE iom ! |
---|
32 | USE lbclnk ! |
---|
33 | USE timing ! Timing |
---|
34 | #if defined key_iomput |
---|
35 | USE xios |
---|
36 | #endif |
---|
37 | |
---|
38 | #if defined key_agrif |
---|
39 | USE agrif_oce, ONLY: lk_agrif_debug !clem |
---|
40 | #endif |
---|
41 | |
---|
42 | IMPLICIT NONE |
---|
43 | PRIVATE |
---|
44 | |
---|
45 | PUBLIC stp ! called by nemogcm.F90 |
---|
46 | |
---|
47 | !!---------------------------------------------------------------------- |
---|
48 | !! NEMO/OPA 3.3 , NEMO Consortium (2010) |
---|
49 | !! $Id$ |
---|
50 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
51 | !!---------------------------------------------------------------------- |
---|
52 | CONTAINS |
---|
53 | |
---|
54 | #if defined key_agrif |
---|
55 | RECURSIVE SUBROUTINE stp( ) |
---|
56 | INTEGER :: kstp ! ocean time-step index |
---|
57 | #else |
---|
58 | SUBROUTINE stp( kstp ) |
---|
59 | INTEGER, INTENT(in) :: kstp ! ocean time-step index |
---|
60 | #endif |
---|
61 | !!---------------------------------------------------------------------- |
---|
62 | !! *** ROUTINE stp *** |
---|
63 | !! |
---|
64 | !! ** Purpose : - Time stepping of SBC (surface boundary) |
---|
65 | !! |
---|
66 | !! ** Method : -1- Update forcings and data |
---|
67 | !! -2- Outputs and diagnostics |
---|
68 | !!---------------------------------------------------------------------- |
---|
69 | INTEGER :: indic ! error indicator if < 0 |
---|
70 | !! --------------------------------------------------------------------- |
---|
71 | |
---|
72 | #if defined key_agrif |
---|
73 | kstp = nit000 + Agrif_Nb_Step() |
---|
74 | IF ( lk_agrif_debug ) THEN |
---|
75 | IF ( Agrif_Root() .and. lwp) Write(*,*) '---' |
---|
76 | IF (lwp) Write(*,*) 'Grid Number',Agrif_Fixed(),' time step ',kstp, 'int tstep',Agrif_NbStepint() |
---|
77 | ENDIF |
---|
78 | |
---|
79 | IF ( kstp == (nit000 + 1) ) lk_agrif_fstep = .FALSE. |
---|
80 | |
---|
81 | # if defined key_iomput |
---|
82 | IF( Agrif_Nbstepint() == 0 ) CALL iom_swap( cxios_context ) |
---|
83 | # endif |
---|
84 | #endif |
---|
85 | indic = 0 ! although indic is not changed in stp_ctl |
---|
86 | ! need to keep the same interface |
---|
87 | IF( kstp == nit000 ) CALL iom_init( cxios_context ) ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS) |
---|
88 | IF( kstp /= nit000 ) CALL day( kstp ) ! Calendar (day was already called at nit000 in day_init) |
---|
89 | CALL iom_setkt( kstp - nit000 + 1, cxios_context ) ! tell iom we are at time step kstp |
---|
90 | |
---|
91 | ! ==> clem: open boundaries is mandatory for LIM3 because ice BDY is not decoupled from |
---|
92 | ! the environment of ocean BDY. Therefore bdy is called in both OPA and SAS modules. |
---|
93 | ! From SAS: ocean bdy data are wrong (but we do not care) and ice bdy data are OK. |
---|
94 | ! This is not clean and should be changed in the future. |
---|
95 | IF( ln_bdy ) CALL bdy_dta ( kstp, time_offset=+1 ) ! update dynamic & tracer data at open boundaries |
---|
96 | ! ==> |
---|
97 | CALL sbc ( kstp ) ! Sea Boundary Condition (including sea-ice) |
---|
98 | |
---|
99 | CALL dia_wri( kstp ) ! ocean model: outputs |
---|
100 | |
---|
101 | #if defined key_agrif |
---|
102 | !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> |
---|
103 | ! AGRIF |
---|
104 | !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< |
---|
105 | CALL Agrif_Integrate_ChildGrids( stp ) |
---|
106 | #endif |
---|
107 | |
---|
108 | !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> |
---|
109 | ! Control |
---|
110 | !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< |
---|
111 | CALL stp_ctl( kstp, indic ) |
---|
112 | IF( indic < 0 ) THEN |
---|
113 | CALL ctl_stop( 'step: indic < 0' ) |
---|
114 | CALL dia_wri_state( 'output.abort', kstp ) |
---|
115 | ENDIF |
---|
116 | IF( kstp == nit000 ) CALL iom_close( numror ) ! close input ocean restart file (clem: not sure...) |
---|
117 | |
---|
118 | !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> |
---|
119 | ! Coupled mode |
---|
120 | !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< |
---|
121 | IF( lk_oasis ) CALL sbc_cpl_snd( kstp ) ! coupled mode : field exchanges if OASIS-coupled ice |
---|
122 | |
---|
123 | #if defined key_iomput |
---|
124 | IF( kstp == nitrst ) THEN |
---|
125 | IF(.NOT.lwxios) THEN |
---|
126 | CALL iom_close( numrow ) |
---|
127 | ELSE |
---|
128 | CALL iom_context_finalize( cwxios_context ) |
---|
129 | ENDIF |
---|
130 | lrst_oce = .FALSE. |
---|
131 | ENDIF |
---|
132 | IF( kstp == nitend .OR. indic < 0 ) THEN |
---|
133 | CALL iom_context_finalize( cxios_context ) ! needed for XIOS+AGRIF |
---|
134 | ENDIF |
---|
135 | #endif |
---|
136 | ! |
---|
137 | IF( nn_timing == 1 .AND. kstp == nit000 ) CALL timing_reset |
---|
138 | ! |
---|
139 | END SUBROUTINE stp |
---|
140 | |
---|
141 | !!====================================================================== |
---|
142 | END MODULE step |
---|