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 branches/nemo_v3_3_beta/NEMOGCM/NEMO/C1D_SRC – NEMO

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/C1D_SRC/step_c1d.F90 @ 2382

Last change on this file since 2382 was 2382, checked in by gm, 13 years ago

v3.3beta: C1D - bug correction to compile with key_c1d

  • Property svn:keywords set to Id
File size: 9.1 KB
RevLine 
[900]1MODULE step_c1d
[253]2   !!======================================================================
[900]3   !!                       ***  MODULE step_c1d  ***
4   !! Time-stepping    : manager of the ocean, tracer and ice time stepping - c1d case
[253]5   !!======================================================================
[900]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
8   !!----------------------------------------------------------------------
[922]9#if defined key_c1d
[253]10   !!----------------------------------------------------------------------
[922]11   !!   'key_c1d'                                       1D Configuration
[253]12   !!---------------------------------------------------------------------- 
[900]13   !!   stp_c1d        : NEMO system time-stepping in c1d case
[253]14   !!----------------------------------------------------------------------
[2382]15   USE step_oce         ! time stepping definition modules
16#if defined key_top
17   USE trcstp           ! passive tracer time-stepping      (trc_stp routine)
18#endif
[1221]19   USE dyncor_c1d      ! Coriolis term (c1d case)         (dyn_cor_1d     )
20   USE dynnxt_c1d      ! time-stepping                    (dyn_nxt routine)
21   USE diawri_c1d      ! write outputs                (dia_wri_c1d routine)
[900]22
[253]23   IMPLICIT NONE
24   PRIVATE
25
[900]26   PUBLIC stp_c1d      ! called by opa.F90
[253]27
28   !! * Substitutions
29#  include "domzgr_substitute.h90"
30#  include "zdfddm_substitute.h90"
31   !!----------------------------------------------------------------------
[2287]32   !! NEMO/C1D 3.3 , NEMO Consortium (2010)
[922]33   !! $Id$
[2382]34   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[253]35   !!----------------------------------------------------------------------
36CONTAINS
37
[900]38   SUBROUTINE stp_c1d( kstp )
[253]39      !!----------------------------------------------------------------------
[900]40      !!                     ***  ROUTINE stp_c1d  ***
[253]41      !!                     
[900]42      !! ** Purpose :  - Time stepping of SBC including LIM (dynamic and thermodynamic eqs.)
43      !!               - Time stepping of OPA (momentum and active tracer eqs.)
44      !!               - Time stepping of TOP (passive tracer eqs.)
[253]45      !!
46      !! ** Method  : -1- Update forcings and data 
[900]47      !!              -2- Update vertical ocean physics
[253]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      !!----------------------------------------------------------------------
[900]55      INTEGER, INTENT(in) ::   kstp   ! ocean time-step index
56      INTEGER ::   jk       ! dummy loop indice
[253]57      INTEGER ::   indic    ! error indicator if < 0
58      !! ---------------------------------------------------------------------
59
[2382]60                             indic = 0                ! reset to no error condition
61      IF( kstp /= nit000 )   CALL day( kstp )         ! Calendar (day was already called at nit000 in day_init)
62                             CALL iom_setkt( kstp )   ! say to iom that we are at time step kstp
[253]63
64      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
[900]65      ! Update data, open boundaries, surface boundary condition (including sea-ice)
[253]66      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
67      IF( lk_dtatem  )   CALL dta_tem( kstp )         ! update 3D temperature data
[900]68      IF( lk_dtasal  )   CALL dta_sal( kstp )         ! update 3D salinity data
69                         CALL sbc    ( kstp )         ! Sea Boundary Condition (including sea-ice)
[253]70
71      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
[2382]72      ! Ocean physics update                (ua, va, ta, sa used as workspace)
[253]73      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
[2382]74                         CALL bn2( tsb, rn2b )        ! before Brunt-Vaisala frequency
75                         CALL bn2( tsn, rn2  )        ! now    Brunt-Vaisala frequency
76      !  VERTICAL PHYSICS   
77                         CALL zdf_bfr( kstp )         ! bottom friction
78      !                                               ! Vertical eddy viscosity and diffusivity coefficients
79      IF( lk_zdfric  )   CALL zdf_ric( kstp )            ! Richardson number dependent Kz
80      IF( lk_zdftke  )   CALL zdf_tke( kstp )            ! TKE closure scheme for Kz
81      IF( lk_zdfgls  )   CALL zdf_gls( kstp )            ! GLS closure scheme for Kz
82      IF( lk_zdfkpp  )   CALL zdf_kpp( kstp )            ! KPP closure scheme for Kz
83      IF( lk_zdfcst  )   THEN                            ! Constant Kz (reset avt, avm[uv] to the background value)
84         avt (:,:,:) = rn_avt0 * tmask(:,:,:)
85         avmu(:,:,:) = rn_avm0 * umask(:,:,:)
86         avmv(:,:,:) = rn_avm0 * vmask(:,:,:)
[900]87      ENDIF
[1164]88
[2382]89      IF( ln_rnf_mouth ) THEN                         ! increase diffusivity at rivers mouths
[1164]90         DO jk = 2, nkrnf   ;   avt(:,:,jk) = avt(:,:,jk) + 2.e0 * rn_avt_rnf * rnfmsk(:,:)   ;   END DO
[900]91      ENDIF
[2382]92      IF( ln_zdfevd  )   CALL zdf_evd( kstp )         ! enhanced vertical eddy diffusivity
93
94      IF( lk_zdftmx  )   CALL zdf_tmx( kstp )         ! tidal vertical mixing
95
[900]96      IF( lk_zdfddm .AND. .NOT. lk_zdfkpp )   &
[2382]97         &               CALL zdf_ddm( kstp )         ! double diffusive mixing
98         
99                         CALL zdf_mxl( kstp )         ! mixed layer depth
[253]100
[2382]101                                                      ! write tke information in the restart file
102      IF( lrst_oce .AND. lk_zdftke )   CALL tke_rst( kstp, 'WRITE' )
103                                                      ! write gls information in the restart file
104      IF( lrst_oce .AND. lk_zdfgls )   CALL gls_rst( kstp, 'WRITE' )
105
106      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
107      ! diagnostics and outputs             (ua, va, ta, sa used as workspace)
108      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
109                         CALL dia_wri_c1d( kstp, indic )       ! ocean model: outputs
110
[922]111#if defined key_top
[439]112      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
113      ! Passive Tracer Model
114      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
[2382]115                         CALL trc_stp( kstp, indic )            ! time-stepping
[439]116#endif
117
[253]118      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
[2382]119      ! Active tracers                              (ua, va used as workspace)
[253]120      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
[2104]121                             tsa(:,:,:,:) = 0.e0                ! set tracer trends to zero
[253]122
[900]123                             CALL tra_sbc    ( kstp )        ! surface boundary condition
124      IF( ln_traqsr      )   CALL tra_qsr    ( kstp )        ! penetrative solar radiation qsr
[2382]125      IF( lk_zdfkpp      )   CALL tra_kpp    ( kstp )        ! KPP non-local tracer fluxes
[900]126                             CALL tra_zdf    ( kstp )        ! vertical mixing
[2104]127                             CALL tra_nxt    ( kstp )        ! tracer fields at next time step
128      IF( ln_zdfnpc      )   CALL tra_npc    ( kstp )        ! applied non penetrative convective adjustment on (t,s)
[2382]129                             CALL eos( tsb, rhd, rhop )      ! now (swap=before) in situ density for dynhpg module
130                             CALL tra_unswap                 ! udate T & S 3D arrays  (to be suppressed)
[253]131
132      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
[2382]133      ! Dynamics                                    (ta, sa used as workspace)
[253]134      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
135                               ua(:,:,:) = 0.e0               ! set dynamics trends to zero
136                               va(:,:,:) = 0.e0
137
[1221]138                               CALL dyn_cor_c1d( kstp )       ! vorticity term including Coriolis
[900]139                               CALL dyn_zdf    ( kstp )       ! vertical diffusion
140                               CALL dyn_nxt_c1d( kstp )       ! lateral velocity at next time step
[253]141
142      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
[900]143      ! Control and restarts
144      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
145                                 CALL stp_ctl( kstp, indic )
146      IF( kstp == nit000     )   CALL iom_close( numror )             ! close input  ocean restart file
147      IF( lrst_oce           )   CALL rst_write  ( kstp )             ! write output ocean restart file
148      !
149   END SUBROUTINE stp_c1d
[253]150
151#else
152   !!----------------------------------------------------------------------
[900]153   !!   Default key                                            NO 1D Config
[253]154   !!----------------------------------------------------------------------
155CONTAINS
[900]156   SUBROUTINE stp_c1d ( kt )      ! dummy routine
157      WRITE(*,*) 'stp_c1d: You should not have seen this print! error?', kt
158   END SUBROUTINE stp_c1d
[253]159#endif
[900]160
[253]161   !!======================================================================
[900]162END MODULE step_c1d
Note: See TracBrowser for help on using the repository browser.