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.
dynnxt_tam.F90 in branches/2012/dev_r3604_LEGI8_TAM/NEMOGCM/NEMO/OPATAM_SRC/DYN – NEMO

source: branches/2012/dev_r3604_LEGI8_TAM/NEMOGCM/NEMO/OPATAM_SRC/DYN/dynnxt_tam.F90 @ 3611

Last change on this file since 3611 was 3611, checked in by pabouttier, 11 years ago

Add TAM code and ORCA2_TAM configuration - see Ticket #1007

  • Property svn:executable set to *
File size: 27.7 KB
Line 
1MODULE dynnxt_tam
2#ifdef key_tam
3   !!======================================================================
4   !!                       ***  MODULE  dynnxt_tam  ***
5   !! Ocean dynamics: time stepping
6   !!                 Tangent and Adjoint Module
7   !!======================================================================
8   !! History of the direct module:
9   !!            OPA  !  1987-02  (P. Andrich, D. L Hostis)  Original code
10   !!                 !  1990-10  (C. Levy, G. Madec)
11   !!            7.0  !  1993-03  (M. Guyon)  symetrical conditions
12   !!            8.0  !  1997-02  (G. Madec & M. Imbard)  opa, release 8.0
13   !!            8.2  !  1997-04  (A. Weaver)  Euler forward step
14   !!             -   !  1997-06  (G. Madec)  lateral boudary cond., lbc routine
15   !!    NEMO    1.0  !  2002-08  (G. Madec)  F90: Free form and module
16   !!             -   !  2002-10  (C. Talandier, A-M. Treguier) Open boundary cond.
17   !!            2.0  !  2005-11  (V. Garnier) Surface pressure gradient organization
18   !!            2.3  !  2007-07  (D. Storkey) Calls to BDY routines.
19   !!            3.2  !  2009-06  (G. Madec, R.Benshila)  re-introduce the vvl option
20   !! History of the TAM routine:
21   !!            9.0  !  2008-06  (A. Vidard) Skeleton
22   !!                 !  2008-08  (A. Vidard) tangent of the 05-11 version
23   !!                 !  2008-08  (A. Vidard) tangent of the 07-07 version
24   !!            3.2  !  2010-04  (F. Vigilant) 3.2 conversion
25   !!            3.4  !  2012-07  (P.-A. Bouttier) 3.4 conversion
26   !!-------------------------------------------------------------------------
27   !!----------------------------------------------------------------------
28   !!   dyn_nxt_tan  : update the horizontal velocity from the momentum trend
29   !!   dyn_nxt_adj  : update the horizontal velocity from the momentum trend
30   !!----------------------------------------------------------------------
31   !! * Modules used
32   USE par_kind
33   USE par_oce
34   USE oce_tam
35   USE dom_oce
36   USE in_out_manager
37   USE dynspg_oce
38   USE dynadv
39   USE lbclnk
40   USE lbclnk_tam
41   USE gridrandom
42   USE dotprodfld
43   USE tstool_tam
44   USE lib_mpp
45   USE wrk_nemo
46   USE timing
47
48   IMPLICIT NONE
49   PRIVATE
50
51   !! * Accessibility
52   PUBLIC dyn_nxt_tan            ! routine called by step.F90
53   PUBLIC dyn_nxt_adj            ! routine called by step.F90
54   PUBLIC dyn_nxt_adj_tst        ! routine called by step.F90
55   !! * Substitutions
56#  include "domzgr_substitute.h90"
57   !!----------------------------------------------------------------------
58
59CONTAINS
60
61   SUBROUTINE dyn_nxt_tan ( kt )
62      !!----------------------------------------------------------------------
63      !!                  ***  ROUTINE dyn_nxt_tan  ***
64      !!
65      !! ** Purpose :   Compute the after horizontal velocity. Apply the boundary
66      !!             condition on the after velocity, achieved the time stepping
67      !!             by applying the Asselin filter on now fields and swapping
68      !!             the fields.
69      !!
70      !! ** Method  : * After velocity is compute using a leap-frog scheme:
71      !!                       (ua,va) = (ub,vb) + 2 rdt (ua,va)
72      !!             Note that with flux form advection and variable volume layer
73      !!             (lk_vvl=T), the leap-frog is applied on thickness weighted
74      !!             velocity.
75      !!             Note also that in filtered free surface (lk_dynspg_flt=T),
76      !!             the time stepping has already been done in dynspg module
77      !!
78      !!              * Apply lateral boundary conditions on after velocity
79      !!             at the local domain boundaries through lbc_lnk call,
80      !!             at the radiative open boundaries (lk_obc=T),
81      !!             at the relaxed   open boundaries (lk_bdy=T), and
82      !!             at the AGRIF zoom     boundaries (lk_agrif=T)
83      !!
84      !!              * Apply the time filter applied and swap of the dynamics
85      !!             arrays to start the next time step:
86      !!                (ub,vb) = (un,vn) + atfp [ (ub,vb) + (ua,va) - 2 (un,vn) ]
87      !!                (un,vn) = (ua,va).
88      !!             Note that with flux form advection and variable volume layer
89      !!             (lk_vvl=T), the time filter is applied on thickness weighted
90      !!             velocity.
91      !!
92      !! ** Action :   ub,vb   filtered before horizontal velocity of next time-step
93      !!               un,vn   now horizontal velocity of next time-step
94      !!----------------------------------------------------------------------
95      !! * Arguments
96      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
97      !! * Local declarations
98#if ! defined key_dynspg_flt
99      REAL(wp) ::   z2dt         ! temporary scalar
100#endif
101      INTEGER  ::   ji, jj, jk, iku, ikv         ! dummy loop indices
102      REAL(wp) ::   zue3atl , zue3ntl , zue3btl  ! temporary scalar
103      REAL(wp) ::   zve3atl , zve3ntl , zve3btl  !    -         -
104      REAL(wp) ::   zuftl   , zvftl              !    -         -
105      !!----------------------------------------------------------------------
106      !
107      !
108      IF( nn_timing == 1 )  CALL timing_start('dyn_nxt_tan')
109      !
110      IF( kt == nit000 ) THEN
111         IF(lwp) WRITE(numout,*)
112         IF(lwp) WRITE(numout,*) 'dyn_nxt_tan : time stepping'
113         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
114      ENDIF
115
116#if defined key_dynspg_flt
117      !
118      ! Next velocity :   Leap-frog time stepping already done in dynspg_flt.F routine
119      ! -------------
120
121      ! Update after velocity on domain lateral boundaries      (only local domain required)
122      ! --------------------------------------------------
123      CALL lbc_lnk( ua_tl, 'U', -1.0_wp )         ! local domain boundaries
124      CALL lbc_lnk( va_tl, 'V', -1.0_wp )
125      !
126#else
127      ! Next velocity :   Leap-frog time stepping
128      ! -------------
129      z2dt = 2. * rdt                                 ! Euler or leap-frog time step
130      IF( neuler == 0 .AND. kt == nit000 )  z2dt = rdt
131      !
132      IF( ln_dynadv_vec .OR. .NOT. lk_vvl ) THEN      ! applied on velocity
133         DO jk = 1, jpkm1
134            ua_tl(:,:,jk) = ( ub_tl(:,:,jk) + z2dt * ua_tl(:,:,jk) ) * umask(:,:,jk)
135            va_tl(:,:,jk) = ( vb_tl(:,:,jk) + z2dt * va_tl(:,:,jk) ) * vmask(:,:,jk)
136         END DO
137      ELSE                                            ! applied on thickness weighted velocity
138         DO jk = 1, jpkm1
139            ua_tl(:,:,jk) = (          ub_tl(:,:,jk) * fse3u_b(:,:,jk)      &
140               &              + z2dt * ua_tl(:,:,jk) * fse3u_n(:,:,jk)  )   &
141               &            / fse3u_a(:,:,jk) * umask(:,:,jk)
142            va_tl(:,:,jk) = (          vb_tl(:,:,jk) * fse3v_b(:,:,jk)      &
143               &              + z2dt * va_tl(:,:,jk) * fse3v_n(:,:,jk)  )   &
144               &            / fse3v_a(:,:,jk) * vmask(:,:,jk)
145         END DO
146      ENDIF
147
148      ! Update after velocity on domain lateral boundaries
149      ! --------------------------------------------------
150      CALL lbc_lnk( ua_tl, 'U', -1.0_wp )     !* local domain boundaries
151      CALL lbc_lnk( va_tl, 'V', -1.0_wp )
152      !
153#endif
154      ! Time filter and swap of dynamics arrays
155      ! ------------------------------------------
156      IF( neuler == 0 .AND. kt == nit000 ) THEN        !* Euler at first time-step: only swap
157         DO jk = 1, jpkm1
158            un_tl(:,:,jk) = ua_tl(:,:,jk)                          ! un <-- ua
159            vn_tl(:,:,jk) = va_tl(:,:,jk)
160         END DO
161      ELSE                                             !* Leap-Frog : Asselin filter and swap
162         IF( .NOT. lk_vvl ) THEN          ! applied on velocity
163            DO jk = 1, jpkm1
164               DO jj = 1, jpj
165                  DO ji = 1, jpi
166                     zuftl = un_tl(ji,jj,jk) + atfp * ( ub_tl(ji,jj,jk) - 2._wp * un_tl(ji,jj,jk) + ua_tl(ji,jj,jk) )
167                     zvftl = vn_tl(ji,jj,jk) + atfp * ( vb_tl(ji,jj,jk) - 2._wp * vn_tl(ji,jj,jk) + va_tl(ji,jj,jk) )
168                     !
169                     ub_tl(ji,jj,jk) = zuftl                      ! ub <-- filtered velocity
170                     vb_tl(ji,jj,jk) = zvftl
171                     un_tl(ji,jj,jk) = ua_tl(ji,jj,jk)             ! un <-- ua
172                     vn_tl(ji,jj,jk) = va_tl(ji,jj,jk)
173                  END DO
174               END DO
175            END DO
176         ELSE                                                ! applied on thickness weighted velocity
177            CALL ctl_stop ( 'dyn_nxt_tan: key_vvl not available yet in TAM' )
178         ENDIF
179      ENDIF
180      !
181      IF( nn_timing == 1 )  CALL timing_stop('dyn_nxt_tan')
182      !
183   END SUBROUTINE dyn_nxt_tan
184
185   SUBROUTINE dyn_nxt_adj ( kt )
186      !!----------------------------------------------------------------------
187      !!                  ***  ROUTINE dyn_nxt_tan  ***
188      !!
189      !! ** Purpose :   Compute the after horizontal velocity. Apply the boundary
190      !!             condition on the after velocity, achieved the time stepping
191      !!             by applying the Asselin filter on now fields and swapping
192      !!             the fields.
193      !!
194      !! ** Method  : * After velocity is compute using a leap-frog scheme:
195      !!                       (ua,va) = (ub,vb) + 2 rdt (ua,va)
196      !!             Note that with flux form advection and variable volume layer
197      !!             (lk_vvl=T), the leap-frog is applied on thickness weighted
198      !!             velocity.
199      !!             Note also that in filtered free surface (lk_dynspg_flt=T),
200      !!             the time stepping has already been done in dynspg module
201      !!
202      !!              * Apply lateral boundary conditions on after velocity
203      !!             at the local domain boundaries through lbc_lnk call,
204      !!             at the radiative open boundaries (lk_obc=T),
205      !!             at the relaxed   open boundaries (lk_bdy=T), and
206      !!             at the AGRIF zoom     boundaries (lk_agrif=T)
207      !!
208      !!              * Apply the time filter applied and swap of the dynamics
209      !!             arrays to start the next time step:
210      !!                (ub,vb) = (un,vn) + atfp [ (ub,vb) + (ua,va) - 2 (un,vn) ]
211      !!                (un,vn) = (ua,va).
212      !!             Note that with flux form advection and variable volume layer
213      !!             (lk_vvl=T), the time filter is applied on thickness weighted
214      !!             velocity.
215      !!
216      !! ** Action :   ub,vb   filtered before horizontal velocity of next time-step
217      !!               un,vn   now horizontal velocity of next time-step
218      !!----------------------------------------------------------------------
219      !! * Arguments
220      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
221#if ! defined key_dynspg_flt
222      REAL(wp) ::   z2dt         ! temporary scalar
223#endif
224      INTEGER  ::   ji, jj, jk, iku, ikv   ! dummy loop indices
225      REAL(wp) ::   zue3aad , zue3nad , zue3bad  ! temporary scalar
226      REAL(wp) ::   zve3aad , zve3nad , zve3bad  !    -         -
227      REAL(wp) ::   zufad   , zvfad              !    -         -
228      !!----------------------------------------------------------------------
229      !
230      IF( nn_timing == 1 )  CALL timing_start('dyn_nxt_adj')
231      !
232      ! adjoint local variables initialization
233      zue3aad = 0.0_wp ;  zue3nad = 0.0_wp ; zue3bad = 0.0_wp
234      zve3aad = 0.0_wp ;  zve3nad = 0.0_wp ; zve3bad = 0.0_wp
235      zufad   = 0.0_wp ;  zvfad   = 0.0_wp
236
237      IF( kt == nitend ) THEN
238         IF(lwp) WRITE(numout,*)
239         IF(lwp) WRITE(numout,*) 'dyn_nxt_adj : time stepping'
240         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
241      ENDIF
242      !
243      ! Time filter and swap of dynamics arrays
244      ! ------------------------------------------
245      IF( neuler == 0 .AND. kt == nit000 ) THEN        !* Euler at first time-step: only swap
246         DO jk = 1, jpkm1
247            ua_ad(:,:,jk) = ua_ad(:,:,jk) + un_ad(:,:,jk)          ! un_ad <-- ua_ad
248            va_ad(:,:,jk) = va_ad(:,:,jk) + vn_ad(:,:,jk)
249            un_ad(:,:,jk) = 0.0_wp
250            vn_ad(:,:,jk) = 0.0_wp
251         END DO
252      ELSE                                             !* Leap-Frog : Asselin filter and swap
253         IF( .NOT. lk_vvl ) THEN          ! applied on velocity
254            DO jk = 1, jpkm1
255               DO jj = 1, jpj
256                  DO ji = 1, jpi
257                     va_ad(ji,jj,jk) = va_ad(ji,jj,jk) + vn_ad(ji,jj,jk)
258                     ua_ad(ji,jj,jk) = ua_ad(ji,jj,jk) + un_ad(ji,jj,jk)
259                     un_ad(ji,jj,jk) = 0.0_wp
260                     vn_ad(ji,jj,jk) = 0.0_wp
261                     zvfad           = zvfad + vb_ad(ji,jj,jk)
262                     zufad           = zufad + ub_ad(ji,jj,jk)
263                     ub_ad(ji,jj,jk) = 0.0_wp
264                     vb_ad(ji,jj,jk) = 0.0_wp
265
266                     ub_ad(ji,jj,jk) = ub_ad(ji,jj,jk) + atfp  * zufad
267                     ua_ad(ji,jj,jk) = ua_ad(ji,jj,jk) + atfp  * zufad
268                     un_ad(ji,jj,jk) = un_ad(ji,jj,jk) + ( 1 - 2._wp * atfp ) * zufad
269                     vb_ad(ji,jj,jk) = vb_ad(ji,jj,jk) + atfp  * zvfad
270                     va_ad(ji,jj,jk) = va_ad(ji,jj,jk) + atfp  * zvfad
271                     vn_ad(ji,jj,jk) = vn_ad(ji,jj,jk) + ( 1 - 2._wp * atfp ) * zvfad
272                     zufad           = 0.0_wp
273                     zvfad           = 0.0_wp
274                  END DO
275               END DO
276            END DO
277         ELSE                                                ! applied on thickness weighted velocity
278            CALL ctl_stop ( 'dyn_nxt_adj: key_vvl not available yet in TAM' )
279         ENDIF
280      ENDIF
281
282#if defined key_dynspg_flt
283      !
284      ! Next velocity :   Leap-frog time stepping already done in dynspg_flt.F routine
285      ! -------------
286
287      ! Update after velocity on domain lateral boundaries      (only local domain required)
288      ! --------------------------------------------------
289      CALL lbc_lnk_adj( ua_ad, 'U', -1.0_wp )         ! local domain boundaries
290      CALL lbc_lnk_adj( va_ad, 'V', -1.0_wp )
291      !
292#else
293      !
294      ! Update after velocity on domain lateral boundaries
295      !
296      ! Update after velocity on domain lateral boundaries
297      ! --------------------------------------------------
298      CALL lbc_lnk_adj( va_ad, 'U', -1.0_wp )     !* local domain boundaries
299      CALL lbc_lnk_adj( ua_ad, 'V', -1.0_wp )
300      ! Next velocity :   Leap-frog time stepping
301      ! -------------
302      z2dt = 2. * rdt                                 ! Euler or leap-frog time step
303      IF( neuler == 0 .AND. kt == nit000 )  z2dt = rdt
304      !
305      IF( ln_dynadv_vec .OR. .NOT. lk_vvl ) THEN      ! applied on velocity
306         DO jk = 1, jpkm1
307            ua_ad(:,:,jk) = ua_ad(:,:,jk) * umask(:,:,jk)
308            va_ad(:,:,jk) = va_ad(:,:,jk) * vmask(:,:,jk)
309            ub_ad(:,:,jk) = ub_ad(:,:,jk) + ua_ad(:,:,jk)
310            vb_ad(:,:,jk) = vb_ad(:,:,jk) + va_ad(:,:,jk)
311            ua_ad(:,:,jk) = ua_ad(:,:,jk) * z2dt
312            va_ad(:,:,jk) = va_ad(:,:,jk) * z2dt
313         END DO
314      ELSE                                            ! applied on thickness weighted velocity
315         DO jk = 1, jpkm1
316            ua_ad(:,:,jk) = ua_ad(:,:,jk)  / fse3u_a(:,:,jk) * umask(:,:,jk)
317            va_ad(:,:,jk) = va_ad(:,:,jk)  / fse3v_a(:,:,jk) * vmask(:,:,jk)
318            ub_ad(:,:,jk) = ub_ad(:,:,jk) + ua_ad(:,:,jk)  * fse3u_b(:,:,jk)
319            vb_ad(:,:,jk) = vb_ad(:,:,jk) + va_ad(:,:,jk)  * fse3v_b(:,:,jk)
320            ua_ad(:,:,jk) = ua_ad(:,:,jk) * z2dt *fse3u_n(:,:,jk)
321            va_ad(:,:,jk) = va_ad(:,:,jk) * z2dt *fse3v_n(:,:,jk)
322         END DO
323      ENDIF
324#endif
325      !
326      IF( nn_timing == 1 )  CALL timing_stop('dyn_nxt_adj')
327      !
328   END SUBROUTINE dyn_nxt_adj
329
330   SUBROUTINE dyn_nxt_adj_tst( kumadt )
331      !!-----------------------------------------------------------------------
332      !!
333      !!                  ***  ROUTINE dyn_nxt_adj_tst ***
334      !!
335      !! ** Purpose : Test the adjoint routine.
336      !!
337      !! ** Method  : Verify the scalar product
338      !!
339      !!                 ( L dx )^T W dy  =  dx^T L^T W dy
340      !!
341      !!              where  L   = tangent routine
342      !!                     L^T = adjoint routine
343      !!                     W   = diagonal matrix of scale factors
344      !!                     dx  = input perturbation (random field)
345      !!                     dy  = L dx
346      !!
347      !! ** Action  : Separate tests are applied for the following dx and dy:
348      !!
349      !!              1) dx = ( SSH ) and dy = ( SSH )
350      !!
351      !! History :
352      !!        ! 08-08 (A. Vidard)
353      !!-----------------------------------------------------------------------
354      !! * Modules used
355
356      !! * Arguments
357      INTEGER, INTENT(IN) :: &
358         & kumadt             ! Output unit
359
360      INTEGER :: &
361         & ji,    &        ! dummy loop indices
362         & jj,    &
363         & jk
364      INTEGER, DIMENSION(jpi,jpj) :: &
365         & iseed_2d        ! 2D seed for the random number generator
366
367      !! * Local declarations
368      REAL(KIND=wp), DIMENSION(:,:,:), ALLOCATABLE :: &
369         & zun_tlin,     & ! Tangent input:   now   u-velocity
370         & zvn_tlin,     & ! Tangent input:   now   v-velocity
371         & zua_tlin,     & ! Tangent input:  after  u-velocity
372         & zva_tlin,     & ! Tangent input:  after  u-velocity
373         & zub_tlin,     & ! Tangent input:  before u-velocity
374         & zvb_tlin,     & ! Tangent input:  before u-velocity
375         & zun_adin,     & ! Adjoint input:   now   u-velocity
376         & zvn_adin,     & ! Adjoint input:   now   v-velocity
377         & zua_adin,     & ! Adjoint input:  after  u-velocity
378         & zva_adin,     & ! Adjoint input:  after  u-velocity
379         & zub_adin,     & ! Adjoint input:  before u-velocity
380         & zvb_adin,     & ! Adjoint input:  before u-velocity
381         & zun_tlout,    & ! Tangent output:  now   u-velocity
382         & zvn_tlout,    & ! Tangent output:  now   v-velocity
383         & zua_tlout,    & ! Tangent output: after  u-velocity
384         & zva_tlout,    & ! Tangent output: after  u-velocity
385         & zub_tlout,    & ! Tangent output: before u-velocity
386         & zvb_tlout,    & ! Tangent output: before u-velocity
387         & zun_adout,    & ! Adjoint output:  now   u-velocity
388         & zvn_adout,    & ! Adjoint output:  now   v-velocity
389         & zua_adout,    & ! Adjoint output: after  u-velocity
390         & zva_adout,    & ! Adjoint output: after  u-velocity
391         & zub_adout,    & ! Adjoint output: before u-velocity
392         & zvb_adout,    & ! Adjoint output: before u-velocity
393         & znu,          & ! 3D random field for u
394         & znv,          & ! 3D random field for v
395         & zbu,          & ! 3D random field for u
396         & zbv,          & ! 3D random field for v
397         & zau,          & ! 3D random field for u
398         & zav             ! 3D random field for v
399
400      REAL(KIND=wp) :: &
401         & zsp1,         & ! scalar product involving the tangent routine
402         & zsp1_1,       & !   scalar product components
403         & zsp1_2,       &
404         & zsp1_3,       &
405         & zsp1_4,       &
406         & zsp1_5,       &
407         & zsp1_6,       &
408         & zsp2,         & ! scalar product involving the adjoint routine
409         & zsp2_1,       & !   scalar product components
410         & zsp2_2,       &
411         & zsp2_3,       &
412         & zsp2_4,       &
413         & zsp2_5,       &
414         & zsp2_6
415      CHARACTER(LEN=14) :: cl_name
416
417      ! Allocate memory
418
419      ALLOCATE( &
420         & zun_tlin(jpi,jpj,jpk),     &
421         & zvn_tlin(jpi,jpj,jpk),     &
422         & zua_tlin(jpi,jpj,jpk),     &
423         & zva_tlin(jpi,jpj,jpk),     &
424         & zub_tlin(jpi,jpj,jpk),     &
425         & zvb_tlin(jpi,jpj,jpk),     &
426         & zun_adin(jpi,jpj,jpk),     &
427         & zvn_adin(jpi,jpj,jpk),     &
428         & zua_adin(jpi,jpj,jpk),     &
429         & zva_adin(jpi,jpj,jpk),     &
430         & zub_adin(jpi,jpj,jpk),     &
431         & zvb_adin(jpi,jpj,jpk),     &
432         & zun_tlout(jpi,jpj,jpk),    &
433         & zvn_tlout(jpi,jpj,jpk),    &
434         & zua_tlout(jpi,jpj,jpk),    &
435         & zva_tlout(jpi,jpj,jpk),    &
436         & zub_tlout(jpi,jpj,jpk),    &
437         & zvb_tlout(jpi,jpj,jpk),    &
438         & zun_adout(jpi,jpj,jpk),    &
439         & zvn_adout(jpi,jpj,jpk),    &
440         & zua_adout(jpi,jpj,jpk),    &
441         & zva_adout(jpi,jpj,jpk),    &
442         & zub_adout(jpi,jpj,jpk),    &
443         & zvb_adout(jpi,jpj,jpk),    &
444         & znu(jpi,jpj,jpk),          &
445         & znv(jpi,jpj,jpk),          &
446         & zbu(jpi,jpj,jpk),          &
447         & zbv(jpi,jpj,jpk),          &
448         & zau(jpi,jpj,jpk),          &
449         & zav(jpi,jpj,jpk)           &
450         & )
451
452
453      !==================================================================
454      ! 1) dx = ( un_tl, vn_tl, hdivn_tl ) and
455      !    dy = ( hdivb_tl, hdivn_tl )
456      !==================================================================
457
458      !--------------------------------------------------------------------
459      ! Reset the tangent and adjoint variables
460      !--------------------------------------------------------------------
461
462          zun_tlin(:,:,:) = 0.0_wp
463          zvn_tlin(:,:,:) = 0.0_wp
464          zua_tlin(:,:,:) = 0.0_wp
465          zva_tlin(:,:,:) = 0.0_wp
466          zub_tlin(:,:,:) = 0.0_wp
467          zvb_tlin(:,:,:) = 0.0_wp
468          zun_adin(:,:,:) = 0.0_wp
469          zvn_adin(:,:,:) = 0.0_wp
470          zua_adin(:,:,:) = 0.0_wp
471          zva_adin(:,:,:) = 0.0_wp
472          zub_adin(:,:,:) = 0.0_wp
473          zvb_adin(:,:,:) = 0.0_wp
474          zun_tlout(:,:,:) = 0.0_wp
475          zvn_tlout(:,:,:) = 0.0_wp
476          zua_tlout(:,:,:) = 0.0_wp
477          zva_tlout(:,:,:) = 0.0_wp
478          zub_tlout(:,:,:) = 0.0_wp
479          zvb_tlout(:,:,:) = 0.0_wp
480          zun_adout(:,:,:) = 0.0_wp
481          zvn_adout(:,:,:) = 0.0_wp
482          zua_adout(:,:,:) = 0.0_wp
483          zva_adout(:,:,:) = 0.0_wp
484          zub_adout(:,:,:) = 0.0_wp
485          zvb_adout(:,:,:) = 0.0_wp
486          znu(:,:,:) = 0.0_wp
487          znv(:,:,:) = 0.0_wp
488          zbu(:,:,:) = 0.0_wp
489          zbv(:,:,:) = 0.0_wp
490          zau(:,:,:) = 0.0_wp
491          zav(:,:,:) = 0.0_wp
492
493          un_tl(:,:,:) = 0.0_wp
494          vn_tl(:,:,:) = 0.0_wp
495          ua_tl(:,:,:) = 0.0_wp
496          va_tl(:,:,:) = 0.0_wp
497          ub_tl(:,:,:) = 0.0_wp
498          vb_tl(:,:,:) = 0.0_wp
499          un_ad(:,:,:) = 0.0_wp
500          vn_ad(:,:,:) = 0.0_wp
501          ua_ad(:,:,:) = 0.0_wp
502          va_ad(:,:,:) = 0.0_wp
503          ub_ad(:,:,:) = 0.0_wp
504          vb_ad(:,:,:) = 0.0_wp
505
506
507      !--------------------------------------------------------------------
508      ! Initialize the tangent input with random noise: dx
509      !--------------------------------------------------------------------
510
511      CALL grid_random(  znu, 'U', 0.0_wp, stdu )
512      CALL grid_random(  znv, 'V', 0.0_wp, stdv )
513      CALL grid_random(  zbu, 'U', 0.0_wp, stdu )
514      CALL grid_random(  zbv, 'V', 0.0_wp, stdv )
515      CALL grid_random(  zau, 'U', 0.0_wp, stdu )
516      CALL grid_random(  zav, 'V', 0.0_wp, stdv )
517
518      DO jk = 1, jpk
519         DO jj = nldj, nlej
520            DO ji = nldi, nlei
521               zun_tlin(ji,jj,jk) = znu(ji,jj,jk)
522               zvn_tlin(ji,jj,jk) = znv(ji,jj,jk)
523               zub_tlin(ji,jj,jk) = zbu(ji,jj,jk)
524               zvb_tlin(ji,jj,jk) = zbv(ji,jj,jk)
525               zua_tlin(ji,jj,jk) = zau(ji,jj,jk)
526               zva_tlin(ji,jj,jk) = zav(ji,jj,jk)
527            END DO
528         END DO
529      END DO
530
531      un_tl(:,:,:) = zun_tlin(:,:,:)
532      vn_tl(:,:,:) = zvn_tlin(:,:,:)
533      ub_tl(:,:,:) = zub_tlin(:,:,:)
534      vb_tl(:,:,:) = zvb_tlin(:,:,:)
535      ua_tl(:,:,:) = zua_tlin(:,:,:)
536      va_tl(:,:,:) = zva_tlin(:,:,:)
537
538      call dyn_nxt_tan ( nit000 )
539
540      zun_tlout(:,:,:) = un_tl(:,:,:)
541      zvn_tlout(:,:,:) = vn_tl(:,:,:)
542      zub_tlout(:,:,:) = ub_tl(:,:,:)
543      zvb_tlout(:,:,:) = vb_tl(:,:,:)
544      zua_tlout(:,:,:) = ua_tl(:,:,:)
545      zva_tlout(:,:,:) = va_tl(:,:,:)
546
547      !--------------------------------------------------------------------
548      ! Initialize the adjoint variables: dy^* = W dy
549      !--------------------------------------------------------------------
550
551      DO jk = 1, jpk
552        DO jj = nldj, nlej
553           DO ji = nldi, nlei
554              zun_adin(ji,jj,jk) = zun_tlout(ji,jj,jk) &
555                 &               * e1u(ji,jj) * e2u(ji,jj) * fse3u(ji,jj,jk) &
556                 &               * umask(ji,jj,jk)
557              zvn_adin(ji,jj,jk) = zvn_tlout(ji,jj,jk) &
558                 &               * e1v(ji,jj) * e2v(ji,jj) * fse3v(ji,jj,jk) &
559                 &               * vmask(ji,jj,jk)
560              zub_adin(ji,jj,jk) = zub_tlout(ji,jj,jk) &
561                 &               * e1u(ji,jj) * e2u(ji,jj) * fse3u(ji,jj,jk) &
562                 &               * umask(ji,jj,jk)
563              zvb_adin(ji,jj,jk) = zvb_tlout(ji,jj,jk) &
564                 &               * e1v(ji,jj) * e2v(ji,jj) * fse3v(ji,jj,jk) &
565                 &               * vmask(ji,jj,jk)
566              zua_adin(ji,jj,jk) = zua_tlout(ji,jj,jk) &
567                 &               * e1u(ji,jj) * e2u(ji,jj) * fse3u(ji,jj,jk) &
568                 &               * umask(ji,jj,jk)
569              zva_adin(ji,jj,jk) = zva_tlout(ji,jj,jk) &
570                 &               * e1v(ji,jj) * e2v(ji,jj) * fse3v(ji,jj,jk) &
571                 &               * vmask(ji,jj,jk)
572            END DO
573         END DO
574      END DO
575      !--------------------------------------------------------------------
576      ! Compute the scalar product: ( L dx )^T W dy
577      !--------------------------------------------------------------------
578
579      zsp1_1 = DOT_PRODUCT( zun_tlout, zun_adin )
580      zsp1_2 = DOT_PRODUCT( zvn_tlout, zvn_adin )
581      zsp1_3 = DOT_PRODUCT( zub_tlout, zub_adin )
582      zsp1_4 = DOT_PRODUCT( zvb_tlout, zvb_adin )
583      zsp1_5 = DOT_PRODUCT( zua_tlout, zua_adin )
584      zsp1_6 = DOT_PRODUCT( zva_tlout, zva_adin )
585      zsp1   = zsp1_1 + zsp1_2 + zsp1_3 + zsp1_4 + zsp1_5 + zsp1_6
586
587      !--------------------------------------------------------------------
588      ! Call the adjoint routine: dx^* = L^T dy^*
589      !--------------------------------------------------------------------
590
591      un_ad(:,:,:) = zun_adin(:,:,:)
592      vn_ad(:,:,:) = zvn_adin(:,:,:)
593      ub_ad(:,:,:) = zub_adin(:,:,:)
594      vb_ad(:,:,:) = zvb_adin(:,:,:)
595      ua_ad(:,:,:) = zua_adin(:,:,:)
596      va_ad(:,:,:) = zva_adin(:,:,:)
597
598      CALL dyn_nxt_adj ( nit000 )
599
600      zun_adout(:,:,:) = un_ad(:,:,:)
601      zvn_adout(:,:,:) = vn_ad(:,:,:)
602      zub_adout(:,:,:) = ub_ad(:,:,:)
603      zvb_adout(:,:,:) = vb_ad(:,:,:)
604      zua_adout(:,:,:) = ua_ad(:,:,:)
605      zva_adout(:,:,:) = va_ad(:,:,:)
606
607      zsp2_1 = DOT_PRODUCT( zun_tlin, zun_adout )
608      zsp2_2 = DOT_PRODUCT( zvn_tlin, zvn_adout )
609      zsp2_3 = DOT_PRODUCT( zub_tlin, zub_adout )
610      zsp2_4 = DOT_PRODUCT( zvb_tlin, zvb_adout )
611      zsp2_5 = DOT_PRODUCT( zua_tlin, zua_adout )
612      zsp2_6 = DOT_PRODUCT( zva_tlin, zva_adout )
613      zsp2   = zsp2_1 + zsp2_2 + zsp2_3 + zsp2_4 + zsp2_5 + zsp2_6
614
615      ! Compare the scalar products
616      ! 14 char:'12345678901234'
617      cl_name = 'dyn_nxt_adj   '
618      CALL prntst_adj( cl_name, kumadt, zsp1, zsp2 )
619
620      DEALLOCATE( &
621         & zun_tlin,     &
622         & zvn_tlin,     &
623         & zua_tlin,     &
624         & zva_tlin,     &
625         & zub_tlin,     &
626         & zvb_tlin,     &
627         & zun_adin,     &
628         & zvn_adin,     &
629         & zua_adin,     &
630         & zva_adin,     &
631         & zub_adin,     &
632         & zvb_adin,     &
633         & zun_tlout,    &
634         & zvn_tlout,    &
635         & zua_tlout,    &
636         & zva_tlout,    &
637         & zub_tlout,    &
638         & zvb_tlout,    &
639         & zun_adout,    &
640         & zvn_adout,    &
641         & zua_adout,    &
642         & zva_adout,    &
643         & zub_adout,    &
644         & zvb_adout,    &
645         & znu,          &
646         & znv,          &
647         & zbu,          &
648         & zbv,          &
649         & zau,          &
650         & zav           &
651         & )
652
653
654   END SUBROUTINE dyn_nxt_adj_tst
655   !!======================================================================
656#endif
657END MODULE dynnxt_tam
Note: See TracBrowser for help on using the repository browser.