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.
sbcana_tam.F90 in branches/2010_and_older/TAM_V3_2_2/NEMOTAM/OPATAM_SRC/SBC – NEMO

source: branches/2010_and_older/TAM_V3_2_2/NEMOTAM/OPATAM_SRC/SBC/sbcana_tam.F90 @ 7797

Last change on this file since 7797 was 2578, checked in by rblod, 13 years ago

first import of NEMOTAM 3.2.2

File size: 22.2 KB
Line 
1MODULE sbcana_tam
2#if defined key_tam
3   !!======================================================================
4   !!                       ***  MODULE  sbcana  ***
5   !! Ocean forcing:  analytical momentum, heat and freshwater forcings
6   !!=====================================================================
7   !! History of the direct module : 
8   !!            3.0   ! 2006-06  (G. Madec)  Original code
9   !!            3.2   ! 2009-07  (G. Madec)  Style only
10   !! History of the T&A module :
11   !!            3.0   ! 2009-10  (F. Vigilant) original verison
12   !!            3.2   ! 2020-04  (A. Vidard) nemo 3.2 update
13   !!----------------------------------------------------------------------
14
15   !!----------------------------------------------------------------------
16   !!   sbc_ana  : set an analytical ocean forcing
17   !!   sbc_gyre : set the GYRE configuration analytical forcing
18   !!----------------------------------------------------------------------
19   USE par_kind      , ONLY: & !
20      & wp
21   USE oce_tam       , ONLY: & ! ocean dynamics and tracers
22      & tb_tl,             &
23      & tb_ad
24   USE par_oce       , ONLY: & ! Ocean space and time domain variables
25      & jpi,                 &
26      & jpj,                 &
27      & jpk,                 &
28      & jpiglo
29   USE dom_oce       , ONLY: & ! ocean space and time domain
30      & e1t,                 &
31      & e2t,                 &
32#if defined key_zco
33      & e3t_0,               &
34#else
35      & e3t,                 &
36#endif
37      & tmask,               &
38      & tmask_i,             &
39      & mig,                 &
40      & mjg,                 &
41      & nldi,                &
42      & nldj,                &
43      & nlei,                &
44      & nlej
45   USE in_out_manager, ONLY: & ! I/O manager
46      & lwp,                 &
47      & numout,              &
48      & numnam,              &
49      & nbench,              &
50      & nbit_cmp,            & 
51      & nit000,              & 
52      & nitend
53   USE lib_mpp       , ONLY: & ! distributed memory computing
54      & lk_mpp,              &
55      & mpp_sum
56   USE sbc_oce_tam   , ONLY: & ! surface variables
57      & emp_tl,              &
58      & emps_tl,             &
59      & emp_ad,              &
60      & emps_ad,             &
61      & qsr_tl,              & ! thermohaline fluxes
62      & qsr_ad,              &
63      & qns_tl,              &
64      & qns_ad,              &
65      & utau_tl,             &
66      & utau_ad,             &
67      & vtau_tl,             &
68      & vtau_ad,             &
69      & taum_tl,             &
70      & taum_ad,             &
71      & wndm_tl,             &
72      & wndm_ad
73   USE tstool_tam    , ONLY: &
74      & prntst_adj,          &
75      & stdemp,              & !   evaporation minus precip
76      & stdt                 !   sea surface height
77   USE gridrandom    , ONLY: & ! Random Gaussian noise on grids
78      & grid_random
79   USE dotprodfld    , ONLY: & ! Computes dot product for 3D and 2D fields
80      & dot_product
81
82   IMPLICIT NONE
83   PRIVATE
84
85   PUBLIC   sbc_ana_tan        ! routine called sbcmod_tam
86   PUBLIC   sbc_ana_adj        ! routine called sbcmod_tam
87   PUBLIC   sbc_gyre_tan       ! routine called sbcmod_tam
88   PUBLIC   sbc_gyre_adj       ! routine called sbcmod_tam
89   PUBLIC   sbc_gyre_adj_tst   ! routine called by tst
90
91   !! * Namelist namsbc_ana
92   INTEGER  ::   nn_tau000 = 1      ! nb of time-step during which the surface stress
93      !                             ! increase from 0 to its nominal value
94   REAL(wp) ::   rn_utau0  = 0.e0   ! constant wind stress value in i-direction
95   REAL(wp) ::   rn_vtau0  = 0.e0   ! constant wind stress value in j-direction
96   REAL(wp) ::   rn_qns0   = 0.e0   ! non solar heat flux
97   REAL(wp) ::   rn_qsr0   = 0.e0   !     solar heat flux
98   REAL(wp) ::   rn_emp0   = 0.e0   ! net freshwater flux
99 
100   REAL(wp) ::   rhoa      = 1.22   ! Air density kg/m3
101   REAL(wp) ::   cdrag     = 1.5e-3 ! drag coefficient
102 
103   !! * Substitutions
104#  include "domzgr_substitute.h90"
105#  include "vectopt_loop_substitute.h90"
106   !!----------------------------------------------------------------------
107   !!   OPA 9.0 , LOCEAN-IPSL (2006)
108   !! $Id$
109   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
110   !!----------------------------------------------------------------------
111
112CONTAINS
113
114   SUBROUTINE sbc_ana_tan( kt )
115      !!---------------------------------------------------------------------
116      !!                    ***  ROUTINE sbc_ana_tan ***
117      !!             
118      !! ** Purpose :   provide at each time-step the ocean surface boundary
119      !!              condition, i.e. the momentum, heat and freshwater fluxes.
120      !!
121      !! ** Method  :   Constant and uniform surface forcing specified from
122      !!              namsbc_ana namelist parameters. All the fluxes are time
123      !!              independant except the stresses which increase from zero
124      !!              during the first nn_tau000 time-step
125      !!                CAUTION : never mask the surface stress field !
126      !!
127      !! ** Action  : - set the ocean surface boundary condition, i.e. 
128      !!                   utau, vtau, taum, wndm, qns, qsr, emp, emps
129      !!----------------------------------------------------------------------
130      INTEGER, INTENT(in) ::   kt       ! ocean time step
131      !!
132      NAMELIST/namsbc_ana/ nn_tau000, rn_utau0, rn_vtau0, rn_qns0, rn_qsr0, rn_emp0
133      !!---------------------------------------------------------------------
134      !
135      IF( kt == nit000 ) THEN
136         !
137         REWIND ( numnam )                   ! Read Namelist namsbc : surface fluxes
138         READ   ( numnam, namsbc_ana )
139         !
140         IF(lwp) WRITE(numout,*)' '
141         IF(lwp) WRITE(numout,*)' sbc_ana_tan : Constant surface fluxes read in namsbc_ana namelist'
142         IF(lwp) WRITE(numout,*)' ~~~~~~~ '
143         IF(lwp) WRITE(numout,*)'              spin up of the stress  nn_tau000 = ', nn_tau000, ' time-steps'
144         IF(lwp) WRITE(numout,*)'              constant i-stress      rn_utau0  = ', rn_utau0 , ' N/m2'
145         IF(lwp) WRITE(numout,*)'              constant j-stress      rn_vtau0  = ', rn_vtau0 , ' N/m2'
146         IF(lwp) WRITE(numout,*)'              non solar heat flux    rn_qns0   = ', rn_qns0  , ' W/m2'
147         IF(lwp) WRITE(numout,*)'              solar heat flux        rn_qsr0   = ', rn_qsr0  , ' W/m2'
148         IF(lwp) WRITE(numout,*)'              net heat flux          rn_emp0   = ', rn_emp0  , ' Kg/m2/s'
149         !
150         nn_tau000 = MAX( nn_tau000, 1 )   ! must be >= 1
151         qns_tl   (:,:) = 0.0_wp
152         qsr_tl   (:,:) = 0.0_wp
153         emp_tl   (:,:) = 0.0_wp
154         emps_tl  (:,:) = 0.0_wp
155         utau_tl  (:,:) = 0.0_wp
156         vtau_tl  (:,:) = 0.0_wp
157         taum_tl  (:,:) = 0.0_wp
158         wndm_tl  (:,:) = 0.0_wp
159         !
160      ENDIF
161      !
162   END SUBROUTINE sbc_ana_tan
163
164   SUBROUTINE sbc_ana_adj( kt )
165      !!---------------------------------------------------------------------
166      !!                    ***  ROUTINE sbc_ana_adj ***
167      !!             
168      !! ** Purpose :   provide at each time-step the ocean surface boundary
169      !!              condition, i.e. the momentum, heat and freshwater fluxes.
170      !!
171      !! ** Method  :   Constant and uniform surface forcing specified from
172      !!              namsbc_ana namelist parameters. All the fluxes are time
173      !!              independant except the stresses which increase from zero
174      !!              during the first nn_tau000 time-step
175      !!                CAUTION : never mask the surface stress field !
176      !!
177      !! ** Action  : - set the ocean surface boundary condition, i.e. 
178      !!                   utau, vtau, taum, wndm, qns, qsr, emp, emps
179      !!----------------------------------------------------------------------
180      INTEGER, INTENT(in) ::   kt       ! ocean time step
181      !!
182      NAMELIST/namsbc_ana/ nn_tau000, rn_utau0, rn_vtau0, rn_qns0, rn_qsr0, rn_emp0
183      !!---------------------------------------------------------------------
184      !
185      IF( kt == nitend ) THEN
186         !
187         IF(lwp) WRITE(numout,*)' '
188         IF(lwp) WRITE(numout,*)' sbc_ana_adj : Constant surface fluxes read in namsbc_ana namelist'
189         IF(lwp) WRITE(numout,*)' ~~~~~~~ '
190
191         nn_tau000 = MAX( nn_tau000, 1 )   ! must be >= 1
192         qns_ad   (:,:) = 0.0_wp
193         qsr_ad   (:,:) = 0.0_wp
194         emp_ad   (:,:) = 0.0_wp
195         emps_ad  (:,:) = 0.0_wp
196         utau_ad  (:,:) = 0.0_wp
197         vtau_ad  (:,:) = 0.0_wp
198         taum_ad  (:,:) = 0.0_wp
199         wndm_ad  (:,:) = 0.0_wp
200         !
201      ENDIF
202      !
203   END SUBROUTINE sbc_ana_adj
204
205
206   SUBROUTINE sbc_gyre_tan( kt )
207      !!---------------------------------------------------------------------
208      !!                    ***  ROUTINE sbc_gyre_tam ***
209      !!             
210      !! ** Purpose :   provide at each time-step the GYRE surface boundary
211      !!              condition, i.e. the momentum, heat and freshwater fluxes.
212      !!
213      !! ** Method  :   analytical seasonal cycle for GYRE configuration.
214      !!                CAUTION : never mask the surface stress field !
215      !!
216      !! ** Action  : - set the ocean surface boundary condition, i.e.   
217      !!                   utau, vtau, taum, wndm, qns, qsr, emp, emps
218      !!----------------------------------------------------------------------
219      INTEGER, INTENT(in) ::   kt          ! ocean time step
220      !!
221      INTEGER  ::   ji, jj                 ! dummy loop indices
222      REAL(wp) ::   ztstar
223      REAL(wp) ::   ztrp
224      REAL(wp) ::   zsumemp_tl, zsurf
225      !!---------------------------------------------------------------------
226         
227      ! ---------------------------- !
228      !  heat and freshwater fluxes  !
229      ! ---------------------------- !
230      !same temperature, E-P as in HAZELEGER 2000
231
232      ztrp= - 40.e0        ! retroaction term on heat fluxes (W/m2/K)
233      DO jj = 1, jpj
234         DO ji = 1, jpi
235            ! domain from 15 deg to 50 deg between 27 and 28  degC at 15N, -3
236            ! and 13 degC at 50N 53.5 + or - 11 = 1/4 period :
237            ! 64.5 in summer, 42.5 in winter
238            ! 23.5 deg : tropics
239            qsr_tl (ji,jj) =  0.0_wp
240            qns_tl (ji,jj) = ztrp *  tb_tl(ji,jj,1) 
241            emp_tl (ji,jj) =  0.0_wp
242         END DO
243      END DO
244      emps_tl(:,:) = emp_tl(:,:)
245
246      ! Compute the emp flux such as its integration on the whole domain at each time is zero
247      IF( nbench /= 1 .AND. nbit_cmp /= 1 ) THEN
248         zsumemp_tl = 0.e0   ;   zsurf = 0.e0
249         DO jj = 1, jpj
250            DO ji = 1, jpi
251               zsumemp_tl = zsumemp_tl + emp_tl(ji,jj) * tmask(ji,jj,1) * tmask_i(ji,jj)
252               zsurf   = zsurf   +              tmask(ji,jj,1) * tmask_i(ji,jj)
253            END DO
254         END DO
255
256         IF( lk_mpp )   CALL mpp_sum( zsumemp_tl  )       ! sum over the global domain
257         IF( lk_mpp )   CALL mpp_sum( zsurf    )       ! sum over the global domain
258
259         ! Default GYRE configuration
260         zsumemp_tl = zsumemp_tl / zsurf
261      ELSE
262         ! Benchmark GYRE configuration (to allow the bit to bit comparison between Mpp/Mono case)
263         zsumemp_tl = 0.e0   ;    zsurf = 0.e0
264      ENDIF
265
266      !salinity terms
267      emp_tl (:,:) = emp_tl(:,:) - zsumemp_tl * tmask(:,:,1)
268      emps_tl(:,:) = emp_tl(:,:)
269
270   END SUBROUTINE sbc_gyre_tan
271
272   SUBROUTINE sbc_gyre_adj( kt )
273      !!---------------------------------------------------------------------
274      !!                    ***  ROUTINE sbc_gyre_adj ***
275      !!             
276      !! ** Purpose :   provide at each time-step the ocean surface boundary
277      !!      condition, i.e. the momentum, heat and freshwater fluxes.
278      !!
279      !! ** Method  :   analytical seasonal cycle for GYRE configuration.
280      !!      * C A U T I O N : never mask the surface stress field !
281      !!
282      !! ** Action  : - set the ocean surface boundary condition, i.e.   
283      !!                   utau, vtau, qns, qsr, emp, emps
284      !!
285      !! Reference : Hazeleger, W., and S. Drijfhout, JPO, 30, 677-695, 2000.
286      !!----------------------------------------------------------------------
287      INTEGER, INTENT(in) ::   kt          ! ocean time step
288
289      INTEGER  ::   ji, jj                 ! dummy loop indices
290      REAL(wp) ::   ztstar
291      REAL(wp) ::   ztrp
292      REAL(wp) ::   zsumemp_ad, zsurf
293      !!---------------------------------------------------------------------
294     
295      zsumemp_ad = 0.0_wp 
296      zsurf = 0.0_wp
297      DO jj = 1, jpj
298         DO ji = 1, jpi
299            emp_ad (ji,jj) = emp_ad(ji,jj) + emps_ad(ji,jj)
300            emps_ad(ji,jj) = 0.0_wp
301         END DO
302      END DO
303      DO jj = 1, jpj
304         DO ji = 1, jpi
305            zsumemp_ad = zsumemp_ad - emp_ad (ji,jj) * tmask(ji,jj,1)
306         END DO
307      END DO
308
309      ! Compute the emp flux such as its integration on the whole domain at each time is zero
310      IF( nbench /= 1 .AND. nbit_cmp /= 1 ) THEN
311
312         DO jj = 1, jpj
313            DO ji = 1, jpi
314               zsurf   = zsurf   +              tmask(ji,jj,1) * tmask_i(ji,jj)
315            END DO
316         END DO
317         ! Default GYRE configuration
318         zsumemp_ad = zsumemp_ad / zsurf
319
320         IF( lk_mpp )   CALL mpp_sum( zsurf    )       ! sum over the global domain
321         IF( lk_mpp )   CALL mpp_sum( zsumemp_ad  )       ! sum over the global domain
322
323         DO jj = 1, jpj
324            DO ji = 1, jpi
325               emp_ad(ji,jj) = emp_ad(ji,jj) + zsumemp_ad * tmask(ji,jj,1) * tmask_i(ji,jj)
326            END DO
327         END DO
328         zsumemp_ad = 0.0_wp   ;   zsurf = 0.0_wp
329      ELSE
330         ! Benchmark GYRE configuration (to allow the bit to bit comparison between Mpp/Mono case)
331         zsumemp_ad = 0.0_wp   ;    zsurf = 0.0_wp
332      ENDIF
333
334      DO jj = 1, jpj
335         DO ji = 1, jpi
336            emp_ad (ji,jj) = emp_ad(ji,jj) + emps_ad(ji,jj)
337            emps_ad(ji,jj) = 0.0_wp
338         END DO
339      END DO 
340
341      ! ---------------------------- !
342      !  heat and freshwater fluxes  !
343      ! ---------------------------- !
344      !same temperature, E-P as in HAZELEGER 2000
345
346      ztrp= - 40.e0        ! retroaction term on heat fluxes (W/m2/K)
347      DO jj = 1, jpj
348         DO ji = 1, jpi
349            ! domain from 15 deg to 50 deg between 27 and 28  degC at 15N, -3
350            ! and 13 degC at 50N 53.5 + or - 11 = 1/4 period :
351            ! 64.5 in summer, 42.5 in winter
352            ! 23.5 deg : tropics
353            emp_ad (ji,jj)   =  0.0_wp
354            tb_ad  (ji,jj,1) = tb_ad(ji,jj,1) + ztrp * qns_ad (ji,jj)
355            qns_ad (ji,jj)   = 0.0_wp
356            qsr_ad (ji,jj)   =  0.0_wp
357         END DO
358      END DO
359
360   END SUBROUTINE sbc_gyre_adj
361
362   SUBROUTINE sbc_gyre_adj_tst ( kumadt )
363      !!-----------------------------------------------------------------------
364      !!
365      !!                  ***  ROUTINE example_adj_tst ***
366      !!
367      !! ** Purpose : Test the adjoint routine.
368      !!
369      !! ** Method  : Verify the scalar product
370      !!           
371      !!                 ( L dx )^T W dy  =  dx^T L^T W dy
372      !!
373      !!              where  L   = tangent routine
374      !!                     L^T = adjoint routine
375      !!                     W   = diagonal matrix of scale factors
376      !!                     dx  = input perturbation (random field)
377      !!                     dy  = L dx
378      !!                   
379      !! History :
380      !!        ! 09-10 (F. Vigilant)
381      !!-----------------------------------------------------------------------
382      !! * Modules used
383
384      !! * Arguments
385      INTEGER, INTENT(IN) :: &
386         & kumadt             ! Output unit
387 
388      !! * Local declarations
389      INTEGER ::  &
390         & istp,  &
391         & jstp,  &
392         & ji,    &        ! dummy loop indices
393         & jj,    &       
394         & jk   
395      INTEGER, DIMENSION(jpi,jpj) :: &
396         & iseed_2d        ! 2D seed for the random number generator
397      REAL(KIND=wp) :: &
398         & zsp1,         & ! scalar product involving the tangent routine
399         & zsp2            ! scalar product involving the adjoint routine
400      REAL(KIND=wp), DIMENSION(:,:), ALLOCATABLE :: &
401         & zemp_tlin ,     & ! Tangent input
402         & zemp_tlout,     & ! Tangent output
403         & zemps_tlout,    & ! Tangent output
404         & zqns_tlout,     & ! Tangent output
405         & zemp_adin ,     & ! Adjoint input
406         & zemps_adin,     & ! Adjoint input
407         & zqns_adin ,     & ! Adjoint input
408         & zemp_adout,     & ! Adjoint output
409         & zr                ! 2D random field
410      REAL(KIND=wp), DIMENSION(:,:,:), ALLOCATABLE :: &
411         & ztb_tlin  ,     & ! Tangent input
412         & ztb_adout ,     & ! Adjoint output
413         & z3r               ! 3D random field
414      CHARACTER(LEN=14) :: cl_name
415      ! Allocate memory
416
417      ALLOCATE( &
418         & zemp_tlin(  jpi,jpj),     &
419         & ztb_tlin(jpi,jpj,jpk),    &
420         & zemp_tlout( jpi,jpj),     &
421         & zemps_tlout( jpi,jpj),    &
422         & zqns_tlout(  jpi,jpj),    &
423         & ztb_adout(jpi,jpj,jpk),   &
424         & zemp_adin(  jpi,jpj),     &
425         & zemps_adin( jpi,jpj),     &
426         & zqns_adin(  jpi,jpj),     &
427         & zemp_adout( jpi,jpj),     &
428         & zr(         jpi,jpj),     &
429         & z3r(     jpi,jpj,jpk)     &
430         & )
431      !==================================================================
432      ! 1) dx = ( emp_tl, emps_tl, ssh_tl ) and
433      !    dy = ( emp_tl, emps_tl )
434      !==================================================================
435      ! Test for time steps nit000 and nit000 + 1 (the matrix changes)
436
437      DO jstp = nit000, nit000 + 1
438
439      !--------------------------------------------------------------------
440      ! Reset the tangent and adjoint variables
441      !--------------------------------------------------------------------
442          zemp_tlin  (:,:) = 0.0_wp
443          ztb_tlin (:,:,:) = 0.0_wp
444          zemp_tlout (:,:) = 0.0_wp
445          zemps_tlout(:,:) = 0.0_wp
446          zqns_tlout (:,:) = 0.0_wp
447          zemp_adin  (:,:) = 0.0_wp
448          zemps_adin (:,:) = 0.0_wp
449          zqns_adin  (:,:) = 0.0_wp
450          zemp_adout (:,:) = 0.0_wp
451          ztb_adout(:,:,:) = 0.0_wp
452          z3r(:,:,:)       = 0.0_wp
453          zr(:,:)          = 0.0_wp
454
455          qns_tl (:,:)     = 0.0_wp
456          qsr_tl (:,:)     = 0.0_wp
457          emps_tl(:,:)     = 0.0_wp
458          qsr_ad (:,:)     = 0.0_wp
459          tb_ad(:,:,:)     = 0.0_wp
460 
461      !--------------------------------------------------------------------
462      ! Initialize the tangent input with random noise: dx
463      !--------------------------------------------------------------------
464
465          DO jj = 1, jpj
466             DO ji = 1, jpi
467                iseed_2d(ji,jj) = - ( 596035 + &
468                     &                  mig(ji) + ( mjg(jj) - 1 ) * jpiglo )
469             END DO
470          END DO
471          CALL grid_random( iseed_2d, zr, 'T', 0.0_wp, stdemp )
472          DO jj = nldj, nlej
473             DO ji = nldi, nlei
474                zemp_tlin(ji,jj) = zr(ji,jj) 
475             END DO
476          END DO
477          DO jj = 1, jpj
478             DO ji = 1, jpi
479                iseed_2d(ji,jj) = - ( 446251 + &
480                     &                  mig(ji) + ( mjg(jj) - 1 ) * jpiglo )
481             END DO
482          END DO
483          CALL grid_random( iseed_2d, z3r, 'T', 0.0_wp, stdt )
484          DO jk = 1, jpk
485             DO jj = nldj, nlej
486                DO ji = nldi, nlei
487                   ztb_tlin(ji,jj,jk) = z3r(ji,jj,jk) 
488                END DO
489             END DO
490          END DO
491
492          tb_tl(:,:,:) = ztb_tlin(:,:,:)
493          emp_tl (:,:) = zemp_tlin (:,:)
494
495          CALL sbc_gyre_tan( istp )
496
497          zemps_tlout(:,:) = emps_tl(:,:)
498          zemp_tlout (:,:) = emp_tl (:,:)
499          zqns_tlout(:,:) = qns_tl(:,:)
500         
501         !-----------------------------------------------------------------
502         ! Initialize the adjoint variables: dy^* = W dy
503         !-----------------------------------------------------------------
504
505          DO jj = nldj, nlej
506             DO ji = nldi, nlei
507                zemp_adin( ji,jj) = zemp_tlout( ji,jj) &
508                     &               * e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,1) &
509                     &               * tmask(ji,jj,1)
510                zemps_adin(ji,jj) = zemps_tlout(ji,jj) &
511                     &               * e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,1) &
512                     &               * tmask(ji,jj,1)
513                zqns_adin(ji,jj) = zqns_tlout(ji,jj) &
514                     &               * e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,1) &
515                     &               * tmask(ji,jj,1)
516             END DO
517          END DO
518
519         !-----------------------------------------------------------------
520         ! Compute the scalar product: ( L dx )^T W dy
521         !-----------------------------------------------------------------
522
523          zsp1 = DOT_PRODUCT( zemp_tlout,  zemp_adin  )   &
524               & + DOT_PRODUCT( zemps_tlout, zemps_adin ) &
525               & + DOT_PRODUCT( zqns_tlout, zqns_adin )   
526
527         !-----------------------------------------------------------------
528         ! Call the adjoint routine: dx^* = L^T dy^*
529         !-----------------------------------------------------------------
530
531         emp_ad (:,:) = zemp_adin (:,:)
532         emps_ad(:,:) = zemps_adin(:,:)
533         qns_ad( :,:) = zqns_adin( :,:)
534
535         CALL sbc_gyre_adj ( istp )
536
537         ztb_adout(:,:,:) = tb_ad(:,:,:)
538         zemp_adout (:,:) = emp_ad (:,:)
539
540         zsp2 = DOT_PRODUCT( zemp_tlin,  zemp_adout  ) &
541            & + DOT_PRODUCT( ztb_tlin,  ztb_adout  ) 
542
543         ! 14 char:'12345678901234'
544         IF ( jstp == nit000 ) THEN
545             WRITE (cl_name,"(A14)") 'sbc_gyre_adj 1'
546         ELSEIF ( jstp == nit000 + 1 ) THEN
547             WRITE (cl_name,"(A14)") 'sbc_gyre_adj 2'
548         END IF
549!         WRITE (cl_name,"(A11,2x,i1)") 'sbc_fwb_adj',jn_fwb
550         CALL prntst_adj( cl_name, kumadt, zsp1, zsp2 )
551
552      END DO
553
554      DEALLOCATE(       &
555         & zemp_tlin,   &
556         & ztb_tlin,    &
557         & zemp_tlout,  &
558         & zemps_tlout, &
559         & zqns_tlout,  &
560         & zemp_adin,   &
561         & zemps_adin,  &
562         & zqns_adin,   &
563         & zemp_adout,  &
564         & ztb_adout,   &
565         & z3r,         &
566         & zr           &
567         & )
568
569   END SUBROUTINE sbc_gyre_adj_tst
570#endif
571   !!======================================================================
572END MODULE sbcana_tam
Note: See TracBrowser for help on using the repository browser.