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 @ 193

Last change on this file since 193 was 163, checked in by opalod, 20 years ago

CT + CL : BUGFIX106 : Remove the T-point/coast distance computation problem in cofdis subroutine in the tradmp.F90 module

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