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

source: branches/2012/dev_r3604_LEGI8_TAM/NEMOGCM/NEMO/OPATAM_SRC/TRA/trazdf_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: 8.7 KB
Line 
1MODULE trazdf_tam
2#ifdef key_tam
3   !!==============================================================================
4   !!                 ***  MODULE  trazdf_zdf  ***
5   !! Ocean active tracers:  vertical component of the tracer mixing trend
6   !!                 Tangent and Adjoint Module
7   !!==============================================================================
8   !! History of the direct module:
9   !!            9.0  !  05-11  (G. Madec)  Original code
10   !! History of the TAM module:
11   !!            9.0  !  08-06  (A. Vidard) Skeleton
12   !!            9.0  !  09-01  (A. Vidard) TAM of the 05-11 version
13   !!----------------------------------------------------------------------
14
15   !!----------------------------------------------------------------------
16   !!   tra_zdf_tan  : Update the tracer trend with the vertical diffusion (tan)
17   !!   tra_zdf_adj  : Update the tracer trend with the vertical diffusion (adj)
18   !!       zdf_ctl  : ???
19   !!----------------------------------------------------------------------
20   USE par_kind
21   USE par_oce
22   USE oce_tam
23   USE dom_oce
24   USE ldftra_oce
25   USE zdf_oce
26   USE trazdf_exp_tam
27   USE trazdf_imp_tam
28   USE in_out_manager
29   USE prtctl
30   USE lib_mpp
31   USE wrk_nemo
32   USE timing
33   USE phycst
34
35   IMPLICIT NONE
36   PRIVATE
37
38   PUBLIC  &
39      & tra_zdf_tan, &
40      & tra_zdf_adj         ! routines called by step_tam.F90
41   PUBLIC  tra_zdf_adj_tst  ! routine called by tst.F90
42   PUBLIC  tra_zdf_init_tam
43   INTEGER ::   nzdf = 0               ! type vertical diffusion algorithm used
44      !                                ! defined from ln_zdf...  namlist logicals)
45
46   !! * Substitutions
47#  include "domzgr_substitute.h90"
48#  include "zdfddm_substitute.h90"
49#  include "vectopt_loop_substitute.h90"
50
51CONTAINS
52
53   SUBROUTINE tra_zdf_tan( kt )
54      !!----------------------------------------------------------------------
55      !!                  ***  ROUTINE tra_zdf_tan  ***
56      !!
57      !! ** Purpose of the direct routine:
58      !!            compute the vertical ocean tracer physics.
59      !!---------------------------------------------------------------------
60      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
61
62      !!---------------------------------------------------------------------
63      !
64      IF( nn_timing == 1 )  CALL timing_start('tra_zdf_tan')
65      !
66      !                                             ! set time step
67      IF( neuler == 0 .AND. kt == nit000 ) THEN     ! at nit000
68         r2dtra =  rdttra(:)                          ! = rdtra (restarting with Euler time stepping)
69      ELSEIF( kt <= nit000 + 1) THEN                ! at nit000 or nit000+1
70         r2dtra = 2. * rdttra(:)                      ! = 2 rdttra (leapfrog)
71      ENDIF
72
73      SELECT CASE ( nzdf )                       ! compute lateral mixing trend and add it to the general trend
74      CASE ( -1 )                                       ! esopa: test all possibility with control print
75         CALL tra_zdf_exp_tan    ( kt, nit000, 'TRA', r2dtra, nn_zdfexp, tsb_tl, tsa_tl, jpts )
76         CALL tra_zdf_imp_tan    ( kt, nit000, 'TRA', r2dtra,            tsb_tl, tsa_tl, jpts  )
77
78      CASE ( 0 )                                       ! explicit scheme
79         CALL tra_zdf_exp_tan    ( kt, nit000, 'TRA', r2dtra, nn_zdfexp, tsb_tl, tsa_tl, jpts  )
80
81      CASE ( 1 )                                       ! implicit scheme
82         CALL tra_zdf_imp_tan    ( kt, nit000, 'TRA', r2dtra,            tsb_tl, tsa_tl, jpts  )
83
84      END SELECT
85      !
86      IF( nn_timing == 1 )  CALL timing_stop('tra_zdf_tan')
87      !
88   END SUBROUTINE tra_zdf_tan
89   SUBROUTINE tra_zdf_adj( kt )
90      !!----------------------------------------------------------------------
91      !!                  ***  ROUTINE tra_zdf_adj  ***
92      !!
93      !! ** Purpose of the direct routine:
94      !!            compute the vertical ocean tracer physics.
95      !!---------------------------------------------------------------------
96      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
97
98      !!---------------------------------------------------------------------
99      !
100      IF( nn_timing == 1 )  CALL timing_start('tra_zdf_adj')
101      !
102      !                                          ! set time step
103      IF( neuler == 0 .AND. kt == nit000 ) THEN     ! at nit000
104         r2dtra =  rdttra(:)                          ! = rdtra (restarting with Euler time stepping)
105      ELSEIF( kt <= nit000 + 1) THEN                ! at nit000 or nit000+1
106         r2dtra = 2. * rdttra(:)                      ! = 2 rdttra (leapfrog)
107      ENDIF
108
109      SELECT CASE ( nzdf )                       ! compute lateral mixing trend and add it to the general trend
110      CASE ( -1 )                                       ! esopa: test all possibility with control print
111         CALL tra_zdf_exp_adj    ( kt, nit000, 'TRA', r2dtra, nn_zdfexp, tsb_ad, tsa_ad, jpts )
112         CALL tra_zdf_imp_adj    ( kt, nit000, 'TRA', r2dtra,            tsb_ad, tsa_ad, jpts )
113
114      CASE ( 0 )                                       ! explicit scheme
115         CALL tra_zdf_exp_adj    ( kt, nit000, 'TRA', r2dtra, nn_zdfexp, tsb_ad, tsa_ad, jpts )
116
117      CASE ( 1 )                                       ! implicit scheme
118         CALL tra_zdf_imp_adj    ( kt, nit000, 'TRA', r2dtra,            tsb_ad, tsa_ad, jpts )
119
120      END SELECT
121      !
122      IF( nn_timing == 1 )  CALL timing_stop('tra_zdf_adj')
123      !
124   END SUBROUTINE tra_zdf_adj
125   SUBROUTINE tra_zdf_adj_tst( kumadt )
126      !! ** Purpose : Test the adjoint routines.
127      !!
128      !! ** Method  : Verify the scalar product
129      !!
130      !!                 ( L dx )^T W dy  =  dx^T L^T W dy
131      !!
132      !!              where  L   = tangent routine
133      !!                     L^T = adjoint routine
134      !!                     W   = diagonal matrix of scale factors
135      !!                     dx  = input perturbation (random field)
136      !!                     dy  = L dx
137      !!
138      !!
139      !!-----------------------------------------------------------------------
140      !! * Modules used
141
142      !! * Arguments
143      INTEGER, INTENT(IN) :: &
144         & kumadt             ! Output unit
145
146      !! * Local declarations
147      ! init
148      CALL tra_zdf_init_tam
149      ! Test the explicit formulation
150      CALL tra_zdf_exp_adj_tst    ( kumadt )
151      ! Test the implicit formulation
152      CALL tra_zdf_imp_adj_tst    ( kumadt )
153   END SUBROUTINE tra_zdf_adj_tst
154   !!==============================================================================
155   SUBROUTINE tra_zdf_init_tam
156      !!----------------------------------------------------------------------
157      !!                 ***  ROUTINE zdf_ctl_tam  ***
158      !!
159      !! ** Purpose :   Choose the vertical mixing scheme
160      !!
161      !! ** Method  :   Set nzdf from ln_zdfexp
162      !!      nzdf = 0   explicit (time-splitting) scheme (ln_zdfexp=T)
163      !!           = 1   implicit (euler backward) scheme (ln_zdfexp=F)
164      !!      NB: rotation of lateral mixing operator or TKE or KPP scheme,
165      !!      the implicit scheme is required.
166      !!----------------------------------------------------------------------
167      USE zdftke
168      USE zdfkpp
169      USE zdfgls
170      !!----------------------------------------------------------------------
171
172      !  Define the vertical tracer physics scheme
173      ! ==========================================
174
175      ! Choice from ln_zdfexp already read in namelist in zdfini module
176      IF( ln_zdfexp ) THEN               ! use explicit scheme
177         nzdf = 0
178      ELSE                               ! use implicit scheme
179         nzdf = 1
180      ENDIF
181
182      ! Force implicit schemes
183      IF( lk_zdfgls .OR. lk_zdftke .OR. lk_zdfkpp       )   nzdf = 1      ! TKE or KPP physics
184      IF( ln_traldf_iso                                 )   nzdf = 1      ! iso-neutral lateral physics
185      IF( ln_traldf_hor .AND. ln_sco                    )   nzdf = 1      ! horizontal lateral physics in s-coordinate
186
187      IF( ln_zdfexp .AND. nzdf == 1 )   THEN
188         CALL ctl_stop( 'tra_zdf_tam : If using the rotation of lateral mixing operator or TKE ', &
189            &           '            or KPP scheme, the implicit scheme is required, set ln_zdfexp = .false.' )
190      ENDIF
191
192      ! Test: esopa
193      IF( lk_esopa )    nzdf = -1                      ! All schemes used
194
195      IF(lwp) THEN
196         WRITE(numout,*)
197         WRITE(numout,*) 'tra_zdf_init_tam : vertical tracer physics scheme'
198         WRITE(numout,*) '~~~~~~~~~~~~~~~'
199         IF( nzdf == -1 )   WRITE(numout,*) '              ESOPA test All scheme used'
200         IF( nzdf ==  0 )   WRITE(numout,*) '              Explicit time-splitting scheme'
201         IF( nzdf ==  1 )   WRITE(numout,*) '              Implicit (euler backward) scheme'
202      ENDIF
203   END SUBROUTINE tra_zdf_init_tam
204#endif
205END MODULE trazdf_tam
Note: See TracBrowser for help on using the repository browser.