New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
step.F90 in NEMO/trunk/src/SAS – NEMO

source: NEMO/trunk/src/SAS/step.F90

Last change on this file was 14239, checked in by smasson, 3 years ago

trunk: replace key_iomput by key_xios

  • Property svn:keywords set to Id
File size: 8.1 KB
RevLine 
[3331]1MODULE 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
[3362]8   !!             .   !    .                                                     
9   !!             .   !    .                                                     
10   !!   NEMO     3.5  !  2012-03  (S. Alderson)
[3331]11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
[14227]14   !!   stp             : OCE system time-stepping
[3331]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)
[6140]19   USE sbc_oce          ! surface boundary condition: fields
[3331]20   USE sbcmod           ! surface boundary condition       (sbc     routine)
21   USE sbcrnf           ! surface boundary condition: runoff variables
[6140]22   USE sbccpl           ! surface boundary condition: coupled interface
[3331]23   USE eosbn2           ! equation of state                (eos_bn2 routine)
24   USE diawri           ! Standard run outputs             (dia_wri routine)
[7646]25   USE bdy_oce   , ONLY: ln_bdy
[9019]26   USE bdydta           ! mandatory for sea-ice
[6140]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           
[14239]34#if defined key_xios
[6140]35   USE xios
36#endif
[5510]37
[7646]38#if defined key_agrif
[9019]39   USE agrif_oce, ONLY: lk_agrif_debug
[9570]40#if defined key_si3
[9596]41   USE agrif_ice_update
[7646]42#endif
[9510]43#endif
[7646]44   
[3331]45   IMPLICIT NONE
46   PRIVATE
47
[6140]48   PUBLIC   stp   ! called by nemogcm.F90
[3331]49
50   !!----------------------------------------------------------------------
[12377]51   !! time level indices
52   !!----------------------------------------------------------------------
53   INTEGER, PUBLIC :: Nbb, Nnn, Naa, Nrhs          !! used by nemo_init
54   !!----------------------------------------------------------------------
[10068]55   !! NEMO/SAS 4.0 , NEMO Consortium (2018)
[5215]56   !! $Id$
[10068]57   !! Software governed by the CeCILL license (see ./LICENSE)
[3331]58   !!----------------------------------------------------------------------
59CONTAINS
60
61#if defined key_agrif
[7761]62   RECURSIVE SUBROUTINE stp( )
[3331]63      INTEGER             ::   kstp   ! ocean time-step index
64#else
65   SUBROUTINE stp( kstp )
66      INTEGER, INTENT(in) ::   kstp   ! ocean time-step index
67#endif
68      !!----------------------------------------------------------------------
69      !!                     ***  ROUTINE stp  ***
70      !!                     
[3358]71      !! ** Purpose : - Time stepping of SBC (surface boundary)
[3331]72      !!
73      !! ** Method  : -1- Update forcings and data 
[3358]74      !!              -2- Outputs and diagnostics
[3331]75      !!----------------------------------------------------------------------
76
77#if defined key_agrif
[12933]78      IF( nstop > 0 ) RETURN   ! avoid to go further if an error was detected during previous time step (child grid)
[3331]79      kstp = nit000 + Agrif_Nb_Step()
[12377]80      Kbb_a = Nbb; Kmm_a = Nnn; Krhs_a = Nrhs   ! agrif_oce module copies of time level indices
[12933]81      IF( lk_agrif_debug ) THEN
82         IF( Agrif_Root() .and. lwp)   WRITE(*,*) '---'
83         IF(lwp)   WRITE(*,*) 'Grid Number', Agrif_Fixed(),' time step ', kstp, 'int tstep', Agrif_NbStepint()
[7646]84      ENDIF
[12933]85      IF( kstp == nit000 + 1 )   lk_agrif_fstep = .FALSE.
[14239]86# if defined key_xios
[5407]87      IF( Agrif_Nbstepint() == 0 )   CALL iom_swap( cxios_context )
[3331]88# endif   
89#endif   
[5407]90      IF( kstp == nit000 )   CALL iom_init( cxios_context ) ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS)
[13970]91                             CALL iom_setkt( kstp - nit000 + 1, cxios_context )   ! tell iom we are at time step kstp
92      IF((kstp == nitrst) .AND. lwxios) THEN
93         CALL iom_swap(      cw_ocerst_cxt          )
94         CALL iom_init_closedef(cw_ocerst_cxt)
95         CALL iom_setkt( kstp - nit000 + 1,      cw_ocerst_cxt          )
96#if defined key_top
97         CALL iom_swap(      cw_toprst_cxt          )
98         CALL iom_init_closedef(cw_toprst_cxt)
99         CALL iom_setkt( kstp - nit000 + 1,      cw_toprst_cxt          )
100#endif
101      ENDIF
[3331]102      IF( kstp /= nit000 )   CALL day( kstp )             ! Calendar (day was already called at nit000 in day_init)
103
[13970]104#if defined key_si3
105      IF(((kstp + nn_fsbc - 1) == nitrst) .AND. lwxios) THEN
106         CALL iom_swap(      cw_icerst_cxt          )
107         CALL iom_init_closedef(cw_icerst_cxt)
108         CALL iom_setkt( kstp - nit000 + 1,      cw_icerst_cxt          )
109      ENDIF
110#endif
111
[9019]112      ! ==> clem: open boundaries is mandatory for sea-ice because ice BDY is not decoupled from 
[14227]113      !           the environment of ocean BDY. Therefore bdy is called in both OCE and SAS modules.
[5510]114      !           From SAS: ocean bdy data are wrong  (but we do not care) and ice bdy data are OK. 
115      !           This is not clean and should be changed in the future.
116      ! ==>
[12377]117      IF( ln_bdy     )       CALL bdy_dta( kstp,      Nnn )                   ! update dynamic & tracer data at open boundaries
118                             CALL sbc    ( kstp, Nbb, Nnn )                   ! Sea Boundary Condition (including sea-ice)
[3331]119
[12377]120                             CALL dia_wri( kstp,      Nnn )                   ! ocean model: outputs
[3331]121
[7646]122#if defined key_agrif
123      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
[12650]124      ! AGRIF recursive integration
[7646]125      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<     
[12933]126                             CALL Agrif_Integrate_ChildGrids( stp )
[7646]127                             
[12933]128#endif                             
[7646]129      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
130      ! Control
131      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
[12933]132                             CALL stp_ctl( kstp, Nnn )
133
[12650]134#if defined key_agrif
135      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
136      ! AGRIF update
137      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<     
138      IF( Agrif_NbStepint() == 0 .AND. nstop == 0 ) THEN                       ! AGRIF Update from zoom N to zoom 1 then to Parent
139#if defined key_si3
140                             CALL Agrif_Update_ice( )   ! update sea-ice
141#endif
142      ENDIF
[12933]143
[12650]144#endif
145      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
146      ! File manipulation at the end of the first time step
147      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<                         
[13970]148      IF( kstp == nit000   ) THEN
149            CALL iom_close( numror )                          ! close input  ocean restart file
150            IF( lrxios )     CALL iom_context_finalize(      cr_ocerst_cxt      )
151      ENDIF
[7646]152     
[5407]153      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
154      ! Coupled mode
155      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
[12933]156      IF( lk_oasis .AND. nstop == 0 ) CALL sbc_cpl_snd( kstp, Nbb, Nnn )       ! coupled mode : field exchanges if OASIS-coupled ice
[5407]157
[14239]158#if defined key_xios
[9367]159      IF( kstp == nitrst ) THEN
160         IF(.NOT.lwxios) THEN
161            CALL iom_close( numrow )     
162         ELSE
[13970]163            CALL iom_context_finalize( cw_ocerst_cxt )
164            iom_file(numrow)%nfid       = 0
165            numrow = 0
[9367]166         ENDIF
167         lrst_oce = .FALSE.
168      ENDIF
[12933]169      IF( kstp == nitend .OR. nstop > 0 ) THEN
170         CALL iom_context_finalize( cxios_context ) ! needed for XIOS+AGRIF
[5407]171      ENDIF
[3769]172#endif
[3331]173      !
[9019]174      IF( ln_timing .AND.  kstp == nit000  )   CALL timing_reset
[3331]175      !
176   END SUBROUTINE stp
177
178   !!======================================================================
179END MODULE step
Note: See TracBrowser for help on using the repository browser.