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/src/OCE/C1D – NEMO

source: NEMO/trunk/src/OCE/C1D/step_c1d.F90 @ 13286

Last change on this file since 13286 was 13237, checked in by smasson, 4 years ago

trunk: Mid-year merge, merge back KERNEL-06_techene_e3

  • Property svn:keywords set to Id
File size: 9.1 KB
RevLine 
[2409]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
[12377]8   !!             4.1  !  2019-08  (A. Coward, D. Storkey) rewrite in preparation for new timestepping scheme
[2409]9   !!----------------------------------------------------------------------
10#if defined key_c1d
11   !!----------------------------------------------------------------------
12   !!   'key_c1d'                                       1D Configuration
13   !!---------------------------------------------------------------------- 
14   !!   stp_c1d        : NEMO system time-stepping in c1d case
15   !!----------------------------------------------------------------------
[4245]16   USE step_oce        ! time stepping definition modules
[12377]17   USE step, ONLY : Nbb, Nnn, Naa, Nrhs ! time level indices
[2409]18#if defined key_top
[4245]19   USE trcstp          ! passive tracer time-stepping      (trc_stp routine)
[2409]20#endif
21   USE dyncor_c1d      ! Coriolis term (c1d case)         (dyn_cor_1d     )
[12377]22   USE dynatf          ! time filtering                   (dyn_atf routine)
[4245]23   USE dyndmp          ! U & V momentum damping           (dyn_dmp routine)
[3680]24   USE restart         ! restart
[2409]25
26   IMPLICIT NONE
27   PRIVATE
28
[12740]29   PUBLIC stp_c1d      ! called by nemogcm.F90
[2409]30
31   !!----------------------------------------------------------------------
[10068]32   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[5215]33   !! $Id$
[10068]34   !! Software governed by the CeCILL license (see ./LICENSE)
[2409]35   !!----------------------------------------------------------------------
36CONTAINS
37
38   SUBROUTINE stp_c1d( kstp )
39      !!----------------------------------------------------------------------
40      !!                     ***  ROUTINE stp_c1d  ***
41      !!                     
[9656]42      !! ** Purpose :  - Time stepping of SBC including sea ice (dynamic and thermodynamic eqs.)
[2409]43      !!               - Time stepping of OPA (momentum and active tracer eqs.)
44      !!               - Time stepping of TOP (passive tracer eqs.)
45      !!
46      !! ** Method  : -1- Update forcings and data 
47      !!              -2- Update vertical ocean physics
48      !!              -3- Compute the t and s trends
49      !!              -4- Update t and s
50      !!              -5- Compute the momentum trends
51      !!              -6- Update the horizontal velocity
52      !!              -7- Compute the diagnostics variables (rd,N2, div,cur,w)
53      !!              -8- Outputs and diagnostics
54      !!----------------------------------------------------------------------
55      INTEGER, INTENT(in) ::   kstp   ! ocean time-step index
[6140]56      !
[2409]57      INTEGER ::   jk       ! dummy loop indice
58      !! ---------------------------------------------------------------------
[4247]59      IF( kstp == nit000 )   CALL iom_init( "nemo")   ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS)
[2409]60      IF( kstp /= nit000 )   CALL day( kstp )         ! Calendar (day was already called at nit000 in day_init)
[4247]61                             CALL iom_setkt( kstp - nit000 + 1, "nemo" )   ! say to iom that we are at time step kstp
[2409]62
63      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
64      ! Update data, open boundaries, surface boundary condition (including sea-ice)
65      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
[12377]66                         CALL sbc    ( kstp, Nbb, Nnn )  ! Sea Boundary Condition (including sea-ice)
[2409]67
68      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
[12377]69      ! Ocean physics update       
[2409]70      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
[12377]71                         CALL eos_rab( ts(:,:,:,:,Nbb), rab_b, Nnn )  ! before local thermal/haline expension ratio at T-points
72                         CALL eos_rab( ts(:,:,:,:,Nnn), rab_n, Nnn )  ! now    local thermal/haline expension ratio at T-points
73                         CALL bn2( ts(:,:,:,:,Nbb), rab_b, rn2b, Nnn ) ! before Brunt-Vaisala frequency
74                         CALL bn2( ts(:,:,:,:,Nnn), rab_n, rn2 , Nnn ) ! now    Brunt-Vaisala frequency
[9019]75     
76      !  VERTICAL PHYSICS
[12377]77                         CALL zdf_phy( kstp, Nbb, Nnn, Nrhs  )    ! vertical physics update (bfr, avt, avs, avm + MLD)
[2409]78
[12377]79      IF(.NOT.ln_linssh )   CALL ssh_nxt       ( kstp, Nbb, Nnn, ssh, Naa )  ! after ssh (includes call to div_hor)
80      IF(.NOT.ln_linssh )   CALL dom_vvl_sf_nxt( kstp, Nbb, Nnn,      Naa )  ! after vertical scale factors
[2409]81
[13237]82      IF(.NOT.ln_linssh )   CALL wzv           ( kstp, Nbb, Nnn, Naa, ww )  ! now cross-level velocity
[2409]83      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
[12377]84      ! diagnostics and outputs       
[2409]85      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
[12377]86                         CALL dia_wri( kstp, Nnn )  ! ocean model: outputs
[12740]87                         CALL dia_hth( kstp, Nnn )  ! Thermocline depth (20°C)
[2409]88
[4153]89
[2409]90#if defined key_top
91      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
92      ! Passive Tracer Model
93      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
[12377]94                        CALL trc_stp( kstp, Nbb, Nnn, Nrhs, Naa  )   ! time-stepping
[2409]95#endif
96
97      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
[12377]98      ! Active tracers                              (uu(:,:,:,Nrhs), vv(:,:,:,Nrhs) used as workspace)
[2409]99      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
[12377]100                        ts(:,:,:,:,Nrhs) = 0._wp       ! set tracer trends to zero
[2409]101
[12377]102                        CALL tra_sbc( kstp,      Nnn, ts, Nrhs  )  ! surface boundary condition
103      IF( ln_traqsr )   CALL tra_qsr( kstp,      Nnn, ts, Nrhs  )  ! penetrative solar radiation qsr
104      IF( ln_tradmp )   CALL tra_dmp( kstp, Nbb, Nnn, ts, Nrhs  )  ! internal damping trends- tracers
105      IF(.NOT.ln_linssh)CALL tra_adv( kstp, Nbb, Nnn, ts, Nrhs  )  ! horizontal & vertical advection
106      IF( ln_zdfosm  )  CALL tra_osm( kstp, Nnn     , ts, Nrhs  )  ! OSMOSIS non-local tracer fluxes
107                        CALL tra_zdf( kstp, Nbb, Nnn, Nrhs, ts, Naa   )         ! vertical mixing
108                        CALL eos( ts(:,:,:,:,Nnn), rhd, rhop, gdept_0(:,:,:) )  ! now potential density for zdfmxl
109      IF( ln_zdfnpc )   CALL tra_npc( kstp,      Nnn, Nrhs, ts, Naa   )         ! applied non penetrative convective adjustment on (t,s)
[12740]110                        CALL tra_atf( kstp, Nbb, Nnn, Naa, ts )                 ! time filtering of "now" tracer arrays
[2409]111
112      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
113      ! Dynamics                                    (ta, sa used as workspace)
114      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
[12377]115                        uu(:,:,:,Nrhs) = 0._wp          ! set dynamics trends to zero
116                        vv(:,:,:,Nrhs) = 0._wp
[2409]117
[12377]118      IF( ln_dyndmp )   CALL dyn_dmp    ( kstp, Nbb, Nnn      , uu, vv, Nrhs )  ! internal damping trends- momentum
119                        CALL dyn_cor_c1d( kstp,      Nnn      , uu, vv, Nrhs )  ! vorticity term including Coriolis
120      IF( ln_zdfosm  )  CALL dyn_osm    ( kstp,      Nnn      , uu, vv, Nrhs )  ! OSMOSIS non-local velocity fluxes
121                        CALL dyn_zdf    ( kstp, Nbb, Nnn, Nrhs, uu, vv, Naa  )  ! vertical diffusion
122                        CALL dyn_atf    ( kstp, Nbb, Nnn, Naa , uu, vv, e3t, e3u, e3v )  ! time filtering of "now" fields
123      IF(.NOT.ln_linssh)CALL ssh_atf    ( kstp, Nbb, Nnn, Naa , ssh )                    ! time filtering of "now" sea surface height
124      !
125      ! Swap time levels
126      Nrhs = Nbb
127      Nbb = Nnn
128      Nnn = Naa
129      Naa = Nrhs
130      !
131      IF(.NOT.ln_linssh)CALL dom_vvl_sf_update( kstp, Nbb, Nnn, Naa )                    ! update of vertical scale factors
[2409]132
133      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
134      ! Control and restarts
135      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
[12933]136                             CALL stp_ctl( kstp, Nnn )
[12377]137      IF( kstp == nit000 )   CALL iom_close( numror )          ! close input  ocean restart file
138      IF( lrst_oce       )   CALL rst_write( kstp, Nbb, Nnn )  ! write output ocean restart file
[2409]139      !
[5412]140#if defined key_iomput
[12933]141      IF( kstp == nitend .OR. nstop > 0 )   CALL xios_context_finalize()   ! needed for XIOS
[5412]142      !
143#endif
[2409]144   END SUBROUTINE stp_c1d
145
146#else
147   !!----------------------------------------------------------------------
148   !!   Default key                                            NO 1D Config
149   !!----------------------------------------------------------------------
150CONTAINS
151   SUBROUTINE stp_c1d ( kt )      ! dummy routine
[9927]152      IMPLICIT NONE
153      INTEGER, INTENT( in ) :: kt
[2409]154      WRITE(*,*) 'stp_c1d: You should not have seen this print! error?', kt
155   END SUBROUTINE stp_c1d
156#endif
157
158   !!======================================================================
159END MODULE step_c1d
Note: See TracBrowser for help on using the repository browser.