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_c1d.F90 in NEMO/trunk/tests/STATION_ASF/MY_SRC – NEMO

source: NEMO/trunk/tests/STATION_ASF/MY_SRC/step_c1d.F90 @ 14768

Last change on this file since 14768 was 14239, checked in by smasson, 4 years ago

trunk: replace key_iomput by key_xios

File size: 4.9 KB
RevLine 
[11637]1MODULE step_c1d
2   !!======================================================================
3   !!                       ***  MODULE step_c1d  ***
4   !! Time-stepping    : manager of the ocean, tracer and ice time stepping - c1d case
5   !!======================================================================
6   !! History :   2.0  !  2004-04  (C. Ethe)  adapted from step.F90 for C1D
7   !!             3.0  !  2008-04  (G. Madec)  redo the adaptation to include SBC
[12249]8   !!             4.1  !  2019-08  (A. Coward, D. Storkey) rewrite in preparation for new timestepping scheme
[14072]9   !!             4.x  !  2020-11  (L. Brodeau) STATION_ASF test-case
[11637]10   !!----------------------------------------------------------------------
11#if defined key_c1d
12   !!----------------------------------------------------------------------
13   !!   'key_c1d'                                       1D Configuration
[12249]14   !!----------------------------------------------------------------------
[11637]15   !!   stp_c1d        : NEMO system time-stepping in c1d case
16   !!----------------------------------------------------------------------
[12249]17   USE step_oce        ! time stepping definition modules
18   USE step, ONLY : Nbb, Nnn, Naa, Nrhs ! time level indices
19   USE restart         ! restart
[11637]20
21   IMPLICIT NONE
22   PRIVATE
23
[14072]24   PUBLIC stp_c1d      ! called by nemogcm.F90
[11637]25
26   !!----------------------------------------------------------------------
27   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[14072]28   !! $Id: step_c1d.F90 13802 2020-11-17 09:21:55Z gsamson $
[11637]29   !! Software governed by the CeCILL license (see ./LICENSE)
30   !!----------------------------------------------------------------------
31CONTAINS
32
33   SUBROUTINE stp_c1d( kstp )
34      !!----------------------------------------------------------------------
35      !!                     ***  ROUTINE stp_c1d  ***
[12249]36      !!
[11637]37      !! ** Purpose :  - Time stepping of SBC including sea ice (dynamic and thermodynamic eqs.)
[14227]38      !!               - Time stepping of OCE (momentum and active tracer eqs.)
[11637]39      !!               - Time stepping of TOP (passive tracer eqs.)
[12249]40      !!
41      !! ** Method  : -1- Update forcings and data
42      !!              -2- Update vertical ocean physics
43      !!              -3- Compute the t and s trends
44      !!              -4- Update t and s
[11637]45      !!              -5- Compute the momentum trends
46      !!              -6- Update the horizontal velocity
47      !!              -7- Compute the diagnostics variables (rd,N2, div,cur,w)
48      !!              -8- Outputs and diagnostics
49      !!----------------------------------------------------------------------
50      INTEGER, INTENT(in) ::   kstp   ! ocean time-step index
51      !
52      INTEGER ::   jk       ! dummy loop indice
53      !! ---------------------------------------------------------------------
54      IF( kstp == nit000 )   CALL iom_init( "nemo")   ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS)
55      IF( kstp /= nit000 )   CALL day( kstp )         ! Calendar (day was already called at nit000 in day_init)
[14072]56                             CALL iom_setkt( kstp - nit000 + 1, "nemo" )   ! say to iom that we are at time step kstp
[11637]57
[12249]58      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
59      ! Update data, open boundaries, surface boundary condition (including sea-ice)
60      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
[14072]61                         CALL sbc    ( kstp, Nbb, Nnn )  ! Sea Boundary Condition (including sea-ice)
[11637]62
[13135]63      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
64      ! diagnostics and outputs
65      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
[14072]66                         CALL dia_wri( kstp, Nnn )  ! ocean model: outputs
[11637]67
[12249]68      ! Swap time levels
69      Nrhs = Nbb
70      Nbb = Nnn
71      Nnn = Naa
72      Naa = Nrhs
73
[11637]74      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
[12249]75      ! Control and restarts
[11637]76      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
[14072]77                             CALL stp_ctl( kstp, Nnn )
[12249]78      IF( kstp == nit000 )   CALL iom_close( numror )          ! close input  ocean restart file
79      IF( lrst_oce       )   CALL rst_write( kstp, Nbb, Nnn )  ! write output ocean restart file
[11637]80      !
[14239]81#if defined key_xios
[13135]82      IF( kstp == nitend .OR. nstop > 0 )   CALL xios_context_finalize()   ! needed for XIOS
[12249]83      !
[11637]84#endif
85   END SUBROUTINE stp_c1d
86
87#else
[12249]88   !!----------------------------------------------------------------------
89   !!   Default key                                            NO 1D Config
90   !!----------------------------------------------------------------------
[11637]91CONTAINS
[12249]92   SUBROUTINE stp_c1d ( kt )      ! dummy routine
[11637]93      IMPLICIT NONE
94      INTEGER, INTENT( in ) :: kt
95      WRITE(*,*) 'stp_c1d: You should not have seen this print! error?', kt
96   END SUBROUTINE stp_c1d
97#endif
[12249]98
[11637]99   !!======================================================================
100END MODULE step_c1d
Note: See TracBrowser for help on using the repository browser.