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

Last change on this file since 480 was 473, checked in by opalod, 18 years ago

nemo_v1_update_060: SM: IOM + 301 levels + CORE + begining of ctl_stop

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