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.
trcdmp.F90 in trunk/NEMO/TOP_SRC/TRP – NEMO

source: trunk/NEMO/TOP_SRC/TRP/trcdmp.F90 @ 247

Last change on this file since 247 was 247, checked in by opalod, 19 years ago

CL : Add CVS Header and CeCILL licence information

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