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 trunk/NEMO/C1D_SRC – NEMO

source: trunk/NEMO/C1D_SRC/step_c1d.F90 @ 900

Last change on this file since 900 was 900, checked in by rblod, 16 years ago

Update 1D configuration according to SBC and LIM3, see ticket #117

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