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.
trdmod.F90 in branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/TRD – NEMO

source: branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/TRD/trdmod.F90 @ 2633

Last change on this file since 2633 was 2633, checked in by trackstand2, 13 years ago

Renamed wrk_use => wrk_in_use and wrk_release => wrk_not_released

  • Property svn:keywords set to Id
File size: 16.9 KB
Line 
1MODULE trdmod
2   !!======================================================================
3   !!                       ***  MODULE  trdmod  ***
4   !! Ocean diagnostics:  ocean tracers and dynamic trends
5   !!=====================================================================
6   !! History :  1.0  !  2004-08  (C. Talandier) Original code
7   !!             -   !  2005-04  (C. Deltel)    Add Asselin trend in the ML budget
8   !!            3.3  ! 2010-10  (C. Ethe, G. Madec) reorganisation of initialisation phase
9   !!----------------------------------------------------------------------
10#if  defined key_trdtra || defined key_trddyn || defined key_trdmld || defined key_trdvor || defined key_esopa
11   !!----------------------------------------------------------------------
12   !!   trd_mod          : Call the trend to be computed
13   !!   trd_mod_init     : Initialization step
14   !!----------------------------------------------------------------------
15   USE oce                     ! ocean dynamics and tracers variables
16   USE dom_oce                 ! ocean space and time domain variables
17   USE zdf_oce                 ! ocean vertical physics variables
18   USE trdmod_oce              ! ocean variables trends
19   USE ldftra_oce              ! ocean active tracers lateral physics
20   USE sbc_oce                 ! surface boundary condition: ocean
21   USE phycst                  ! physical constants
22   USE trdvor                  ! ocean vorticity trends
23   USE trdicp                  ! ocean bassin integral constraints properties
24   USE trdmld                  ! ocean active mixed layer tracers trends
25   USE in_out_manager          ! I/O manager
26
27   IMPLICIT NONE
28   PRIVATE
29
30   REAL(wp) ::   r2dt          ! time-step, = 2 rdttra except at nit000 (=rdttra) if neuler=0
31
32   PUBLIC trd_mod              ! called by all dynXX or traXX modules
33   PUBLIC trd_mod_init         ! called by opa.F90 module
34
35   !! * Substitutions
36#  include "domzgr_substitute.h90"
37#  include "vectopt_loop_substitute.h90"
38   !!----------------------------------------------------------------------
39   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
40   !! $Id$
41   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
42   !!----------------------------------------------------------------------
43
44CONTAINS
45
46   SUBROUTINE trd_mod( ptrdx, ptrdy, ktrd, ctype, kt )
47      !!---------------------------------------------------------------------
48      !!                  ***  ROUTINE trd_mod  ***
49      !!
50      !! ** Purpose : Dispatch all trends computation, e.g. vorticity, mld or
51      !!              integral constraints
52      !!----------------------------------------------------------------------
53      USE wrk_nemo, ONLY: wrk_in_use, wrk_not_released
54      USE wrk_nemo, ONLY: ztswu => wrk_2d_1,  &
55                          ztswv => wrk_2d_2,  &
56                          ztbfu => wrk_2d_3,  &
57                          ztbfv => wrk_2d_4,  &
58                          z2dx  => wrk_2d_5,  &
59                          z2dy  => wrk_2d_6
60      !
61      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptrdx   ! Temperature or U trend
62      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptrdy   ! Salinity    or V trend
63      CHARACTER(len=3)          , INTENT(in   ) ::   ctype   ! momentum or tracers trends type 'DYN'/'TRA'
64      INTEGER                   , INTENT(in   ) ::   kt      ! time step
65      INTEGER                   , INTENT(in   ) ::   ktrd    ! tracer trend index
66      !!
67      INTEGER ::   ji, jj   ! dummy loop indices
68      !!----------------------------------------------------------------------
69
70      IF(wrk_in_use(2, 1,2,3,4,5,6))THEN
71         CALL ctl_warn('trd_mod: Requested workspace arrays already in use.')   ;   RETURN
72      END IF
73
74      z2dx(:,:) = 0._wp   ;   z2dy(:,:) = 0._wp                            ! initialization of workspace arrays
75
76      IF( neuler == 0 .AND. kt == nit000    ) THEN   ;   r2dt =      rdt   ! = rdtra (restart with Euler time stepping)
77      ELSEIF(               kt <= nit000 + 1) THEN   ;   r2dt = 2. * rdt   ! = 2 rdttra (leapfrog)
78      ENDIF
79
80      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
81      ! I. Integral Constraints Properties for momentum and/or tracers trends
82      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
83
84      IF( ( mod(kt,nn_trd) == 0 .OR. kt == nit000 .OR. kt == nitend) )   THEN
85         !
86         IF( lk_trdtra .AND. ctype == 'TRA' )   THEN       ! active tracer trends
87            SELECT CASE ( ktrd )
88            CASE ( jptra_trd_ldf )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_ldf, ctype )   ! lateral diff
89            CASE ( jptra_trd_zdf )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_zdf, ctype )   ! vertical diff (Kz)
90            CASE ( jptra_trd_bbc )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_bbc, ctype )   ! bottom boundary cond
91            CASE ( jptra_trd_bbl )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_bbl, ctype )   ! bottom boundary layer
92            CASE ( jptra_trd_npc )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_npc, ctype )   ! static instability mixing
93            CASE ( jptra_trd_dmp )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_dmp, ctype )   ! damping
94            CASE ( jptra_trd_qsr )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_qsr, ctype )   ! penetrative solar radiat.
95            CASE ( jptra_trd_nsr )   ;   z2dx(:,:) = ptrdx(:,:,1)   
96                                         z2dy(:,:) = ptrdy(:,:,1)
97                                         CALL trd_icp( z2dx , z2dy , jpicpt_nsr, ctype )   ! non solar radiation
98            CASE ( jptra_trd_xad )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_xad, ctype )   ! x- horiz adv
99            CASE ( jptra_trd_yad )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_yad, ctype )   ! y- horiz adv
100            CASE ( jptra_trd_zad )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_zad, ctype )   ! z- vertical adv
101                                         CALL trd_icp( ptrdx, ptrdy, jpicpt_zad, ctype )   
102                                         ! compute the surface flux condition wn(:,:,1)*tn(:,:,1)
103                                         z2dx(:,:) = wn(:,:,1)*tn(:,:,1)/fse3t(:,:,1)
104                                         z2dy(:,:) = wn(:,:,1)*sn(:,:,1)/fse3t(:,:,1)
105                                         CALL trd_icp( z2dx , z2dy , jpicpt_zl1, ctype )   ! 1st z- vertical adv
106            END SELECT
107         END IF
108
109         IF( lk_trddyn .AND. ctype == 'DYN' )   THEN       ! momentum trends
110            !
111            SELECT CASE ( ktrd )
112            CASE ( jpdyn_trd_hpg )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_hpg, ctype )   ! hydrost. pressure grad
113            CASE ( jpdyn_trd_keg )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_keg, ctype )   ! KE gradient
114            CASE ( jpdyn_trd_rvo )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_rvo, ctype )   ! relative vorticity
115            CASE ( jpdyn_trd_pvo )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_pvo, ctype )   ! planetary vorticity
116            CASE ( jpdyn_trd_ldf )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_ldf, ctype )   ! lateral diffusion
117            CASE ( jpdyn_trd_had )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_had, ctype )   ! horizontal advection
118            CASE ( jpdyn_trd_zad )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_zad, ctype )   ! vertical advection
119            CASE ( jpdyn_trd_spg )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_spg, ctype )   ! surface pressure grad.
120            CASE ( jpdyn_trd_dat )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_dat, ctype )   ! damping term
121            CASE ( jpdyn_trd_zdf )                                                         ! vertical diffusion
122               ! subtract surface forcing/bottom friction trends
123               ! from vertical diffusive momentum trends
124               ztswu(:,:) = 0._wp   ;   ztswv(:,:) = 0._wp
125               ztbfu(:,:) = 0._wp   ;   ztbfv(:,:) = 0._wp 
126               DO jj = 2, jpjm1   
127                  DO ji = fs_2, fs_jpim1   ! vector opt.
128                     ! save the surface forcing momentum fluxes
129                     ztswu(ji,jj) = utau(ji,jj) / ( fse3u(ji,jj,1)*rau0 )
130                     ztswv(ji,jj) = vtau(ji,jj) / ( fse3v(ji,jj,1)*rau0 )
131                     ! bottom friction contribution now handled explicitly
132                     ptrdx(ji,jj,1) = ptrdx(ji,jj,1) - ztswu(ji,jj)
133                     ptrdy(ji,jj,1) = ptrdy(ji,jj,1) - ztswv(ji,jj)
134                  END DO
135               END DO
136               !
137               CALL trd_icp( ptrdx, ptrdy, jpicpd_zdf, ctype )   
138               CALL trd_icp( ztswu, ztswv, jpicpd_swf, ctype )                               ! wind stress forcing term
139               ! bottom friction contribution now handled explicitly
140            CASE ( jpdyn_trd_bfr )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpd_bfr, ctype )     ! bottom friction term
141            END SELECT
142            !
143         END IF
144         !
145      END IF
146
147      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
148      ! II. Vorticity trends
149      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
150
151      IF( lk_trdvor .AND. ctype == 'DYN' )   THEN
152         !
153         SELECT CASE ( ktrd ) 
154         CASE ( jpdyn_trd_hpg )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_prg )   ! Hydrostatique Pressure Gradient
155         CASE ( jpdyn_trd_keg )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_keg )   ! KE Gradient
156         CASE ( jpdyn_trd_rvo )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_rvo )   ! Relative Vorticity
157         CASE ( jpdyn_trd_pvo )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_pvo )   ! Planetary Vorticity Term
158         CASE ( jpdyn_trd_ldf )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_ldf )   ! Horizontal Diffusion
159         CASE ( jpdyn_trd_had )   ;   CALL ctl_warn('Vorticity for horizontal advection trend never checked')   
160         CASE ( jpdyn_trd_zad )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_zad )   ! Vertical Advection
161         CASE ( jpdyn_trd_spg )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_spg )   ! Surface Pressure Grad.
162         CASE ( jpdyn_trd_dat )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_bev )   ! Beta V 
163         CASE ( jpdyn_trd_zdf )                                                      ! Vertical Diffusion
164            ! subtract surface forcing/bottom friction trends
165            ! from vertical diffusive momentum trends
166            ztswu(:,:) = 0.e0   ;   ztswv(:,:) = 0.e0
167            ztbfu(:,:) = 0.e0   ;   ztbfv(:,:) = 0.e0 
168            DO jj = 2, jpjm1   
169               DO ji = fs_2, fs_jpim1   ! vector opt.
170                  ! save the surface forcing momentum fluxes
171                  ztswu(ji,jj) = utau(ji,jj) / ( fse3u(ji,jj,1)*rau0 )
172                  ztswv(ji,jj) = vtau(ji,jj) / ( fse3v(ji,jj,1)*rau0 )
173                  !
174                  ptrdx(ji,jj,1     ) = ptrdx(ji,jj,1     ) - ztswu(ji,jj)
175                  ptrdy(ji,jj,1     ) = ptrdy(ji,jj,1     ) - ztswv(ji,jj)
176               END DO
177            END DO
178            !
179            CALL trd_vor_zint( ptrdx, ptrdy, jpvor_zdf )   
180            CALL trd_vor_zint( ztswu, ztswv, jpvor_swf )                               ! Wind stress forcing term
181         CASE ( jpdyn_trd_bfr )
182            CALL trd_vor_zint( ptrdx, ptrdy, jpvor_bfr )                               ! Bottom friction term
183         END SELECT
184         !
185      ENDIF
186
187      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
188      ! III. Mixed layer trends for active tracers
189      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
190
191      IF( lk_trdmld .AND. ctype == 'TRA' )   THEN
192         
193         !-----------------------------------------------------------------------------------------------
194         ! W.A.R.N.I.N.G :
195         ! jptra_trd_ldf : called by traldf.F90
196         !                 at this stage we store:
197         !                  - the lateral geopotential diffusion (here, lateral = horizontal)
198         !                  - and the iso-neutral diffusion if activated
199         ! jptra_trd_zdf : called by trazdf.F90
200         !                 * in case of iso-neutral diffusion we store the vertical diffusion component in the
201         !                   lateral trend including the K_z contrib, which will be removed later (see trd_mld)
202         !-----------------------------------------------------------------------------------------------
203
204         SELECT CASE ( ktrd )
205         CASE ( jptra_trd_xad )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_xad, '3D' )   ! merid. advection
206         CASE ( jptra_trd_yad )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_yad, '3D' )   ! zonal  advection
207         CASE ( jptra_trd_zad )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_zad, '3D' )   ! vertical advection
208         CASE ( jptra_trd_ldf )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_ldf, '3D' )   ! lateral diffusive
209         CASE ( jptra_trd_bbl )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_bbl, '3D' )   ! bottom boundary layer
210         CASE ( jptra_trd_zdf )
211            IF( ln_traldf_iso )   THEN
212               CALL trd_mld_zint( ptrdx, ptrdy, jpmld_ldf, '3D' )   ! vertical diffusion (K_z)
213            ELSE
214               CALL trd_mld_zint( ptrdx, ptrdy, jpmld_zdf, '3D' )   ! vertical diffusion (K_z)
215            ENDIF
216         CASE ( jptra_trd_dmp )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_dmp, '3D' )   ! internal 3D restoring (tradmp)
217         CASE ( jptra_trd_qsr )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_for, '3D' )   ! air-sea : penetrative sol radiat
218         CASE ( jptra_trd_nsr )
219            ptrdx(:,:,2:jpk) = 0.e0   ;   ptrdy(:,:,2:jpk) = 0.e0
220            CALL trd_mld_zint( ptrdx, ptrdy, jpmld_for, '2D' )                             ! air-sea : non penetr sol radiat
221         CASE ( jptra_trd_bbc )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_bbc, '3D' )   ! bottom bound cond (geoth flux)
222         CASE ( jptra_trd_atf )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_atf, '3D' )   ! asselin numerical
223         CASE ( jptra_trd_npc )   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_npc, '3D' )   ! non penetr convect adjustment
224         END SELECT
225
226      ENDIF
227      !
228      IF( wrk_not_released(2, 1,2,3,4,5,6) )   CALL ctl_warn('trd_mod: Failed to release workspace arrays.')
229      !
230   END SUBROUTINE trd_mod
231
232#else
233   !!----------------------------------------------------------------------
234   !!   Default case :                                         Empty module
235   !!----------------------------------------------------------------------
236   USE trdmod_oce      ! ocean variables trends
237   USE trdvor          ! ocean vorticity trends
238   USE trdicp          ! ocean bassin integral constraints properties
239   USE trdmld          ! ocean active mixed layer tracers trends
240   !!----------------------------------------------------------------------
241CONTAINS
242   SUBROUTINE trd_mod(ptrd3dx, ptrd3dy, ktrd , ctype, kt )   ! Empty routine
243      REAL(wp) ::   ptrd3dx(:,:,:), ptrd3dy(:,:,:)
244      INTEGER  ::   ktrd, kt                           
245      CHARACTER(len=3) ::  ctype                 
246      WRITE(*,*) 'trd_3d: You should not have seen this print! error ?', ptrd3dx(1,1,1), ptrd3dy(1,1,1)
247      WRITE(*,*) ' "   ": You should not have seen this print! error ?', ktrd, ctype, kt
248   END SUBROUTINE trd_mod
249#endif
250
251   SUBROUTINE trd_mod_init
252      !!----------------------------------------------------------------------
253      !!                  ***  ROUTINE trd_mod_init  ***
254      !!
255      !! ** Purpose :   Initialization of activated trends
256      !!----------------------------------------------------------------------
257      USE in_out_manager          ! I/O manager
258      !!   
259      NAMELIST/namtrd/ nn_trd, nn_ctls, cn_trdrst_in, cn_trdrst_out, ln_trdmld_restart, rn_ucf, ln_trdmld_instant
260      !!----------------------------------------------------------------------
261
262      IF( l_trdtra .OR. l_trddyn )   THEN
263         REWIND( numnam )
264         READ  ( numnam, namtrd )      ! namelist namtrd : trends diagnostic
265
266         IF(lwp) THEN
267            WRITE(numout,*)
268            WRITE(numout,*) ' trd_mod_init : Momentum/Tracers trends'
269            WRITE(numout,*) ' ~~~~~~~~~~~~~'
270            WRITE(numout,*) '   Namelist namtrd : set trends parameters'
271            WRITE(numout,*) '      frequency of trends diagnostics   nn_trd             = ', nn_trd
272            WRITE(numout,*) '      control surface type              nn_ctls            = ', nn_ctls
273            WRITE(numout,*) '      restart for ML diagnostics        ln_trdmld_restart  = ', ln_trdmld_restart
274            WRITE(numout,*) '      instantaneous or mean ML T/S      ln_trdmld_instant  = ', ln_trdmld_instant
275            WRITE(numout,*) '      unit conversion factor            rn_ucf             = ', rn_ucf
276        ENDIF
277      ENDIF
278      !
279      IF( lk_trddyn .OR. lk_trdtra )    CALL trd_icp_init       ! integral constraints trends
280      IF( lk_trdmld                )    CALL trd_mld_init       ! mixed-layer trends (active  tracers) 
281      IF( lk_trdvor                )    CALL trd_vor_init       ! vorticity trends       
282      !
283   END SUBROUTINE trd_mod_init
284
285   !!======================================================================
286END MODULE trdmod
Note: See TracBrowser for help on using the repository browser.