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 @ 2281

Last change on this file since 2281 was 2281, checked in by smasson, 14 years ago

set proper svn properties to all files...

  • Property svn:keywords set to Id
File size: 11.2 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 oce             ! ocean dynamics and tracers variables
16   USE dom_oce         ! ocean space and time domain variables
17   USE zdf_oce         ! ocean vertical physics variables
18   USE in_out_manager  ! I/O manager
19   USE iom             !
20   USE lbclnk
21
22   USE daymod          ! calendar                         (day     routine)
23
24   USE dtatem          ! ocean temperature data           (dta_tem routine)
25   USE dtasal          ! ocean salinity    data           (dta_sal routine)
26   USE sbcmod          ! surface boundary condition       (sbc     routine)
27   USE sbcrnf          ! surface boundary condition: runoff variables
28
29   USE trcstp          ! passive tracer time-stepping      (trc_stp routine)
30
31   USE traqsr          ! solar radiation penetration      (tra_qsr routine)
32   USE trasbc          ! surface boundary condition       (tra_sbc routine)
33   !   zdfkpp          ! KPP non-local tracer fluxes      (tra_kpp routine)
34   USE trazdf          ! vertical mixing                  (tra_zdf routine)
35   USE tranxt          ! time-stepping                    (tra_nxt routine)
36   USE tranpc          ! non-penetrative convection       (tra_npc routine)
37
38   USE eosbn2          ! equation of state                (eos_bn2 routine)
39
40   USE dyncor_c1d      ! Coriolis term (c1d case)         (dyn_cor_1d     )
41   USE dynzdf          ! vertical diffusion               (dyn_zdf routine)
42   USE dynnxt_c1d      ! time-stepping                    (dyn_nxt routine)
43   USE diawri_c1d      ! write outputs                (dia_wri_c1d routine)
44
45   USE zdfbfr          ! bottom friction                  (zdf_bfr routine)
46   USE zdftke          ! TKE vertical mixing              (zdf_tke routine)
47   USE zdfkpp          ! KPP vertical mixing              (zdf_kpp routine)
48   USE zdfddm          ! double diffusion mixing          (zdf_ddm routine)
49   USE zdfevd          ! enhanced vertical diffusion      (zdf_evd routine)
50   USE zdfric          ! Richardson vertical mixing       (zdf_ric routine)
51   USE zdfmxl          ! Mixed-layer depth                (zdf_mxl routine)
52
53
54   USE diawri          ! Standard run outputs             (dia_wri routine)
55
56   USE stpctl          ! time stepping control            (stp_ctl routine)
57   USE restart         ! ocean restart                    (rst_wri routine)
58   USE prtctl          ! Print control                    (prt_ctl routine)
59
60   IMPLICIT NONE
61   PRIVATE
62
63   PUBLIC stp_c1d      ! called by opa.F90
64
65   !! * Substitutions
66#  include "domzgr_substitute.h90"
67#  include "zdfddm_substitute.h90"
68   !!----------------------------------------------------------------------
69   !! NEMO 3.0 , LOCEAN-IPSL (2008)
70   !! $Id$
71   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
72   !!----------------------------------------------------------------------
73
74CONTAINS
75
76   SUBROUTINE stp_c1d( kstp )
77      !!----------------------------------------------------------------------
78      !!                     ***  ROUTINE stp_c1d  ***
79      !!                     
80      !! ** Purpose :  - Time stepping of SBC including LIM (dynamic and thermodynamic eqs.)
81      !!               - Time stepping of OPA (momentum and active tracer eqs.)
82      !!               - Time stepping of TOP (passive tracer eqs.)
83      !!
84      !! ** Method  : -1- Update forcings and data 
85      !!              -2- Update vertical ocean physics
86      !!              -3- Compute the t and s trends
87      !!              -4- Update t and s
88      !!              -5- Compute the momentum trends
89      !!              -6- Update the horizontal velocity
90      !!              -7- Compute the diagnostics variables (rd,N2, div,cur,w)
91      !!              -8- Outputs and diagnostics
92      !!----------------------------------------------------------------------
93      INTEGER, INTENT(in) ::   kstp   ! ocean time-step index
94      INTEGER ::   jk       ! dummy loop indice
95      INTEGER ::   indic    ! error indicator if < 0
96      !! ---------------------------------------------------------------------
97
98      indic = 1                    ! reset to no error condition
99
100      CALL day( kstp )             ! Calendar
101
102      CALL rst_opn( kstp )         ! Open the restart file
103
104      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
105      ! Update data, open boundaries, surface boundary condition (including sea-ice)
106      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
107
108      IF( lk_dtatem  )   CALL dta_tem( kstp )         ! update 3D temperature data
109      IF( lk_dtasal  )   CALL dta_sal( kstp )         ! update 3D salinity data
110
111                         CALL sbc    ( kstp )         ! Sea Boundary Condition (including sea-ice)
112
113      IF( ninist == 1 ) THEN                          ! Output the initial state and forcings
114                        CALL dia_wri_state( 'output.init', kstp )   ;   ninist = 0
115      ENDIF
116
117
118      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
119      ! Ocean physics update
120      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
121      !-----------------------------------------------------------------------
122      !  VERTICAL PHYSICS
123      !-----------------------------------------------------------------------
124      ! N.B. ua, va, ta, sa arrays are used as workspace in this section
125      !-----------------------------------------------------------------------
126
127                        CALL bn2( tb, sb, rn2 )             ! before Brunt-Vaisala frequency
128     
129      !                                                     ! Vertical eddy viscosity and diffusivity coefficients
130      IF( lk_zdfric )   CALL zdf_ric( kstp )                     ! Richardson number dependent Kz
131      IF( lk_zdftke )   CALL zdf_tke( kstp )                     ! TKE closure scheme for Kz
132      IF( lk_zdfkpp )   CALL zdf_kpp( kstp )                     ! KPP closure scheme for Kz
133      IF( lk_zdfcst )   THEN                                     ! Constant Kz (reset avt, avm to the background value)
134         avt (:,:,:) = avt0 * tmask(:,:,:)
135         avmu(:,:,:) = avm0 * umask(:,:,:)
136         avmv(:,:,:) = avm0 * vmask(:,:,:)
137      ENDIF
138
139      IF( ln_rnf_mouth ) THEN                                ! increase diffusivity at rivers mouths
140         DO jk = 2, nkrnf   ;   avt(:,:,jk) = avt(:,:,jk) + 2.e0 * rn_avt_rnf * rnfmsk(:,:)   ;   END DO
141      ENDIF
142      IF( ln_zdfevd )   CALL zdf_evd( kstp )                 ! enhanced vertical eddy diffusivity
143      IF( lk_zdfddm .AND. .NOT. lk_zdfkpp )   &
144         &              CALL zdf_ddm( kstp )                 ! double diffusive mixing
145                        CALL zdf_bfr( kstp )                 ! bottom friction
146                        CALL zdf_mxl( kstp )                 ! mixed layer depth
147
148#if defined key_top
149      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
150      ! Passive Tracer Model
151      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
152      ! N.B. ua, va, ta, sa arrays are used as workspace in this section
153      !-----------------------------------------------------------------------
154                             CALL trc_stp( kstp, indic )            ! time-stepping
155#endif
156
157      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
158      ! Active tracers
159      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
160      ! N.B. ua, va arrays are used as workspace in this section
161      !-----------------------------------------------------------------------
162                             tsa(:,:,:,:) = 0.e0                ! set tracer trends to zero
163
164                             CALL tra_sbc    ( kstp )        ! surface boundary condition
165      IF( ln_traqsr      )   CALL tra_qsr    ( kstp )        ! penetrative solar radiation qsr
166      IF( lk_zdfkpp )        CALL tra_kpp    ( kstp )        ! KPP non-local tracer fluxes
167                             CALL tra_zdf    ( kstp )        ! vertical mixing
168                             CALL tra_nxt    ( kstp )        ! tracer fields at next time step
169      IF( ln_zdfnpc      )   CALL tra_npc    ( kstp )        ! applied non penetrative convective adjustment on (t,s)
170                             CALL eos( tsb, rhd, rhop )   ! now (swap=before) in situ density for dynhpg module
171
172      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
173      ! Dynamics
174      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
175      ! N.B. ta, sa arrays are used as workspace in this section
176      !-----------------------------------------------------------------------
177                               ua(:,:,:) = 0.e0               ! set dynamics trends to zero
178                               va(:,:,:) = 0.e0
179
180                               CALL dyn_cor_c1d( kstp )       ! vorticity term including Coriolis
181                               CALL dyn_zdf    ( kstp )       ! vertical diffusion
182                               CALL dyn_nxt_c1d( kstp )       ! lateral velocity at next time step
183
184      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
185      ! Control and restarts
186      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
187                                 CALL stp_ctl( kstp, indic )
188      IF( kstp == nit000     )   CALL iom_close( numror )             ! close input  ocean restart file
189      IF( lrst_oce           )   CALL rst_write  ( kstp )             ! write output ocean restart file
190
191      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
192      ! diagnostics and outputs
193      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
194      ! N.B. ua, va, ta, sa arrays are used as workspace in this section
195      !-----------------------------------------------------------------------
196
197      IF( nstop == 0 )           CALL dia_wri_c1d( kstp, indic )       ! ocean model: outputs
198      !
199   END SUBROUTINE stp_c1d
200
201#else
202   !!----------------------------------------------------------------------
203   !!   Default key                                            NO 1D Config
204   !!----------------------------------------------------------------------
205CONTAINS
206   SUBROUTINE stp_c1d ( kt )      ! dummy routine
207      WRITE(*,*) 'stp_c1d: You should not have seen this print! error?', kt
208   END SUBROUTINE stp_c1d
209#endif
210
211   !!======================================================================
212END MODULE step_c1d
Note: See TracBrowser for help on using the repository browser.