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.
tradmp.F90 in trunk/NEMO/OPA_SRC/TRA – NEMO

source: trunk/NEMO/OPA_SRC/TRA/tradmp.F90 @ 1517

Last change on this file since 1517 was 1438, checked in by rblod, 15 years ago

Merge VVL branch with the trunk (act II), see ticket #429

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 34.1 KB
Line 
1MODULE tradmp
2   !!======================================================================
3   !!                       ***  MODULE  tradmp  ***
4   !! Ocean physics: internal restoring trend on active tracers (T and S)
5   !!======================================================================
6   !! History :  5.0  !  91-03  (O. Marti, G. Madec)  Original code
7   !!                 !  92-06  (M. Imbard)  doctor norme
8   !!                 !  96-01  (G. Madec)  statement function for e3
9   !!                 !  97-05  (G. Madec)  macro-tasked on jk-slab
10   !!                 !  98-07  (M. Imbard, G. Madec) ORCA version
11   !!            7.0  !  01-02  (M. Imbard)  cofdis, Original code
12   !!            8.1  !  01-02  (G. Madec, E. Durand)  cleaning
13   !!            8.5  !  02-08  (G. Madec, E. Durand)  free form + modules
14   !!----------------------------------------------------------------------
15#if   defined key_tradmp   ||   defined key_esopa
16   !!----------------------------------------------------------------------
17   !!   key_tradmp                                         internal damping
18   !!----------------------------------------------------------------------
19   !!----------------------------------------------------------------------
20   !!   tra_dmp      : update the tracer trend with the internal damping
21   !!   tra_dmp_init : initialization, namlist read, parameters control
22   !!   dtacof_zoom  : restoring coefficient for zoom domain
23   !!   dtacof       : restoring coefficient for global domain
24   !!   cofdis       : compute the distance to the coastline
25   !!----------------------------------------------------------------------
26   USE oce             ! ocean dynamics and tracers variables
27   USE dom_oce         ! ocean space and time domain variables
28   USE trdmod          ! ocean active tracers trends
29   USE trdmod_oce      ! ocean variables trends
30   USE zdf_oce         ! ocean vertical physics
31   USE in_out_manager  ! I/O manager
32   USE phycst          ! Define parameters for the routines
33   USE dtatem          ! temperature data
34   USE dtasal          ! salinity data
35   USE zdfmxl          ! mixed layer depth
36   USE lib_mpp         ! distribued memory computing
37   USE prtctl          ! Print control
38
39   IMPLICIT NONE
40   PRIVATE
41
42   PUBLIC tra_dmp      ! routine called by step.F90
43
44#if ! defined key_agrif
45   LOGICAL, PUBLIC, PARAMETER ::   lk_tradmp = .TRUE.     !: internal damping flag
46#else
47   LOGICAL, PUBLIC            ::   lk_tradmp = .TRUE.     !: internal damping flag
48#endif
49   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   resto    !: restoring coeff. on T and S (s-1)
50   
51   !!* newtonian damping namelist (mandmp)
52   INTEGER  ::   ndmp   =   -1    ! = 0/-1/'latitude' for damping over T and S
53   INTEGER  ::   ndmpf  =    2    ! = 1 create a damping.coeff NetCDF file
54   INTEGER  ::   nmldmp =    0    ! = 0/1/2 flag for damping in the mixed layer
55   REAL(wp) ::   sdmp   =   50.   ! surface time scale for internal damping (days)
56   REAL(wp) ::   bdmp   =  360.   ! bottom time scale for internal damping (days)
57   REAL(wp) ::   hdmp   =  800.   ! depth of transition between sdmp and bdmp (meters)
58
59   !! * Substitutions
60#  include "domzgr_substitute.h90"
61#  include "vectopt_loop_substitute.h90"
62   !!----------------------------------------------------------------------
63   !!   OPA 9.0 , LOCEAN-IPSL (2006)
64   !! $Id$
65   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
66   !!----------------------------------------------------------------------
67
68CONTAINS
69
70   SUBROUTINE tra_dmp( kt )
71      !!----------------------------------------------------------------------
72      !!                   ***  ROUTINE tra_dmp  ***
73      !!                 
74      !! ** Purpose :   Compute the tracer trend due to a newtonian damping
75      !!      of the tracer field towards given data field and add it to the
76      !!      general tracer trends.
77      !!
78      !! ** Method  :   Newtonian damping towards t_dta and s_dta computed
79      !!      and add to the general tracer trends:
80      !!                     ta = ta + resto * (t_dta - tb)
81      !!                     sa = sa + resto * (s_dta - sb)
82      !!         The trend is computed either throughout the water column
83      !!      (nlmdmp=0) or in area of weak vertical mixing (nlmdmp=1) or
84      !!      below the well mixed layer (nlmdmp=2)
85      !!
86      !! ** Action  : - update the tracer trends (ta,sa) with the newtonian
87      !!                damping trends.
88      !!              - save the trends in (ttrd,strd) ('key_trdtra')
89      !!----------------------------------------------------------------------
90      USE oce, ONLY :   ztrdt => ua   ! use ua as 3D workspace   
91      USE oce, ONLY :   ztrds => va   ! use va as 3D workspace   
92      !!
93      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
94      !!
95      INTEGER  ::   ji, jj, jk            ! dummy loop indices
96      REAL(wp) ::   ztest, zta, zsa       ! temporary scalars
97      !!----------------------------------------------------------------------
98
99      IF( kt == nit000 )   CALL tra_dmp_init      ! Initialization
100
101      IF( l_trdtra )   THEN                       ! Save ta and sa trends
102         ztrdt(:,:,:) = ta(:,:,:) 
103         ztrds(:,:,:) = sa(:,:,:) 
104      ENDIF
105
106      ! 1. Newtonian damping trends on tracer fields
107      ! --------------------------------------------
108      !    compute the newtonian damping trends depending on nmldmp
109
110      SELECT CASE ( nmldmp )
111      !
112      CASE( 0 )                ! newtonian damping throughout the water column
113         DO jk = 1, jpkm1
114            DO jj = 2, jpjm1
115               DO ji = fs_2, fs_jpim1   ! vector opt.
116                  zta = resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - tb(ji,jj,jk) )
117                  zsa = resto(ji,jj,jk) * ( s_dta(ji,jj,jk) - sb(ji,jj,jk) )
118                  ! add the trends to the general tracer trends
119                  ta(ji,jj,jk) = ta(ji,jj,jk) + zta
120                  sa(ji,jj,jk) = sa(ji,jj,jk) + zsa
121                  ! save the salinity trend (used in flx to close the salt budget)
122               END DO
123            END DO
124         END DO
125         !
126      CASE ( 1 )                ! no damping in the turbocline (avt > 5 cm2/s)
127         DO jk = 1, jpkm1
128            DO jj = 2, jpjm1
129               DO ji = fs_2, fs_jpim1   ! vector opt.
130                  ztest = avt(ji,jj,jk) - 5.e-4
131                  IF( ztest < 0. ) THEN
132                     zta = resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - tb(ji,jj,jk) )
133                     zsa = resto(ji,jj,jk) * ( s_dta(ji,jj,jk) - sb(ji,jj,jk) )
134                  ELSE
135                     zta = 0.e0
136                     zsa = 0.e0
137                  ENDIF
138                  ! add the trends to the general tracer trends
139                  ta(ji,jj,jk) = ta(ji,jj,jk) + zta
140                  sa(ji,jj,jk) = sa(ji,jj,jk) + zsa
141                  ! save the salinity trend (used in flx to close the salt budget)
142               END DO
143            END DO
144         END DO
145         !
146      CASE ( 2 )                ! no damping in the mixed layer
147         DO jk = 1, jpkm1
148            DO jj = 2, jpjm1
149               DO ji = fs_2, fs_jpim1   ! vector opt.
150                  IF( fsdept(ji,jj,jk) >= hmlp (ji,jj) ) THEN
151                     zta = resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - tb(ji,jj,jk) )
152                     zsa = resto(ji,jj,jk) * ( s_dta(ji,jj,jk) - sb(ji,jj,jk) )
153                  ELSE
154                     zta = 0.e0
155                     zsa = 0.e0
156                  ENDIF
157                  ! add the trends to the general tracer trends
158                  ta(ji,jj,jk) = ta(ji,jj,jk) + zta
159                  sa(ji,jj,jk) = sa(ji,jj,jk) + zsa
160                  ! save the salinity trend (used in flx to close the salt budget)
161               END DO
162            END DO
163         END DO
164         !
165      END SELECT
166
167      IF( l_trdtra )   THEN          ! save the damping tracer trends for diagnostic
168         ztrdt(:,:,:) = ta(:,:,:) - ztrdt(:,:,:)
169         ztrds(:,:,:) = sa(:,:,:) - ztrds(:,:,:)
170         CALL trd_mod(ztrdt, ztrds, jptra_trd_dmp, 'TRA', kt)
171      ENDIF
172      !                              ! Control print
173      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ta, clinfo1=' dmp  - Ta: ', mask1=tmask,   &
174         &                       tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
175      !
176   END SUBROUTINE tra_dmp
177
178
179   SUBROUTINE tra_dmp_init
180      !!----------------------------------------------------------------------
181      !!                  ***  ROUTINE tra_dmp_init  ***
182      !!
183      !! ** Purpose :   Initialization for the newtonian damping
184      !!
185      !! ** Method  :   read the nammbf namelist and check the parameters
186      !!      called by tra_dmp at the first timestep (nit000)
187      !!----------------------------------------------------------------------
188      NAMELIST/namtdp/ ndmp, ndmpf, nmldmp, sdmp, bdmp, hdmp
189      !!----------------------------------------------------------------------
190
191      REWIND ( numnam )                  ! Read Namelist namtdp : temperature and salinity damping term
192      READ   ( numnam, namtdp )
193      IF( lzoom )   nmldmp = 0           ! restoring to climatology at closed north or south boundaries
194
195      IF(lwp) THEN                       ! Namelist print
196         WRITE(numout,*)
197         WRITE(numout,*) 'tra_dmp : T and S newtonian damping'
198         WRITE(numout,*) '~~~~~~~'
199         WRITE(numout,*) '       Namelist namtdp : set damping parameter'
200         WRITE(numout,*) '          T and S damping option         ndmp   = ', ndmp
201         WRITE(numout,*) '          create a damping.coeff file    ndmpf  = ', ndmpf
202         WRITE(numout,*) '          mixed layer damping option     nmldmp = ', nmldmp, '(zoom: forced to 0)'
203         WRITE(numout,*) '          surface time scale (days)      sdmp   = ', sdmp
204         WRITE(numout,*) '          bottom time scale (days)       bdmp   = ', bdmp
205         WRITE(numout,*) '          depth of transition (meters)   hdmp   = ', hdmp
206      ENDIF
207
208      SELECT CASE ( ndmp )
209      CASE (  -1  )   ;   IF(lwp) WRITE(numout,*) '          tracer damping in the Med & Red seas only'
210      CASE ( 1:90 )   ;   IF(lwp) WRITE(numout,*) '          tracer damping poleward of', ndmp, ' degrees'
211      CASE DEFAULT
212         WRITE(ctmp1,*) '          bad flag value for ndmp = ', ndmp
213         CALL ctl_stop(ctmp1)
214      END SELECT
215
216      SELECT CASE ( nmldmp )
217      CASE ( 0 )   ;   IF(lwp) WRITE(numout,*) '          tracer damping throughout the water column'
218      CASE ( 1 )   ;   IF(lwp) WRITE(numout,*) '          no tracer damping in the turbocline (avt > 5 cm2/s)'
219      CASE ( 2 )   ;   IF(lwp) WRITE(numout,*) '          no tracer damping in the mixed layer'
220      CASE DEFAULT
221         WRITE(ctmp1,*) '          bad flag value for nmldmp = ', nmldmp
222         CALL ctl_stop(ctmp1)
223      END SELECT
224
225      IF( .NOT.lk_dtasal .OR. .NOT.lk_dtatem )   &
226         &   CALL ctl_stop( 'no temperature and/or salinity data define key_dtatem and key_dtasal' )
227
228      !                          ! Damping coefficients initialization
229      IF( lzoom ) THEN   ;   CALL dtacof_zoom
230      ELSE               ;   CALL dtacof
231      ENDIF
232      !
233   END SUBROUTINE tra_dmp_init
234
235
236   SUBROUTINE dtacof_zoom
237      !!----------------------------------------------------------------------
238      !!                  ***  ROUTINE dtacof_zoom  ***
239      !!
240      !! ** Purpose :   Compute the damping coefficient for zoom domain
241      !!
242      !! ** Method  : - set along closed boundary due to zoom a damping over
243      !!      6 points with a max time scale of 5 days.
244      !!              - ORCA arctic/antarctic zoom: set the damping along
245      !!      south/north boundary over a latitude strip.
246      !!
247      !! ** Action  : - resto, the damping coeff. for T and S
248      !!----------------------------------------------------------------------
249      INTEGER  ::   ji, jj, jk, jn              ! dummy loop indices
250      REAL(wp) ::   zlat, zlat0, zlat1, zlat2   ! temporary scalar
251      REAL(wp), DIMENSION(6)  ::   zfact        ! temporary workspace
252      !!----------------------------------------------------------------------
253
254      zfact(1) =  1.
255      zfact(2) =  1. 
256      zfact(3) = 11./12.
257      zfact(4) =  8./12.
258      zfact(5) =  4./12.
259      zfact(6) =  1./12.
260      zfact(:) = zfact(:) / ( 5. * rday )    ! 5 days max restoring time scale
261
262      resto(:,:,:) = 0.e0
263
264      ! damping along the forced closed boundary over 6 grid-points
265      DO jn = 1, 6
266         IF( lzoom_w )   resto( mi0(jn+jpizoom):mi1(jn+jpizoom), : , : )                    = zfact(jn)   ! west  closed
267         IF( lzoom_s )   resto( : , mj0(jn+jpjzoom):mj1(jn+jpjzoom), : )                    = zfact(jn)   ! south closed
268         IF( lzoom_e )   resto( mi0(jpiglo+jpizoom-1-jn):mi1(jpiglo+jpizoom-1-jn) , : , : ) = zfact(jn)   ! east  closed
269         IF( lzoom_n )   resto( : , mj0(jpjglo+jpjzoom-1-jn):mj1(jpjglo+jpjzoom-1-jn) , : ) = zfact(jn)   ! north closed
270      END DO
271
272
273      IF( lzoom_arct .AND. lzoom_anta ) THEN
274         !
275         ! ====================================================
276         !  ORCA configuration : arctic zoom or antarctic zoom
277         ! ====================================================
278
279         IF(lwp) WRITE(numout,*)
280         IF(lwp .AND. lzoom_arct ) WRITE(numout,*) '              dtacof_zoom : ORCA    Arctic zoom'
281         IF(lwp .AND. lzoom_arct ) WRITE(numout,*) '              dtacof_zoom : ORCA Antarctic zoom'
282         IF(lwp) WRITE(numout,*)
283
284         ! ... Initialization :
285         !     zlat0 : latitude strip where resto decreases
286         !     zlat1 : resto = 1 before zlat1
287         !     zlat2 : resto decreases from 1 to 0 between zlat1 and zlat2
288         resto(:,:,:) = 0.e0
289         zlat0 = 10.
290         zlat1 = 30.
291         zlat2 = zlat1 + zlat0
292
293         ! ... Compute arrays resto ; value for internal damping : 5 days
294         DO jk = 2, jpkm1
295            DO jj = 1, jpj
296               DO ji = 1, jpi
297                  zlat = ABS( gphit(ji,jj) )
298                  IF ( zlat1 <= zlat .AND. zlat <= zlat2 ) THEN
299                     resto(ji,jj,jk) = 0.5 * ( 1./(5.*rday) ) *   &
300                        ( 1. - cos(rpi*(zlat2-zlat)/zlat0) ) 
301                  ELSE IF ( zlat < zlat1 ) THEN
302                     resto(ji,jj,jk) = 1./(5.*rday)
303                  ENDIF
304               END DO
305            END DO
306         END DO
307         !
308      ENDIF
309
310      ! ... Mask resto array
311      resto(:,:,:) = resto(:,:,:) * tmask(:,:,:)
312      !
313   END SUBROUTINE dtacof_zoom
314
315
316   SUBROUTINE dtacof
317      !!----------------------------------------------------------------------
318      !!                  ***  ROUTINE dtacof  ***
319      !!
320      !! ** Purpose :   Compute the damping coefficient
321      !!
322      !! ** Method  :   Arrays defining the damping are computed for each grid
323      !!      point for temperature and salinity (resto)
324      !!      Damping depends on distance to coast, depth and latitude
325      !!
326      !! ** Action  : - resto, the damping coeff. for T and S
327      !!----------------------------------------------------------------------
328      USE iom
329      USE ioipsl
330      !!
331      INTEGER ::   ji, jj, jk                   ! dummy loop indices
332      INTEGER ::   ii0, ii1, ij0, ij1           !    "          "
333      INTEGER ::   inum0                        ! logical unit for file restoring damping term
334      INTEGER ::   icot                         ! logical unit for file distance to the coast
335      REAL(wp) ::   zinfl, zlon                 ! temporary scalars
336      REAL(wp) ::   zlat, zlat0, zlat1, zlat2   !    "         "
337      REAL(wp) ::   zsdmp, zbdmp                !    "         "
338      REAL(wp), DIMENSION(jpk)         ::   zhfac
339      REAL(wp), DIMENSION(jpi,jpj)     ::   zmrs
340      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zdct
341      !!----------------------------------------------------------------------
342
343      ! ====================================
344      !  ORCA configuration : global domain
345      ! ====================================
346
347      IF(lwp) WRITE(numout,*)
348      IF(lwp) WRITE(numout,*) '              dtacof : Global domain of ORCA'
349      IF(lwp) WRITE(numout,*) '              ------------------------------'
350
351      ! ... Initialization :
352      !   zdct()      : distant to the coastline
353      !   resto()     : array of restoring coeff. on T and S
354
355      resto(:,:,:) = 0.e0
356
357      IF ( ndmp > 0 ) THEN
358
359         !    ------------------------------------
360         !     Damping poleward of 'ndmp' degrees
361         !    ------------------------------------
362
363         IF(lwp) WRITE(numout,*)
364         IF(lwp) WRITE(numout,*) '              Damping poleward of ', ndmp,' deg.'
365         IF(lwp) WRITE(numout,*)
366
367         ! ... Distance to coast (zdct)
368
369         IF(lwp) WRITE(numout,*)
370         IF(lwp) WRITE(numout,*) ' dtacof : distance to coast file'
371         CALL iom_open ( 'dist.coast.nc', icot, ldstop = .FALSE. )
372         IF( icot > 0 ) THEN
373            CALL iom_get ( icot, jpdom_data, 'Tcoast', zdct )
374            CALL iom_close (icot)
375         ELSE
376            !   ... Compute and save the distance-to-coast array (output in zdct)
377            CALL cofdis( zdct )
378         ENDIF
379
380         ! ... Compute arrays resto
381         !      zinfl : distance of influence for damping term
382         !      zlat0 : latitude strip where resto decreases
383         !      zlat1 : resto = 0 between -zlat1 and zlat1
384         !      zlat2 : resto increases from 0 to 1 between |zlat1| and |zlat2|
385         !          and resto = 1 between |zlat2| and 90 deg.
386         zinfl = 1000.e3
387         zlat0 = 10
388         zlat1 = ndmp
389         zlat2 = zlat1 + zlat0
390
391         DO jj = 1, jpj
392            DO ji = 1, jpi
393               zlat = ABS( gphit(ji,jj) )
394               IF ( zlat1 <= zlat .AND. zlat <= zlat2 ) THEN
395                  resto(ji,jj,1) = 0.5 * ( 1. - cos(rpi*(zlat-zlat1)/zlat0 ) )
396               ELSEIF ( zlat > zlat2 ) THEN
397                  resto(ji,jj,1) = 1.
398               ENDIF
399            END DO
400         END DO
401
402         !   ... North Indian ocean (20N/30N x 45E/100E) : resto=0
403         IF ( ndmp == 20 ) THEN
404            DO jj = 1, jpj
405               DO ji = 1, jpi
406                  zlat = gphit(ji,jj)
407                  zlon = MOD( glamt(ji,jj), 360. )
408                  IF ( zlat1 < zlat .AND. zlat < zlat2 .AND.   &
409                     45.  < zlon .AND. zlon < 100. ) THEN
410                     resto(ji,jj,1) = 0.
411                  ENDIF
412               END DO
413            END DO
414         ENDIF
415
416         zsdmp = 1./(sdmp * rday)
417         zbdmp = 1./(bdmp * rday)
418         DO jk = 2, jpkm1
419            DO jj = 1, jpj
420               DO ji = 1, jpi
421                  zdct(ji,jj,jk) = MIN( zinfl, zdct(ji,jj,jk) )
422                  !   ... Decrease the value in the vicinity of the coast
423                  resto(ji,jj,jk) = resto(ji,jj,1) * 0.5 * ( 1. - COS( rpi*zdct(ji,jj,jk)/zinfl) )
424                  !   ... Vertical variation from zsdmp (sea surface) to zbdmp (bottom)
425                  resto(ji,jj,jk) = resto(ji,jj,jk)      * ( zbdmp + (zsdmp-zbdmp)*EXP(-fsdept(ji,jj,jk)/hdmp) )
426               END DO
427            END DO
428         END DO
429         !
430      ENDIF
431
432
433      IF( cp_cfg == "orca" .AND. ( ndmp > 0 .OR. ndmp == -1 ) ) THEN
434
435         !                                         ! =========================
436         !                                         !  Med and Red Sea damping
437         !                                         ! =========================
438         IF(lwp)WRITE(numout,*)
439         IF(lwp)WRITE(numout,*) '              ORCA configuration: Damping in Med and Red Seas'
440
441
442         zmrs(:,:) = 0.e0                             ! damping term on the Med or Red Sea
443
444         SELECT CASE ( jp_cfg )
445         !                                           ! =======================
446         CASE ( 4 )                                  !  ORCA_R4 configuration
447            !                                        ! =======================
448            ! Mediterranean Sea
449            ij0 =  50   ;   ij1 =  56
450            ii0 =  81   ;   ii1 =  91   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0
451            ij0 =  50   ;   ij1 =  55
452            ii0 =  75   ;   ii1 =  80   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0
453            ij0 =  52   ;   ij1 =  53
454            ii0 =  70   ;   ii1 =  74   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0
455            ! Smooth transition from 0 at surface to 1./rday at the 18th level in Med and Red Sea
456            DO jk = 1, 17
457               zhfac (jk) = 0.5*( 1.- COS( rpi*(jk-1)/16. ) ) / rday
458            END DO
459            DO jk = 18, jpkm1
460               zhfac (jk) = 1./rday
461            END DO
462            !                                        ! =======================
463         CASE ( 2 )                                  !  ORCA_R2 configuration
464            !                                        ! =======================
465            ! Mediterranean Sea
466            ij0 =  96   ;   ij1 = 110
467            ii0 = 157   ;   ii1 = 181   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0
468            ij0 = 100   ;   ij1 = 110
469            ii0 = 144   ;   ii1 = 156   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0
470            ij0 = 100   ;   ij1 = 103
471            ii0 = 139   ;   ii1 = 143   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0
472            ! Decrease before Gibraltar Strait
473            ij0 = 101   ;   ij1 = 102
474            ii0 = 139   ;   ii1 = 141   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.e0
475            ii0 = 142   ;   ii1 = 142   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 / 90.e0
476            ii0 = 143   ;   ii1 = 143   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.40e0
477            ii0 = 144   ;   ii1 = 144   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.75e0
478            ! Red Sea
479            ij0 =  87   ;   ij1 =  96
480            ii0 = 147   ;   ii1 = 163   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0
481            ! Decrease before Bab el Mandeb Strait
482            ij0 =  91   ;   ij1 =  91
483            ii0 = 153   ;   ii1 = 160   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.80e0
484            ij0 =  90   ;   ij1 =  90
485            ii0 = 153   ;   ii1 = 160   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.40e0
486            ij0 =  89   ;   ij1 =  89
487            ii0 = 158   ;   ii1 = 160   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 / 90.e0
488            ij0 =  88   ;   ij1 =  88
489            ii0 = 160   ;   ii1 = 163   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.e0
490            ! Smooth transition from 0 at surface to 1./rday at the 18th level in Med and Red Sea
491            DO jk = 1, 17
492               zhfac (jk) = 0.5*( 1.- COS( rpi*(jk-1)/16. ) ) / rday
493            END DO
494            DO jk = 18, jpkm1
495               zhfac (jk) = 1./rday
496            END DO
497            !                                        ! =======================
498         CASE ( 05 )                                 !  ORCA_R05 configuration
499            !                                        ! =======================
500            ! Mediterranean Sea
501            ii0 = 568   ;   ii1 = 574 
502            ij0 = 324   ;   ij1 = 333   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0
503            ii0 = 575   ;   ii1 = 658
504            ij0 = 314   ;   ij1 = 366   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0
505            ! Black Sea (remaining part
506            ii0 = 641   ;   ii1 = 651
507            ij0 = 367   ;   ij1 = 372   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0
508            ! Decrease before Gibraltar Strait
509            ij0 = 324   ;   ij1 = 333
510            ii0 = 565   ;   ii1 = 565   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0 / 90.e0
511            ii0 = 566   ;   ii1 = 566   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.40
512            ii0 = 567   ;   ii1 = 567   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.75
513            ! Red Sea
514            ii0 = 641   ;   ii1 = 665
515            ij0 = 270   ;   ij1 = 310   ;   zmrs( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 1.e0
516            ! Decrease before Bab el Mandeb Strait
517            ii0 = 666   ;   ii1 = 675
518            ij0 = 270   ;   ij1 = 290   
519            DO ji = mi0(ii0), mi1(ii1)
520               zmrs( ji , mj0(ij0):mj1(ij1) ) = 0.1 * ABS( FLOAT(ji - mi1(ii1)) )
521            END DO
522            zsdmp = 1./(sdmp * rday)
523            zbdmp = 1./(bdmp * rday)
524            DO jk = 1, jpk
525               zhfac (jk) = ( zbdmp + (zsdmp-zbdmp) * EXP(-fsdept(1,1,jk)/hdmp) )
526            END DO
527            !                                       ! ========================
528         CASE ( 025 )                               !  ORCA_R025 configuration
529            !                                       ! ========================
530            CALL ctl_stop( ' Not yet implemented in ORCA_R025' )
531            !
532         END SELECT
533
534         DO jk = 1, jpkm1
535            resto(:,:,jk) = zmrs(:,:) * zhfac(jk) + ( 1. - zmrs(:,:) ) * resto(:,:,jk)
536         END DO
537
538         ! Mask resto array and set to 0 first and last levels
539         resto(:,:, : ) = resto(:,:,:) * tmask(:,:,:)
540         resto(:,:, 1 ) = 0.e0
541         resto(:,:,jpk) = 0.e0
542
543      ELSE
544         !    ------------
545         !     No damping
546         !    ------------
547         CALL ctl_stop( 'Choose a correct value of ndmp or DO NOT defined key_tradmp' )
548      ENDIF
549
550      !    ----------------------------
551      !     Create Print damping array
552      !    ----------------------------
553
554      ! ndmpf   : = 1 create a damping.coeff NetCDF file
555
556      IF( ndmpf == 1 ) THEN
557         IF(lwp) WRITE(numout,*) '              create damping.coeff.nc file'
558         CALL iom_open  ( 'damping.coeff', inum0, ldwrt = .TRUE., kiolib = jprstlib )
559         CALL iom_rstput( 0, 0, inum0, 'Resto', resto )
560         CALL iom_close ( inum0 )
561      ENDIF
562      !
563   END SUBROUTINE dtacof
564
565
566   SUBROUTINE cofdis( pdct )
567      !!----------------------------------------------------------------------
568      !!                 ***  ROUTINE cofdis  ***
569      !!
570      !! ** Purpose :   Compute the distance between ocean T-points and the
571      !!      ocean model coastlines. Save the distance in a NetCDF file.
572      !!
573      !! ** Method  :   For each model level, the distance-to-coast is
574      !!      computed as follows :
575      !!       - The coastline is defined as the serie of U-,V-,F-points
576      !!      that are at the ocean-land bound.
577      !!       - For each ocean T-point, the distance-to-coast is then
578      !!      computed as the smallest distance (on the sphere) between the
579      !!      T-point and all the coastline points.
580      !!       - For land T-points, the distance-to-coast is set to zero.
581      !!      C A U T I O N : Computation not yet implemented in mpp case.
582      !!
583      !! ** Action  : - pdct, distance to the coastline (argument)
584      !!              - NetCDF file 'dist.coast.nc'
585      !!----------------------------------------------------------------------
586      USE ioipsl      ! IOipsl librairy
587      !!
588      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( out ) ::   pdct   ! distance to the coastline
589      !!
590      INTEGER ::   ji, jj, jk, jl      ! dummy loop indices
591      INTEGER ::   iju, ijt            ! temporary integers
592      INTEGER ::   icoast, itime
593      INTEGER ::   icot         ! logical unit for file distance to the coast
594      LOGICAL, DIMENSION(jpi,jpj) ::   llcotu, llcotv, llcotf   ! ???
595      CHARACTER (len=32) ::   clname
596      REAL(wp) ::   zdate0
597      REAL(wp), DIMENSION(jpi,jpj)   ::   zxt, zyt, zzt, zmask   ! cartesian coordinates for T-points
598      REAL(wp), DIMENSION(3*jpi*jpj) ::   zxc, zyc, zzc, zdis    ! temporary workspace
599      !!----------------------------------------------------------------------
600
601      ! 0. Initialization
602      ! -----------------
603      IF(lwp) WRITE(numout,*)
604      IF(lwp) WRITE(numout,*) 'cofdis : compute the distance to coastline'
605      IF(lwp) WRITE(numout,*) '~~~~~~'
606      IF(lwp) WRITE(numout,*)
607      IF( lk_mpp ) &
608           & CALL ctl_stop('         Computation not yet implemented with key_mpp_...', &
609           &               '         Rerun the code on another computer or ', &
610           &               '         create the "dist.coast.nc" file using IDL' )
611
612      pdct(:,:,:) = 0.e0
613      zxt(:,:) = cos( rad * gphit(:,:) ) * cos( rad * glamt(:,:) )
614      zyt(:,:) = cos( rad * gphit(:,:) ) * sin( rad * glamt(:,:) )
615      zzt(:,:) = sin( rad * gphit(:,:) )
616
617
618      ! 1. Loop on vertical levels
619      ! --------------------------
620      !                                                ! ===============
621      DO jk = 1, jpkm1                                 ! Horizontal slab
622         !                                             ! ===============
623         ! Define the coastline points (U, V and F)
624         DO jj = 2, jpjm1
625            DO ji = 2, jpim1
626               zmask(ji,jj) =  ( tmask(ji,jj+1,jk) + tmask(ji+1,jj+1,jk) &
627                   &           + tmask(ji,jj  ,jk) + tmask(ji+1,jj  ,jk) )
628               llcotu(ji,jj) = ( tmask(ji,jj,  jk) + tmask(ji+1,jj  ,jk) == 1. ) 
629               llcotv(ji,jj) = ( tmask(ji,jj  ,jk) + tmask(ji  ,jj+1,jk) == 1. ) 
630               llcotf(ji,jj) = ( zmask(ji,jj) > 0. ) .AND. ( zmask(ji,jj) < 4. )
631            END DO
632         END DO
633
634         ! Lateral boundaries conditions
635         llcotu(:, 1 ) = umask(:,  2  ,jk) == 1
636         llcotu(:,jpj) = umask(:,jpjm1,jk) == 1
637         llcotv(:, 1 ) = vmask(:,  2  ,jk) == 1
638         llcotv(:,jpj) = vmask(:,jpjm1,jk) == 1
639         llcotf(:, 1 ) = fmask(:,  2  ,jk) == 1
640         llcotf(:,jpj) = fmask(:,jpjm1,jk) == 1
641
642         IF( nperio == 1 .OR. nperio == 4 .OR. nperio == 6 ) THEN
643            llcotu( 1 ,:) = llcotu(jpim1,:)
644            llcotu(jpi,:) = llcotu(  2  ,:)
645            llcotv( 1 ,:) = llcotv(jpim1,:)
646            llcotv(jpi,:) = llcotv(  2  ,:)
647            llcotf( 1 ,:) = llcotf(jpim1,:)
648            llcotf(jpi,:) = llcotf(  2  ,:)
649         ELSE
650            llcotu( 1 ,:) = umask(  2  ,:,jk) == 1
651            llcotu(jpi,:) = umask(jpim1,:,jk) == 1
652            llcotv( 1 ,:) = vmask(  2  ,:,jk) == 1
653            llcotv(jpi,:) = vmask(jpim1,:,jk) == 1
654            llcotf( 1 ,:) = fmask(  2  ,:,jk) == 1
655            llcotf(jpi,:) = fmask(jpim1,:,jk) == 1
656         ENDIF
657         IF( nperio == 3 .OR. nperio == 4 ) THEN
658            DO ji = 1, jpim1
659               iju = jpi - ji + 1
660               llcotu(ji,jpj  ) = llcotu(iju,jpj-2)
661               llcotf(ji,jpjm1) = llcotf(iju,jpj-2)
662               llcotf(ji,jpj  ) = llcotf(iju,jpj-3)
663            END DO
664            DO ji = jpi/2, jpim1
665               iju = jpi - ji + 1
666               llcotu(ji,jpjm1) = llcotu(iju,jpjm1)
667            END DO
668            DO ji = 2, jpi
669               ijt = jpi - ji + 2
670               llcotv(ji,jpjm1) = llcotv(ijt,jpj-2)
671               llcotv(ji,jpj  ) = llcotv(ijt,jpj-3)
672            END DO
673         ENDIF
674         IF( nperio == 5 .OR. nperio == 6 ) THEN
675            DO ji = 1, jpim1
676               iju = jpi - ji
677               llcotu(ji,jpj  ) = llcotu(iju,jpjm1)
678               llcotf(ji,jpj  ) = llcotf(iju,jpj-2)
679            END DO
680            DO ji = jpi/2, jpim1
681               iju = jpi - ji
682               llcotf(ji,jpjm1) = llcotf(iju,jpjm1)
683            END DO
684            DO ji = 1, jpi
685               ijt = jpi - ji + 1
686               llcotv(ji,jpj  ) = llcotv(ijt,jpjm1)
687            END DO
688            DO ji = jpi/2+1, jpi
689               ijt = jpi - ji + 1
690               llcotv(ji,jpjm1) = llcotv(ijt,jpjm1)
691            END DO
692         ENDIF
693
694         ! Compute cartesian coordinates of coastline points
695         ! and the number of coastline points
696
697         icoast = 0
698         DO jj = 1, jpj
699            DO ji = 1, jpi
700               IF( llcotf(ji,jj) ) THEN
701                  icoast = icoast + 1
702                  zxc(icoast) = COS( rad*gphif(ji,jj) ) * COS( rad*glamf(ji,jj) )
703                  zyc(icoast) = COS( rad*gphif(ji,jj) ) * SIN( rad*glamf(ji,jj) )
704                  zzc(icoast) = SIN( rad*gphif(ji,jj) )
705               ENDIF
706               IF( llcotu(ji,jj) ) THEN
707                  icoast = icoast+1
708                  zxc(icoast) = COS( rad*gphiu(ji,jj) ) * COS( rad*glamu(ji,jj) )
709                  zyc(icoast) = COS( rad*gphiu(ji,jj) ) * SIN( rad*glamu(ji,jj) )
710                  zzc(icoast) = SIN( rad*gphiu(ji,jj) )
711               ENDIF
712               IF( llcotv(ji,jj) ) THEN
713                  icoast = icoast+1
714                  zxc(icoast) = COS( rad*gphiv(ji,jj) ) * COS( rad*glamv(ji,jj) )
715                  zyc(icoast) = COS( rad*gphiv(ji,jj) ) * SIN( rad*glamv(ji,jj) )
716                  zzc(icoast) = SIN( rad*gphiv(ji,jj) )
717               ENDIF
718            END DO
719         END DO
720
721         ! Distance for the T-points
722
723         DO jj = 1, jpj
724            DO ji = 1, jpi
725               IF( tmask(ji,jj,jk) == 0. ) THEN
726                  pdct(ji,jj,jk) = 0.
727               ELSE
728                  DO jl = 1, icoast
729                     zdis(jl) = ( zxt(ji,jj) - zxc(jl) )**2   &
730                        &     + ( zyt(ji,jj) - zyc(jl) )**2   &
731                        &     + ( zzt(ji,jj) - zzc(jl) )**2
732                  END DO
733                  pdct(ji,jj,jk) = ra * SQRT( MINVAL( zdis(1:icoast) ) )
734               ENDIF
735            END DO
736         END DO
737         !                                                ! ===============
738      END DO                                              !   End of slab
739      !                                                   ! ===============
740
741
742      ! 2. Create the  distance to the coast file in NetCDF format
743      ! ----------------------------------------------------------   
744      clname = 'dist.coast'
745      itime = 0
746      CALL ymds2ju( 0     , 1      , 1     , 0.e0 , zdate0 )
747      CALL restini( 'NONE', jpi    , jpj   , glamt, gphit ,   &
748         &          jpk   , gdept_0, clname, itime, zdate0,   &
749         &          rdt   , icot                         )
750      CALL restput( icot, 'Tcoast', jpi, jpj, jpk, 0, pdct )
751      CALL restclo( icot )
752
753   END SUBROUTINE cofdis
754
755#else
756   !!----------------------------------------------------------------------
757   !!   Default key                                     NO internal damping
758   !!----------------------------------------------------------------------
759   LOGICAL , PUBLIC, PARAMETER ::   lk_tradmp = .FALSE.    !: internal damping flag
760CONTAINS
761   SUBROUTINE tra_dmp( kt )        ! Empty routine
762      WRITE(*,*) 'tra_dmp: You should not have seen this print! error?', kt
763   END SUBROUTINE tra_dmp
764#endif
765
766   !!======================================================================
767END MODULE tradmp
Note: See TracBrowser for help on using the repository browser.