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 branches/TAM_V3_0/NEMO/OPA_SRC/TRA – NEMO

source: branches/TAM_V3_0/NEMO/OPA_SRC/TRA/tradmp.F90 @ 1884

Last change on this file since 1884 was 1884, checked in by rblod, 14 years ago

Light adaptation of NEMO direct model routine to handle TAM

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