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/TAM_V3_0/NEMOTAM/OPATAM_SRC/SBC – NEMO

source: branches/TAM_V3_0/NEMOTAM/OPATAM_SRC/SBC/sbcana_tam.F90 @ 1885

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

add TAM sources

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