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/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/OPA_SRC/DOM – NEMO

source: branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/OPA_SRC/DOM/domstp.F90

Last change on this file was 11738, checked in by marc, 5 years ago

The Dr Hook changes from my perl code.

File size: 5.3 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 :  OPA  ! 1990-10  (O. Marti)  Original code
11   !!                 ! 1996-01  (G. Madec)  terrain following coordinates
12   !!   NEMO     1.0  ! 2002-08  (G. Madec)  F90: Free form and module
13   !!----------------------------------------------------------------------
14   USE oce            ! ocean dynamics and tracers
15   USE dom_oce        ! ocean space and time domain
16   USE in_out_manager ! I/O manager
17   USE lib_mpp        ! MPP library
18
19   USE yomhook, ONLY: lhook, dr_hook
20   USE parkind1, ONLY: jprb, jpim
21
22   IMPLICIT NONE
23   PRIVATE
24
25   PUBLIC   dom_stp   ! routine called by inidom.F90
26
27   !! * Substitutions
28#  include "domzgr_substitute.h90"
29   !!----------------------------------------------------------------------
30   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
31   !! $Id$
32   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
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 :   Bryan, K., 1984, J. Phys. Oceanogr., 14, 666-673.
62      !!----------------------------------------------------------------------
63      INTEGER ::   jk              ! dummy loop indice
64      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
65      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
66      REAL(KIND=jprb)               :: zhook_handle
67
68      CHARACTER(LEN=*), PARAMETER :: RoutineName='DOM_STP'
69
70      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
71
72      !!----------------------------------------------------------------------
73
74      IF(lwp) THEN
75         WRITE(numout,*)
76         WRITE(numout,*) 'dom_stp : time stepping setting'
77         WRITE(numout,*) '~~~~~~~'
78      ENDIF
79
80      ! 0. Asselin Time filter
81      ! ----------------------
82     
83      atfp1 = 1. - 2. * atfp
84
85      SELECT CASE ( nacc )
86
87         CASE ( 0 )                ! Synchronous time stepping
88            IF(lwp) WRITE(numout,*)'               synchronous time stepping'
89            IF(lwp) WRITE(numout,*)'               dynamics and tracer time step = ', rdt/3600., ' hours'
90
91            rdttra(:) = rdt
92
93         CASE ( 1 )                ! Accelerating the convergence
94            IF(lwp) WRITE(numout,*) '              no tracer damping in the turbocline'
95            IF(lwp) WRITE(numout,*)'               accelerating the convergence'
96            IF(lwp) WRITE(numout,*)'               dynamics time step = ', rdt/3600., ' hours'
97            IF( ln_sco .AND. rdtmin /= rdtmax .AND. lk_vvl )   &
98                 & CALL ctl_stop ( ' depth dependent acceleration of convergence not implemented in s-coordinates &
99                 &                   nor in variable volume' )
100            IF(lwp) WRITE(numout,*)'         tracers   time step :  dt (hours)  level'
101
102            DO jk = 1, jpk
103               IF( gdept_1d(jk) <= rdth ) rdttra(jk) = rdtmin
104               IF( gdept_1d(jk) >  rdth ) THEN
105                  rdttra(jk) = rdtmin + ( rdtmax - rdtmin )   &
106                                      * ( EXP( ( gdept_1d(jk ) - rdth ) / rdth ) - 1. )   &
107                                      / ( EXP( ( gdept_1d(jpk) - rdth ) / rdth ) - 1. )
108               ENDIF
109               IF(lwp) WRITE(numout,"(36x,f5.2,5x,i3)") rdttra(jk)/3600., jk
110            END DO 
111
112         CASE DEFAULT              ! E R R O R
113
114            WRITE(ctmp1,*) ' nacc value e r r o r, nacc= ',nacc
115            CALL ctl_stop( ctmp1 )
116
117      END SELECT
118
119      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
120   END SUBROUTINE dom_stp
121
122   !!======================================================================
123END MODULE domstp
Note: See TracBrowser for help on using the repository browser.