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.
dyndmp.F90 in NEMO/trunk/src/OCE/C1D – NEMO

source: NEMO/trunk/src/OCE/C1D/dyndmp.F90 @ 12377

Last change on this file since 12377 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 10.6 KB
Line 
1MODULE dyndmp
2   !!======================================================================
3   !!                       ***  MODULE  dyndmp  ***
4   !! Ocean dynamics: internal restoring trend on momentum (U and V current)
5   !!                 This should only be used for C1D case in current form
6   !!======================================================================
7   !! History :  3.5  ! 2013-08  (D. Calvert)  Original code
8   !!            3.6  ! 2014-08  (T. Graham) Modified to use netcdf file of
9   !!                             restoration coefficients supplied to tradmp
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   dyn_dmp_alloc : allocate dyndmp arrays
14   !!   dyn_dmp_init  : namelist read, parameter control and resto coeff.
15   !!   dyn_dmp       : update the momentum trend with the internal damping
16   !!----------------------------------------------------------------------
17   USE oce            ! ocean: variables
18   USE dom_oce        ! ocean: domain variables
19   USE c1d            ! 1D vertical configuration
20   USE tradmp         ! ocean: internal damping
21   USE zdf_oce        ! ocean: vertical physics
22   USE phycst         ! physical constants
23   USE dtauvd         ! data: U & V current
24   USE zdfmxl         ! vertical physics: mixed layer depth
25   !
26   USE in_out_manager ! I/O manager
27   USE lib_mpp        ! MPP library
28   USE prtctl         ! Print control
29   USE timing         ! Timing
30   USE iom            ! I/O manager
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC   dyn_dmp_init ! routine called by nemogcm.F90
36   PUBLIC   dyn_dmp      ! routine called by step_c1d.F90
37
38   LOGICAL, PUBLIC ::   ln_dyndmp   !: Flag for Newtonian damping
39
40   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  utrdmp    !: damping U current trend (m/s2)
41   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  vtrdmp    !: damping V current trend (m/s2)
42   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  resto_uv  !: restoring coeff. on U & V current
43
44   !! * Substitutions
45#  include "do_loop_substitute.h90"
46   !!----------------------------------------------------------------------
47   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
48   !! $Id$
49   !! Software governed by the CeCILL license (see ./LICENSE)
50   !!----------------------------------------------------------------------
51CONTAINS
52
53   INTEGER FUNCTION dyn_dmp_alloc()
54      !!----------------------------------------------------------------------
55      !!                ***  FUNCTION dyn_dmp_alloc  ***
56      !!----------------------------------------------------------------------
57      ALLOCATE( utrdmp(jpi,jpj,jpk), vtrdmp(jpi,jpj,jpk), resto_uv(jpi,jpj,jpk), STAT= dyn_dmp_alloc )
58      !
59      CALL mpp_sum ( 'dyndmp', dyn_dmp_alloc )
60      IF( dyn_dmp_alloc > 0 )   CALL ctl_warn('dyn_dmp_alloc: allocation of arrays failed')
61      !
62   END FUNCTION dyn_dmp_alloc
63
64
65   SUBROUTINE dyn_dmp_init
66      !!----------------------------------------------------------------------
67      !!                  ***  ROUTINE dyn_dmp_init  ***
68      !!
69      !! ** Purpose :   Initialization for the Newtonian damping
70      !!
71      !! ** Method  : - read the ln_dyndmp parameter from the namc1d_dyndmp namelist
72      !!              - allocate damping arrays
73      !!              - check the parameters of the namtra_dmp namelist
74      !!              - calculate damping coefficient
75      !!----------------------------------------------------------------------
76      INTEGER ::   ios, imask   ! local integers
77      !!
78      NAMELIST/namc1d_dyndmp/ ln_dyndmp
79      !!----------------------------------------------------------------------
80      !
81      READ  ( numnam_ref, namc1d_dyndmp, IOSTAT = ios, ERR = 901)
82901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namc1d_dyndmp in reference namelist' )
83      READ  ( numnam_cfg, namc1d_dyndmp, IOSTAT = ios, ERR = 902 )
84902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namc1d_dyndmp in configuration namelist' )
85      IF(lwm) WRITE ( numond, namc1d_dyndmp )
86      !
87      IF(lwp) THEN                           ! control print
88         WRITE(numout,*)
89         WRITE(numout,*) 'dyn_dmp_init : U and V current Newtonian damping'
90         WRITE(numout,*) '~~~~~~~~~~~~'
91         WRITE(numout,*) '   Namelist namc1d_dyndmp : Set damping flag'
92         WRITE(numout,*) '      add a damping term or not       ln_dyndmp = ', ln_dyndmp
93         WRITE(numout,*) '   Namelist namtra_dmp    : Set damping parameters'
94         WRITE(numout,*) '      Apply relaxation   or not       ln_tradmp = ', ln_tradmp
95         WRITE(numout,*) '      mixed layer damping option      nn_zdmp   = ', nn_zdmp
96         WRITE(numout,*) '      Damping file name               cn_resto  = ', cn_resto
97         WRITE(numout,*)
98      ENDIF
99      !
100      IF( ln_dyndmp ) THEN
101         !                                   !==   allocate the data arrays   ==!
102         IF( dyn_dmp_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'dyn_dmp_init: unable to allocate arrays' )
103         !
104         SELECT CASE ( nn_zdmp )             !==   control print of vertical option   ==!
105         CASE ( 0    )   ;   IF(lwp) WRITE(numout,*) '   momentum damping throughout the water column'
106         CASE ( 1    )   ;   IF(lwp) WRITE(numout,*) '   no momentum damping in the turbocline (avt > 5 cm2/s)'
107         CASE ( 2    )   ;   IF(lwp) WRITE(numout,*) '   no momentum damping in the mixed layer'
108         CASE DEFAULT
109            WRITE(ctmp1,*) '          bad flag value for nn_zdmp = ', nn_zdmp
110            CALL ctl_stop(ctmp1)
111         END SELECT
112         !
113         IF( .NOT. ln_uvd_dyndmp ) THEN      ! force the initialization of U & V current data for damping
114            CALL ctl_warn( 'dyn_dmp_init: U & V current read data not initialized, we force ln_uvd_dyndmp=T' )
115            CALL dta_uvd_init( ld_dyndmp=ln_dyndmp )
116         ENDIF
117         !
118         utrdmp(:,:,:) = 0._wp               ! internal damping trends
119         vtrdmp(:,:,:) = 0._wp
120         !
121         !Read in mask from file
122         CALL iom_open ( cn_resto, imask)
123         CALL iom_get  ( imask, jpdom_autoglo, 'resto', resto)
124         CALL iom_close( imask )
125      ENDIF
126      !
127   END SUBROUTINE dyn_dmp_init
128
129
130   SUBROUTINE dyn_dmp( kt, Kbb, Kmm, puu, pvv, Krhs )
131      !!----------------------------------------------------------------------
132      !!                   ***  ROUTINE dyn_dmp  ***
133      !!                 
134      !! ** Purpose :   Compute the momentum trends due to a newtonian damping
135      !!      of the ocean velocities towards the given data and add it to the
136      !!      general momentum trends.
137      !!
138      !! ** Method  :   Compute Newtonian damping towards u_dta and v_dta
139      !!      and add to the general momentum trends:
140      !!                     puu(Krhs) = puu(Krhs) + resto_uv * (u_dta - puu(Kbb))
141      !!                     pvv(Krhs) = pvv(Krhs) + resto_uv * (v_dta - pvv(Kbb))
142      !!      The trend is computed either throughout the water column
143      !!      (nn_zdmp=0), where the vertical mixing is weak (nn_zdmp=1) or
144      !!      below the well mixed layer (nn_zdmp=2)
145      !!
146      !! ** Action  : - (puu(:,:,:,Krhs),pvv(:,:,:,Krhs))   momentum trends updated with the damping trend
147      !!----------------------------------------------------------------------
148      INTEGER                             , INTENT(in   ) ::   kt             ! ocean time-step index
149      INTEGER                             , INTENT(in   ) ::   Kbb, Kmm, Krhs ! ocean time level indices
150      REAL(wp), DIMENSION(jpi,jpj,jpk,jpt), INTENT(inout) ::   puu, pvv       ! ocean velocities and RHS of momentum equation
151      !!
152      INTEGER  ::   ji, jj, jk   ! dummy loop indices
153      REAL(wp) ::   zua, zva     ! local scalars
154      REAL(wp), DIMENSION(jpi,jpj,jpk,2) ::   zuv_dta   ! Read in data
155      !!----------------------------------------------------------------------
156      !
157      IF( ln_timing )   CALL timing_start( 'dyn_dmp' )
158      !
159      !
160      !                           !==   read and interpolate U & V current data at kt   ==!
161      CALL dta_uvd( kt, Kmm, zuv_dta ) !!! NOTE: This subroutine must be altered for use outside
162                                  !!!       the C1D context (use of U,V grid variables)
163      !
164      SELECT CASE ( nn_zdmp )     !==   Calculate/add Newtonian damping to the momentum trend   ==!
165      !
166      CASE( 0 )                   ! Newtonian damping throughout the water column
167         DO_3D_00_00( 1, jpkm1 )
168            zua = resto_uv(ji,jj,jk) * ( zuv_dta(ji,jj,jk,1) - puu(ji,jj,jk,Kbb) )
169            zva = resto_uv(ji,jj,jk) * ( zuv_dta(ji,jj,jk,2) - pvv(ji,jj,jk,Kbb) )
170            puu(ji,jj,jk,Krhs) = puu(ji,jj,jk,Krhs) + zua
171            pvv(ji,jj,jk,Krhs) = pvv(ji,jj,jk,Krhs) + zva
172            utrdmp(ji,jj,jk) = zua           ! save the trends
173            vtrdmp(ji,jj,jk) = zva     
174         END_3D
175         !
176      CASE ( 1 )                  ! no damping above the turbocline (avt > 5 cm2/s)
177         DO_3D_00_00( 1, jpkm1 )
178            IF( avt(ji,jj,jk) <= avt_c ) THEN
179               zua = resto_uv(ji,jj,jk) * ( zuv_dta(ji,jj,jk,1) - puu(ji,jj,jk,Kbb) )
180               zva = resto_uv(ji,jj,jk) * ( zuv_dta(ji,jj,jk,2) - pvv(ji,jj,jk,Kbb) )
181            ELSE
182               zua = 0._wp
183               zva = 0._wp 
184            ENDIF
185            puu(ji,jj,jk,Krhs) = puu(ji,jj,jk,Krhs) + zua
186            pvv(ji,jj,jk,Krhs) = pvv(ji,jj,jk,Krhs) + zva
187            utrdmp(ji,jj,jk) = zua           ! save the trends
188            vtrdmp(ji,jj,jk) = zva
189         END_3D
190         !
191      CASE ( 2 )                  ! no damping in the mixed layer
192         DO_3D_00_00( 1, jpkm1 )
193            IF( gdept(ji,jj,jk,Kmm) >= hmlp (ji,jj) ) THEN
194               zua = resto_uv(ji,jj,jk) * ( zuv_dta(ji,jj,jk,1) - puu(ji,jj,jk,Kbb) )
195               zva = resto_uv(ji,jj,jk) * ( zuv_dta(ji,jj,jk,2) - pvv(ji,jj,jk,Kbb) )
196            ELSE
197               zua = 0._wp
198               zva = 0._wp 
199            ENDIF
200            puu(ji,jj,jk,Krhs) = puu(ji,jj,jk,Krhs) + zua
201            pvv(ji,jj,jk,Krhs) = pvv(ji,jj,jk,Krhs) + zva
202            utrdmp(ji,jj,jk) = zua           ! save the trends
203            vtrdmp(ji,jj,jk) = zva
204         END_3D
205         !
206      END SELECT
207      !
208      !                           ! Control print
209      IF( sn_cfctl%l_prtctl   )   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' dmp  - Ua: ', mask1=umask,   &
210         &                                      tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
211      !
212      !
213      IF( ln_timing )   CALL timing_stop( 'dyn_dmp')
214      !
215   END SUBROUTINE dyn_dmp
216
217   !!======================================================================
218END MODULE dyndmp
Note: See TracBrowser for help on using the repository browser.