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_tam.F90 in branches/TAM_V3_0/NEMOTAM/OPATAM_SRC/TRA – NEMO

source: branches/TAM_V3_0/NEMOTAM/OPATAM_SRC/TRA/tradmp_tam.F90 @ 1885

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

add TAM sources

File size: 27.8 KB
Line 
1MODULE tradmp_tam
2#ifdef key_tam
3   !!======================================================================
4   !!                       ***  MODULE  tradmp_tam  ***
5   !! Ocean physics: internal restoring trend on active tracers (T and S)
6   !!                Tangent and Adjoint Module
7   !!======================================================================
8   !! History of the direct module:
9   !!            5.0  !  91-03  (O. Marti, G. Madec)  Original code
10   !!                 !  92-06  (M. Imbard)  doctor norme
11   !!                 !  96-01  (G. Madec)  statement function for e3
12   !!                 !  97-05  (G. Madec)  macro-tasked on jk-slab
13   !!                 !  98-07  (M. Imbard, G. Madec) ORCA version
14   !!            7.0  !  01-02  (M. Imbard)  cofdis, Original code
15   !!            8.1  !  01-02  (G. Madec, E. Durand)  cleaning
16   !!            8.5  !  02-08  (G. Madec, E. Durand)  free form + modules
17   !!                 !  03-08  (M. Balmaseda)  mods to allow eq. damping
18   !! History of the TAM:
19   !!                 !  08-09  (A. Vidard) tangent and adjoint module
20   !!                                       of the 03-08 version
21   !!----------------------------------------------------------------------
22#if   defined key_tradmp   ||   defined key_esopa
23   !!----------------------------------------------------------------------
24   !!   key_tradmp                                         internal damping
25   !!----------------------------------------------------------------------
26   !!----------------------------------------------------------------------
27   !!   tra_dmp      : update the tracer trend with the internal damping
28   !!   tra_dmp_init : initialization, namlist read, parameters control
29   !!   dtacof_zoom  : restoring coefficient for zoom domain
30   !!   dtacof       : restoring coefficient for global domain
31   !!   cofdis       : compute the distance to the coastline
32   !!----------------------------------------------------------------------
33   USE par_kind      , ONLY: & ! Precision variables
34      & wp
35   USE par_oce       , ONLY: & ! Ocean space and time domain variables
36      & jpi,                 &
37      & jpj,                 & 
38      & jpk,                 &
39      & jpim1,               &
40      & jpjm1,               &
41      & jpkm1,               &
42      & jpiglo,              &
43      & jpjglo,              &
44      & jpizoom,             &
45      & jpjzoom
46   USE oce_tam       , ONLY: & ! ocean dynamics and tracers variables
47      & tb_tl,               &
48      & sb_tl,               &
49      & ta_tl,               &
50      & sa_tl,               &
51      & tb_ad,               &
52      & sb_ad,               &
53      & ta_ad,               &
54      & sa_ad     
55   USE dom_oce       , ONLY: & ! Ocean space and time domain
56      & lzoom,               & 
57      & lzoom_e,             & 
58      & lzoom_w,             & 
59      & lzoom_s,             & 
60      & lzoom_n,             & 
61      & lzoom_arct,          & 
62      & lzoom_anta,          &
63      & nperio,              &
64      & rdt,                 &
65      & mi0,                 &
66      & mj0,                 &
67      & mi1,                 &
68      & mj1,                 &
69      & mig,                 &
70      & mjg,                 &
71      & nldi,                &
72      & nldj,                &
73      & nlei,                &
74      & nlej,                &
75      & e1t,                 &
76      & e2t,                 &
77#if defined key_zco
78      & e3t_0,               &
79      & gdept_0,             &
80#else
81      & e3t,                 &
82      & gdept,               &
83#endif
84      & gdept_0,             &
85      & umask,               &
86      & vmask,               &
87      & tmask,               &
88      & fmask,               &
89      & gphiu,               &
90      & glamu,               &
91      & gphiv,               &
92      & glamv,               &
93      & gphit,               &
94      & glamt,               &
95      & gphif,               &
96      & glamf
97   USE zdf_oce, ONLY: &! ocean vertical physics
98      & avt
99   USE in_out_manager, ONLY: & ! I/O manager
100      & ctl_stop,            &
101      & lwp,                 &
102      & numout,              & 
103      & numnam,              & 
104      & ctmp1,               & 
105      & nit000,              &
106      & nitend
107   USE phycst        , ONLY: & ! Define parameters for the routines
108      & rday,                & 
109      & rpi,                 &
110      & ra,                  &
111      & rad
112   USE lib_mpp       , ONLY: & ! distributed memory computing
113      & lk_mpp
114   USE tradmp        , ONLY : &
115      & dtacof_zoom, dtacof,  &
116      & cofdis
117   USE prtctl        , ONLY: & ! Print control
118      & prt_ctl
119   USE gridrandom    , ONLY: & ! Random Gaussian noise on grids
120      & grid_random
121   USE dotprodfld    , ONLY: & ! Computes dot product for 3D and 2D fields
122      & dot_product
123   USE dtatem        , ONLY: & ! temperature data
124      & lk_dtatem
125   USE dtasal        , ONLY: & ! salinity data
126      & lk_dtasal
127   USE zdfmxl        , ONLY: & ! mixed layer depth
128      & hmlp
129   USE tstool_tam    , ONLY: &
130      & prntst_adj,          & !
131      & stdt,                & ! stdev for temperature
132      & stds                   !           salinity
133   USE paresp        , ONLY: &
134      & wesp_t,              &
135      & wesp_s
136   IMPLICIT NONE
137   PRIVATE
138
139   PUBLIC tra_dmp_tan      ! routine called by step_tam.F90
140   PUBLIC tra_dmp_adj      ! routine called by step_tam.F90
141   PUBLIC tra_dmp_adj_tst  ! routine called by tst.F90
142#if ! defined key_agrif
143   LOGICAL, PUBLIC, PARAMETER ::   lk_tradmp = .TRUE.     !: internal damping flag
144#else
145   LOGICAL, PUBLIC            ::   lk_tradmp = .TRUE.     !: internal damping flag
146#endif
147   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) :: &
148     & resto          !: restoring coeff. on T and S (s-1)
149   
150   
151   LOGICAL :: lfirst = .TRUE.     !: flag for initialisation
152   !!* newtonian damping namelist (mandmp)
153   INTEGER  ::   ndmp   =   -1    ! = 0/-1/'latitude' for damping over T and S
154   INTEGER  ::   ndmpf  =    2    ! = 1 create a damping.coeff NetCDF file
155   INTEGER  ::   nmldmp =    0    ! = 0/1/2 flag for damping in the mixed layer
156   REAL(wp) ::   sdmp   =   50.   ! surface time scale for internal damping (days)
157   REAL(wp) ::   bdmp   =  360.   ! bottom time scale for internal damping (days)
158   REAL(wp) ::   hdmp   =  800.   ! depth of transition between sdmp and bdmp (meters)
159   !! * Substitutions
160#  include "domzgr_substitute.h90"
161#  include "vectopt_loop_substitute.h90"
162
163
164CONTAINS
165
166   SUBROUTINE tra_dmp_tan( kt )
167      !!----------------------------------------------------------------------
168      !!                   ***  ROUTINE tra_dmp_tan  ***
169      !!                 
170      !! ** Purpose of direct routine:
171      !!      Compute the tracer trend due to a newtonian damping
172      !!      of the tracer field towards given data field and add it to the
173      !!      general tracer trends.
174      !!
175      !! ** Method  :   Newtonian damping towards t_dta and s_dta computed
176      !!      and add to the general tracer trends:
177      !!                     ta = ta + resto * (t_dta - tb)
178      !!                     sa = sa + resto * (s_dta - sb)
179      !!         The trend is computed either throughout the water column
180      !!      (nlmdmp=0) or in area of weak vertical mixing (nlmdmp=1) or
181      !!      below the well mixed layer (nlmdmp=2)
182      !!
183      !! ** Action  : - update the tracer trends (ta,sa) with the newtonian
184      !!                damping trends.
185      !!
186      !! ASSUME key_zdfcst_tam
187      !!----------------------------------------------------------------------
188      !!
189      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
190      !!
191      INTEGER  ::   ji, jj, jk            ! dummy loop indices
192      REAL(wp) ::   ztest, ztatl, zsatl       ! temporary scalars
193      !!----------------------------------------------------------------------
194      IF( kt == nit000 )   CALL tra_dmp_init_tam  ! Initialization
195
196      ! 1. Newtonian damping trends on tracer fields
197      ! --------------------------------------------
198      !    compute the newtonian damping trends depending on nmldmp
199
200      SELECT CASE ( nmldmp )
201      !
202      CASE( 0 )                ! newtonian damping throughout the water column
203         DO jk = 1, jpkm1
204            DO jj = 2, jpjm1
205               DO ji = fs_2, fs_jpim1   ! vector opt.
206                  ztatl = - resto(ji,jj,jk) *  tb_tl(ji,jj,jk) 
207                  zsatl = - resto(ji,jj,jk) *  sb_tl(ji,jj,jk) 
208                  ! add the trends to the general tracer trends
209                  ta_tl(ji,jj,jk) = ta_tl(ji,jj,jk) + ztatl
210                  sa_tl(ji,jj,jk) = sa_tl(ji,jj,jk) + zsatl
211               END DO
212            END DO
213         END DO
214         !
215      CASE ( 1 )                ! no damping in the turbocline (avt > 5 cm2/s)
216         DO jk = 1, jpkm1
217            DO jj = 2, jpjm1
218               DO ji = fs_2, fs_jpim1   ! vector opt.
219                  ztest = avt(ji,jj,jk) - 5.e-4
220      !! ASSUME key_zdfcst_tam
221                  IF( ztest < 0. ) THEN
222                     ztatl = - resto(ji,jj,jk) * tb_tl(ji,jj,jk) 
223                     zsatl = - resto(ji,jj,jk) * sb_tl(ji,jj,jk)
224                  ELSE
225                     ztatl = 0.e0
226                     zsatl = 0.e0
227                  ENDIF
228                  ! add the trends to the general tracer trends
229                  ta_tl(ji,jj,jk) = ta_tl(ji,jj,jk) + ztatl
230                  sa_tl(ji,jj,jk) = sa_tl(ji,jj,jk) + zsatl
231               END DO
232            END DO
233         END DO
234         !
235      CASE ( 2 )                ! no damping in the mixed layer 
236         DO jk = 1, jpkm1
237            DO jj = 2, jpjm1
238               DO ji = fs_2, fs_jpim1   ! vector opt.
239                  IF( fsdept(ji,jj,jk) >= hmlp (ji,jj) ) THEN
240                     ztatl = - resto(ji,jj,jk) * tb_tl(ji,jj,jk)
241                     zsatl = - resto(ji,jj,jk) * sb_tl(ji,jj,jk)
242                  ELSE
243                     ztatl = 0.e0
244                     zsatl = 0.e0
245                  ENDIF
246                  ! add the trends to the general tracer trends
247                  ta_tl(ji,jj,jk) = ta_tl(ji,jj,jk) + ztatl
248                  sa_tl(ji,jj,jk) = sa_tl(ji,jj,jk) + zsatl
249               END DO
250            END DO
251         END DO
252         !
253      END SELECT
254
255   END SUBROUTINE tra_dmp_tan
256   SUBROUTINE tra_dmp_adj( kt )
257      !!----------------------------------------------------------------------
258      !!                   ***  ROUTINE tra_dmp_adj  ***
259      !!                 
260      !! ** Purpose of direct routine:
261      !!      Compute the tracer trend due to a newtonian damping
262      !!      of the tracer field towards given data field and add it to the
263      !!      general tracer trends.
264      !!
265      !! ** Method  :   Newtonian damping towards t_dta and s_dta computed
266      !!      and add to the general tracer trends:
267      !!                     ta = ta + resto * (t_dta - tb)
268      !!                     sa = sa + resto * (s_dta - sb)
269      !!         The trend is computed either throughout the water column
270      !!      (nlmdmp=0) or in area of weak vertical mixing (nlmdmp=1) or
271      !!      below the well mixed layer (nlmdmp=2)
272      !!
273      !! ** Action  : - update the tracer trends (ta,sa) with the newtonian
274      !!                damping trends.
275      !!              - save the trends in (ttrd,strd) ('key_trdtra')
276      !! ASSUME key_zdfcst_tam
277      !!----------------------------------------------------------------------
278      !!
279      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
280      !!
281      INTEGER  ::   ji, jj, jk            ! dummy loop indices
282      REAL(wp) ::   ztest, ztaad, zsaad       ! temporary scalars
283      !!----------------------------------------------------------------------
284      IF( kt == nitend )   CALL tra_dmp_init_tam  ! Initialization
285
286      ! 1. Newtonian damping trends on tracer fields
287      ! --------------------------------------------
288      !    compute the newtonian damping trends depending on nmldmp
289      ztaad = 0.e0
290      zsaad = 0.e0
291
292      SELECT CASE ( nmldmp )
293      !
294      CASE( 0 )                ! newtonian damping throughout the water column
295         DO jk = 1, jpkm1
296            DO jj = 2, jpjm1
297               DO ji = fs_2, fs_jpim1   ! vector opt.
298                  ! add the trends to the general tracer trends
299                  ztaad = ta_ad(ji,jj,jk) + ztaad
300                  zsaad = sa_ad(ji,jj,jk) + zsaad
301
302                  tb_ad(ji,jj,jk)  = tb_ad(ji,jj,jk) - ztaad * resto(ji,jj,jk)
303                  sb_ad(ji,jj,jk)  = sb_ad(ji,jj,jk) - zsaad * resto(ji,jj,jk)
304                  ztaad = 0.0_wp
305                  zsaad = 0.0_wp
306                END DO
307            END DO
308         END DO
309         !
310      CASE ( 1 )                ! no damping in the turbocline (avt > 5 cm2/s)
311         DO jk = 1, jpkm1
312            DO jj = 2, jpjm1
313               DO ji = fs_2, fs_jpim1   ! vector opt.
314                  ! add the trends to the general tracer trends
315                  ztaad = ta_ad(ji,jj,jk) + ztaad
316                  zsaad = sa_ad(ji,jj,jk) + zsaad
317                  ztest = avt(ji,jj,jk) - 5.e-4
318      !! ASSUME key_zdfcst_tam
319                  IF( ztest < 0. ) THEN
320                     tb_ad(ji,jj,jk)  = tb_ad(ji,jj,jk) - ztaad * resto(ji,jj,jk)
321                     sb_ad(ji,jj,jk)  = sb_ad(ji,jj,jk) - zsaad * resto(ji,jj,jk)
322                     ztaad = 0.0_wp
323                     zsaad = 0.0_wp
324                  ELSE
325                     ztaad = 0.e0
326                     zsaad = 0.e0
327                  ENDIF
328               END DO
329            END DO
330         END DO
331         !
332      CASE ( 2 )                ! no damping in the mixed layer
333         DO jk = 1, jpkm1
334            DO jj = 2, jpjm1
335               DO ji = fs_2, fs_jpim1   ! vector opt.
336                  ! add the trends to the general tracer trends
337                  ztaad = ta_ad(ji,jj,jk) + ztaad
338                  zsaad = sa_ad(ji,jj,jk) + zsaad
339                  IF( fsdept(ji,jj,jk) >= hmlp (ji,jj) ) THEN
340                     tb_ad(ji,jj,jk)  = tb_ad(ji,jj,jk) - ztaad * resto(ji,jj,jk)
341                     sb_ad(ji,jj,jk)  = sb_ad(ji,jj,jk) - zsaad * resto(ji,jj,jk)
342                     ztaad = 0.0_wp
343                     zsaad = 0.0_wp
344                  ELSE
345                     ztaad = 0.e0
346                     zsaad = 0.e0
347                  ENDIF
348               END DO
349            END DO
350         END DO
351         !
352      END SELECT
353
354
355   END SUBROUTINE tra_dmp_adj
356   SUBROUTINE tra_dmp_init_tam
357      !!----------------------------------------------------------------------
358      !!                  ***  ROUTINE tra_dmp_init_tam  ***
359      !!
360      !! ** Purpose :   Initialization for the newtonian damping
361      !!
362      !! ** Method  :   read the nammbf namelist and check the parameters
363      !!      called by tra_dmp at the first timestep (nit000)
364      !!----------------------------------------------------------------------
365
366      NAMELIST/namtdp/ ndmp, ndmpf, nmldmp, sdmp, bdmp, hdmp
367      !!----------------------------------------------------------------------
368
369      IF (lfirst) THEN
370
371         REWIND ( numnam )                  ! Read Namelist namtdp : temperature and salinity damping term
372         READ   ( numnam, namtdp )
373         IF( lzoom )   nmldmp = 0           ! restoring to climatology at closed north or south boundaries
374         
375         IF(lwp) THEN                       ! Namelist print
376            WRITE(numout,*)
377            WRITE(numout,*) 'tra_dmp_tam : T and S newtonian damping'
378            WRITE(numout,*) '~~~~~~~~~~~'
379            WRITE(numout,*) '       Namelist namtdp : set damping parameter'
380            WRITE(numout,*) '          T and S damping option         ndmp   = ', ndmp
381            WRITE(numout,*) '          create a damping.coeff file    ndmpf  = ', ndmpf
382            WRITE(numout,*) '          mixed layer damping option     nmldmp = ', nmldmp, '(zoom: forced to 0)'
383            WRITE(numout,*) '          surface time scale (days)      sdmp   = ', sdmp
384            WRITE(numout,*) '          bottom time scale (days)       bdmp   = ', bdmp
385            WRITE(numout,*) '          depth of transition (meters)   hdmp   = ', hdmp
386         ENDIF
387         
388         !! ** modified to allow damping at the equator
389         
390         SELECT CASE ( ndmp )
391         CASE (  -1  )   ;   IF(lwp) WRITE(numout,*) '          tracer damping in the Med & Red seas only'
392         CASE ( 0:90 )   ;   IF(lwp) WRITE(numout,*) '          tracer damping poleward of', ndmp, ' degrees'
393         CASE DEFAULT
394            IF(lwp) WRITE(numout,*) '          tracer damping disabled', ndmp
395            !         WRITE(ctmp1,*) '          bad flag value for ndmp = ', ndmp
396            !         CALL ctl_stop(ctmp1)
397         END SELECT
398         
399         SELECT CASE ( nmldmp )
400         CASE ( 0 )   ;   IF(lwp) WRITE(numout,*) '          tracer damping throughout the water column'
401         CASE ( 1 )   ;   IF(lwp) WRITE(numout,*) '          no tracer damping in the turbocline (avt > 5 cm2/s)'
402         CASE ( 2 )   ;   IF(lwp) WRITE(numout,*) '          no tracer damping in the mixed layer'
403         CASE DEFAULT
404            WRITE(ctmp1,*) '          bad flag value for nmldmp = ', nmldmp
405            CALL ctl_stop(ctmp1)
406         END SELECT
407         
408         IF( .NOT.lk_dtasal .OR. .NOT.lk_dtatem )   &
409            &   CALL ctl_stop( 'no temperature and/or salinity data define key_dtatem and key_dtasal' )
410         
411         !                          ! Damping coefficients initialization
412         IF( lzoom ) THEN   ;   CALL dtacof_zoom
413         ELSE               ;   CALL dtacof
414         ENDIF
415         !
416         lfirst = .FALSE.
417      END IF
418   END SUBROUTINE tra_dmp_init_tam
419
420   SUBROUTINE tra_dmp_adj_tst ( kumadt ) 
421      !!-----------------------------------------------------------------------
422      !!
423      !!          ***  ROUTINE tra_sbc_adj_tst : TEST OF tra_sbc_adj  ***
424      !!
425      !! ** Purpose : Test the adjoint routine.
426      !!
427      !! ** Method  : Verify the scalar product
428      !!           
429      !!                 ( L dx )^T W dy  =  dx^T L^T W dy
430      !!
431      !!              where  L   = tangent routine
432      !!                     L^T = adjoint routine
433      !!                     W   = diagonal matrix of scale factors
434      !!                     dx  = input perturbation (random field)
435      !!                     dy  = L dx
436      !!
437       !! History :
438      !!        ! 08-08 (A. Vidard)
439      !!-----------------------------------------------------------------------
440      !! * Modules used
441
442      !! * Arguments
443      INTEGER, INTENT(IN) :: &
444         & kumadt             ! Output unit
445 
446      INTEGER ::  &
447         & istp,  &
448         & jstp,  &
449         & ji,    &        ! dummy loop indices
450         & jj,    &       
451         & jk     
452      INTEGER, DIMENSION(jpi,jpj) :: &
453         & iseed_2d        ! 2D seed for the random number generator
454
455      !! * Local declarations
456      REAL(KIND=wp), DIMENSION(:,:,:), ALLOCATABLE :: &
457         & zsb_tlin,     &! Tangent input : before salinity
458         & ztb_tlin,     &! Tangent input : before temperature
459         & zsa_tlin,     &! Tangent input : after salinity
460         & zta_tlin,     &! Tangent input : after temperature
461         & zsa_tlout,    &! Tangent output: after salinity
462         & zta_tlout,    &! Tangent output: after temperature
463         & zsb_adout,    &! Adjoint output : before salinity
464         & ztb_adout,    &! Adjoint output : before temperature
465         & zsa_adout,    &! Adjoint output : after salinity
466         & zta_adout,    &! Adjoint output : after temperature
467         & zsa_adin,     &! Adjoint input : after salinity
468         & zta_adin,     &! Adjoint input : after temperature
469         & z3r            ! 3D field
470         
471      REAL(KIND=wp) ::       &
472         & zsp1,             & ! scalar product involving the tangent routine
473         & zsp1_1,           & ! scalar product involving the tangent routine
474         & zsp1_2,           & ! scalar product involving the tangent routine
475         & zsp1_3,           & ! scalar product involving the tangent routine
476         & zsp1_4,           & ! scalar product involving the tangent routine
477         & zsp2,             & ! scalar product involving the adjoint routine
478         & zsp2_1,           & ! scalar product involving the adjoint routine
479         & zsp2_2,           & ! scalar product involving the adjoint routine
480         & zsp2_3,           & ! scalar product involving the adjoint routine
481         & zsp2_4              ! scalar product involving the adjoint routine
482      CHARACTER(LEN=14) ::   &
483         & cl_name
484
485      ALLOCATE( & 
486         & ztb_tlin(jpi,jpj,jpk),     &
487         & zsb_tlin(jpi,jpj,jpk),     &
488         & zsa_tlin(jpi,jpj,jpk),     &
489         & zta_tlin(jpi,jpj,jpk),     &
490         & zsa_tlout(jpi,jpj,jpk),    &
491         & zta_tlout(jpi,jpj,jpk),    &
492         & ztb_adout(jpi,jpj,jpk),    &
493         & zsb_adout(jpi,jpj,jpk),    &
494         & zsa_adout(jpi,jpj,jpk),    &
495         & zta_adout(jpi,jpj,jpk),    &
496         & zsa_adin(jpi,jpj,jpk),     &
497         & zta_adin(jpi,jpj,jpk),     &
498         & z3r         (jpi,jpj,jpk)  &
499         & )
500      ! Test for time steps nit000 and nit000 + 1 (the matrix changes)
501
502      DO jstp = nit000, nit000 + 2
503         istp = jstp
504         IF ( jstp == nit000 +2 ) istp = nitend
505
506      ! Initialize the reference state
507      avt(:,:,:) = 1.e-1
508      !=============================================================
509      ! 1) dx = ( T ) and dy = ( T )
510      !=============================================================
511
512      !--------------------------------------------------------------------
513      ! Reset the tangent and adjoint variables
514      !--------------------------------------------------------------------
515      zsb_tlin(:,:,:)      = 0.0_wp 
516      ztb_tlin(:,:,:)      = 0.0_wp 
517      zsa_tlin(:,:,:)      = 0.0_wp 
518      zta_tlin(:,:,:)      = 0.0_wp 
519      zsa_tlout(:,:,:)     = 0.0_wp 
520      zta_tlout(:,:,:)     = 0.0_wp 
521      zsb_adout(:,:,:)     = 0.0_wp 
522      ztb_adout(:,:,:)     = 0.0_wp 
523      zsa_adout(:,:,:)     = 0.0_wp 
524      zta_adout(:,:,:)     = 0.0_wp 
525      zsa_adin(:,:,:)      = 0.0_wp 
526      zta_adin(:,:,:)      = 0.0_wp 
527
528      sa_ad(:,:,:)      = 0.0_wp 
529      sb_ad(:,:,:)      = 0.0_wp 
530      ta_ad(:,:,:)      = 0.0_wp 
531      tb_ad(:,:,:)      = 0.0_wp 
532      sa_tl(:,:,:)      = 0.0_wp 
533      sb_tl(:,:,:)      = 0.0_wp 
534      ta_tl(:,:,:)      = 0.0_wp 
535      tb_tl(:,:,:)      = 0.0_wp 
536
537      DO jj = 1, jpj
538         DO ji = 1, jpi
539            iseed_2d(ji,jj) = - ( 785483 + &
540               &                  mig(ji) + ( mjg(jj) - 1 ) * jpiglo )
541         END DO
542      END DO
543      CALL grid_random( iseed_2d, z3r, 'T', 0.0_wp, stds )
544      DO jk = 1, jpk
545         DO jj = nldj, nlej
546            DO ji = nldi, nlei
547               zsb_tlin(ji,jj,jk) = z3r(ji,jj,jk) 
548            END DO
549         END DO
550      END DO
551      DO jj = 1, jpj
552         DO ji = 1, jpi
553            iseed_2d(ji,jj) = - ( 358606 + &
554               &                  mig(ji) + ( mjg(jj) - 1 ) * jpiglo )
555         END DO
556      END DO
557      CALL grid_random( iseed_2d, z3r, 'T', 0.0_wp, stdt )
558      DO jk = 1, jpk
559         DO jj = nldj, nlej
560            DO ji = nldi, nlei
561               ztb_tlin(ji,jj,jk) = z3r(ji,jj,jk) 
562            END DO
563         END DO
564      END DO
565
566      DO jj = 1, jpj
567         DO ji = 1, jpi
568            iseed_2d(ji,jj) = - ( 596035 + &
569               &                  mig(ji) + ( mjg(jj) - 1 ) * jpiglo )
570         END DO
571      END DO
572      CALL grid_random( iseed_2d, z3r, 'T', 0.0_wp, stds )
573      DO jk = 1, jpk
574         DO jj = nldj, nlej
575            DO ji = nldi, nlei
576               zsa_tlin(ji,jj,jk) = z3r(ji,jj,jk) 
577            END DO
578         END DO
579      END DO
580
581      DO jj = 1, jpj
582         DO ji = 1, jpi
583            iseed_2d(ji,jj) = - ( 523432 + &
584               &                  mig(ji) + ( mjg(jj) - 1 ) * jpiglo )
585         END DO
586      END DO
587      CALL grid_random( iseed_2d, z3r, 'T', 0.0_wp, stdt )
588      DO jk = 1, jpk
589         DO jj = nldj, nlej
590            DO ji = nldi, nlei
591               zta_tlin(ji,jj,jk) = z3r(ji,jj,jk) 
592            END DO
593         END DO
594      END DO
595
596      sb_tl(:,:,:) = zsb_tlin(:,:,:) 
597      tb_tl(:,:,:) = ztb_tlin(:,:,:) 
598      sa_tl(:,:,:) = zsa_tlin(:,:,:) 
599      ta_tl(:,:,:) = zta_tlin(:,:,:)
600     
601      CALL tra_dmp_tan( istp )
602
603      zsa_tlout(:,:,:)     = sa_tl(:,:,:) 
604      zta_tlout(:,:,:)     = ta_tl(:,:,:)
605
606      !--------------------------------------------------------------------
607      ! Initialize the adjoint variables: dy^* = W dy
608      !--------------------------------------------------------------------
609
610      DO jk = 1, jpk
611        DO jj = nldj, nlej
612           DO ji = nldi, nlei
613              zsa_adin(ji,jj,jk)     = zsa_tlout(ji,jj,jk) &
614                 &                   * e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) &
615                 &                   * tmask(ji,jj,jk) * wesp_s(jk)
616              zta_adin(ji,jj,jk)     = zta_tlout(ji,jj,jk) &
617                 &                   * e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) &
618                 &                   * tmask(ji,jj,jk) * wesp_t(jk)
619            END DO
620         END DO
621      END DO
622
623      !--------------------------------------------------------------------
624      ! Compute the scalar product: ( L dx )^T W dy
625      !--------------------------------------------------------------------
626
627      zsp1_1 = DOT_PRODUCT( zsa_tlout    , zsa_adin     )
628      zsp1_2 = DOT_PRODUCT( zta_tlout    , zta_adin     )
629      zsp1   = zsp1_1 + zsp1_2 
630      !--------------------------------------------------------------------
631      ! Call the adjoint routine: dx^* = L^T dy^*
632      !--------------------------------------------------------------------
633
634      sa_ad(:,:,:)     = zsa_adin(:,:,:)
635      ta_ad(:,:,:)     = zta_adin(:,:,:)
636
637      CALL tra_dmp_adj( istp )
638
639      zsb_adout(:,:,:) = sb_ad(:,:,:)
640      ztb_adout(:,:,:) = tb_ad(:,:,:)
641      zsa_adout(:,:,:) = sa_ad(:,:,:)
642      zta_adout(:,:,:) = ta_ad(:,:,:)
643
644      !--------------------------------------------------------------------
645      ! Compute the scalar product: dx^T L^T W dy
646      !--------------------------------------------------------------------
647
648      zsp2_1 = DOT_PRODUCT( zsb_tlin  , zsb_adout   )
649      zsp2_2 = DOT_PRODUCT( ztb_tlin  , ztb_adout   )
650      zsp2_3 = DOT_PRODUCT( zsa_tlin  , zsa_adout   )
651      zsp2_4 = DOT_PRODUCT( zta_tlin  , zta_adout   )
652
653      zsp2 = zsp2_1 + zsp2_2 + zsp2_3 + zsp2_4
654
655      ! Compare the scalar products
656
657      ! 14 char:'12345678901234'
658      IF ( istp == nit000 ) THEN
659         cl_name = 'tra_dmp_adj T1'
660      ELSEIF ( istp == nit000 +1 ) THEN
661         cl_name = 'tra_dmp_adj T2'
662      ELSEIF ( istp == nitend ) THEN
663         cl_name = 'tra_dmp_adj T3'
664      END IF
665      CALL prntst_adj( cl_name, kumadt, zsp1, zsp2 )
666
667      END DO
668
669      DEALLOCATE( & 
670         & zsb_tlin,     &
671         & ztb_tlin,     &
672         & zsa_tlin,     &
673         & zta_tlin,     &
674         & zsa_tlout,    &
675         & zta_tlout,    &
676         & zsb_adout,    &
677         & ztb_adout,    &
678         & zsa_adout,    &
679         & zta_adout,    &
680         & zsa_adin,     &
681         & zta_adin,     &
682         & z3r           &
683         & )
684
685   END SUBROUTINE tra_dmp_adj_tst
686
687#else
688   !!----------------------------------------------------------------------
689   !!   Default key                                     NO internal damping
690   !!----------------------------------------------------------------------
691   LOGICAL , PUBLIC, PARAMETER ::   lk_tradmp = .FALSE.    !: internal damping flag
692CONTAINS
693   SUBROUTINE tra_dmp_tan( kt )        ! Empty routine
694      WRITE(*,*) 'tra_dmp_tan: You should not have seen this print! error?', kt
695   END SUBROUTINE tra_dmp_tan
696   SUBROUTINE tra_dmp_adj( kt )        ! Empty routine
697      WRITE(*,*) 'tra_dmp_adj: You should not have seen this print! error?', kt
698   END SUBROUTINE tra_dmp_adj
699   SUBROUTINE tra_dmp_adj_tst( kt )        ! Empty routine
700      WRITE(*,*) 'tra_dmp_adj_tst: You should not have seen this print! error?', kt
701   END SUBROUTINE tra_dmp_adj_tst
702#endif
703
704   !!======================================================================
705#endif
706END MODULE tradmp_tam
Note: See TracBrowser for help on using the repository browser.