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

source: branches/DEV_r2191_3partymerge2010/NEMO/OPA_SRC/TRA/tradmp.F90 @ 2207

Last change on this file since 2207 was 2207, checked in by acc, 14 years ago

#733 DEV_r2191_3partymerge2010. Merged in changes from devukmo2010 branch

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