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.
domstp.F90 in branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/DOM – NEMO

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/DOM/domstp.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: 4.9 KB
Line 
1MODULE domstp
2   !!==============================================================================
3   !!                       ***  MODULE domstp   ***
4   !! Ocean initialization : time domain
5   !!==============================================================================
6
7   !!----------------------------------------------------------------------
8   !!   dom_stp        : ocean time domain initialization
9   !!----------------------------------------------------------------------
10   !! History :
11   !!        !  90-10  (O. Marti)  Original code
12   !!        !  96-01  (G. Madec)  terrain following coordinates
13   !!   8.5  !  02-08  (G. Madec)  F90: Free form and module
14   !!----------------------------------------------------------------------
15   !! * Modules used
16   USE oce             ! ocean dynamics and tracers
17   USE dom_oce         ! ocean space and time domain
18   USE in_out_manager  ! I/O manager
19
20   IMPLICIT NONE
21   PRIVATE
22
23   !! * routine accessibility
24   PUBLIC dom_stp        ! routine called by inidom.F90
25
26   !! * Substitutions
27#  include "domzgr_substitute.h90"
28   !!----------------------------------------------------------------------
29   !!   OPA 9.0 , LOCEAN-IPSL (2005)
30   !! $Id$
31   !! Software governed by the CeCILL licence  (NEMOGCM/License_CeCILL.txt)
32   !!----------------------------------------------------------------------
33
34CONTAINS
35
36   SUBROUTINE dom_stp
37      !!----------------------------------------------------------------------
38      !!                    ***  ROUTINE dom_stp  ***
39      !!         
40      !! ** Purpose :   Intialize ocean time step for the run
41      !!
42      !! ** Method  : - Initialization of a coef. use in the Asselin time
43      !!      filter:  atfp1 = 1 - 2 * atfp  where atfp is the Asselin time
44      !!      filter parameter read in namelist
45      !!              - Model time step:
46      !!      nacc = 0 : synchronous time intergration.
47      !!      There is one time step only, defined by: rdt, rdttra(k)=rdt
48      !!      nacc = 1 : accelerating the convergence. There is 2 different
49      !!      time steps for dynamics and tracers:
50      !!        rdt      : dynamical part
51      !!        rdttra(k): temperature and salinity
52      !!      The tracer time step is a function of vertical level. the model
53      !!      reference time step ( i.e. for wind stress, surface heat and
54      !!      salt fluxes) is the surface tracer time step is rdttra(1).
55      !!         N.B. depth dependent acceleration of convergence is not im-
56      !!      plemented for s-coordinate.
57      !!
58      !! ** Action  : - rdttra   : vertical profile of tracer time step
59      !!              - atfp1    : = 1 - 2*atfp
60      !!
61      !! References :
62      !!      Bryan, K., 1984, J. Phys. Oceanogr., 14, 666-673.
63      !!----------------------------------------------------------------------
64      INTEGER ::   jk              ! dummy loop indice
65      !!----------------------------------------------------------------------
66
67      IF(lwp) THEN
68         WRITE(numout,*)
69         WRITE(numout,*) 'dom_stp : time stepping setting'
70         WRITE(numout,*) '~~~~~~~'
71      ENDIF
72
73      ! 0. Asselin Time filter
74      ! ----------------------
75     
76      atfp1 = 1. - 2. * atfp
77
78      SELECT CASE ( nacc )
79
80         CASE ( 0 )                ! Synchronous time stepping
81            IF(lwp) WRITE(numout,*)'               synchronous time stepping'
82            IF(lwp) WRITE(numout,*)'               dynamics and tracer time step = ', rdt/3600., ' hours'
83
84            rdttra(:) = rdt
85
86         CASE ( 1 )                ! Accelerating the convergence
87            IF(lwp) WRITE(numout,*) '              no tracer damping in the turbocline'
88            IF(lwp) WRITE(numout,*)'               accelerating the convergence'
89            IF(lwp) WRITE(numout,*)'               dynamics time step = ', rdt/3600., ' hours'
90            IF( ln_sco .AND. rdtmin /= rdtmax .AND. lk_vvl )   &
91                 & CALL ctl_stop ( ' depth dependent acceleration of convergence not implemented in s-coordinates &
92                 &                   nor in variable volume' )
93            IF(lwp) WRITE(numout,*)'         tracers   time step :  dt (hours)  level'
94
95            DO jk = 1, jpk
96               IF( gdept_0(jk) <= rdth ) rdttra(jk) = rdtmin
97               IF( gdept_0(jk) >  rdth ) THEN
98                  rdttra(jk) = rdtmin + ( rdtmax - rdtmin )   &
99                                      * ( EXP( ( gdept_0(jk ) - rdth ) / rdth ) - 1. )   &
100                                      / ( EXP( ( gdept_0(jpk) - rdth ) / rdth ) - 1. )
101               ENDIF
102               IF(lwp) WRITE(numout,"(36x,f5.2,5x,i3)") rdttra(jk)/3600., jk
103            END DO 
104
105         CASE DEFAULT              ! E R R O R
106
107            WRITE(ctmp1,*) ' nacc value e r r o r, nacc= ',nacc
108            CALL ctl_stop( ctmp1 )
109
110      END SELECT
111
112   END SUBROUTINE dom_stp
113
114   !!======================================================================
115END MODULE domstp
Note: See TracBrowser for help on using the repository browser.