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/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/C1D – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/C1D/step_c1d.F90 @ 4460

Last change on this file since 4460 was 3211, checked in by spickles2, 12 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

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