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.
trdvor.F90 in branches/UKMO/GO6_dyn_vrt_diag/NEMOGCM/NEMO/OPA_SRC/TRD – NEMO

source: branches/UKMO/GO6_dyn_vrt_diag/NEMOGCM/NEMO/OPA_SRC/TRD/trdvor.F90 @ 9672

Last change on this file since 9672 was 9022, checked in by glong, 7 years ago

Removed old dyn_vrt_dia subrouting and associated code. Updated trdvor to use new io and output vertical integrals as well as vertical averages.

File size: 27.3 KB
Line 
1MODULE trdvor
2   !!======================================================================
3   !!                       ***  MODULE  trdvor  ***
4   !! Ocean diagnostics:  momentum trends
5   !!=====================================================================
6   !! History :  1.0  !  2006-01  (L. Brunier, A-M. Treguier) Original code
7   !!            2.0  !  2008-04  (C. Talandier) New trends organization
8   !!            3.5  !  2012-02  (G. Madec) regroup beta.V computation with pvo trend
9   !!----------------------------------------------------------------------
10
11   !!----------------------------------------------------------------------
12   !!   trd_vor      : momentum trends averaged over the depth
13   !!   trd_vor_zint : vorticity vertical integration
14   !!   trd_vor_init : initialization step
15   !!----------------------------------------------------------------------
16   USE oce             ! ocean dynamics and tracers variables
17   USE dom_oce         ! ocean space and time domain variables
18   USE trd_oce         ! trends: ocean variables
19   USE zdf_oce         ! ocean vertical physics
20   USE sbc_oce         ! surface boundary condition: ocean
21   USE phycst          ! Define parameters for the routines
22   USE ldfdyn_oce      ! ocean active tracers: lateral physics
23   USE dianam          ! build the name of file (routine)
24   USE zdfmxl          ! mixed layer depth
25   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
26   USE in_out_manager  ! I/O manager
27   USE ioipsl          ! NetCDF library
28   USE lib_mpp         ! MPP library
29   USE wrk_nemo        ! Memory allocation
30   USE iom             ! I/O manager library
31
32   IMPLICIT NONE
33   PRIVATE
34
35   INTERFACE trd_vor_zint
36      MODULE PROCEDURE trd_vor_zint_2d, trd_vor_zint_3d
37   END INTERFACE
38
39   PUBLIC   trd_vor        ! routine called by trddyn.F90
40   PUBLIC   trd_vor_init   ! routine called by opa.F90
41   PUBLIC   trd_vor_alloc  ! routine called by nemogcm.F90
42
43   INTEGER ::   nmoydpvor  ! needs for IOIPSL output
44   INTEGER ::   ndebug     ! (0/1) set it to 1 in case of problem to have more print
45
46   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:)    ::   vor        ! time average
47   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:)    ::   vor_b      ! before vorticity (kt-1)
48   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:)    ::   vor_bb     ! vorticity at begining of the nwrite-1 timestep averaging period
49   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:)    ::   vor_bn     ! after vorticity at time step after
50   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:)    ::   rotot      ! begining of the NWRITE-1 timesteps
51   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)      ::   intvor_tot !
52   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)      ::   avrvor_tot !
53   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)      ::   intvor_res !
54   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)      ::   avrvor_res !
55   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:)    ::   intvortrd  ! vertically integrated curl of trends
56   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:)    ::   avrvortrd  ! vertically averaged curl of trends
57         
58   CHARACTER(len=12) ::   cvort
59
60   !! * Substitutions
61#  include "domzgr_substitute.h90"
62#  include "ldfdyn_substitute.h90"
63#  include "vectopt_loop_substitute.h90"
64   !!----------------------------------------------------------------------
65   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
66   !! $Id$
67   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
68   !!----------------------------------------------------------------------
69CONTAINS
70
71   INTEGER FUNCTION trd_vor_alloc()
72      !!----------------------------------------------------------------------------
73      !!                  ***  ROUTINE trd_vor_alloc  ***
74      !!----------------------------------------------------------------------------
75      ALLOCATE( vor   (jpi,jpj,jpvor_types) , vor_b  (jpi,jpj,jpvor_types) ,   &
76         &      vor_bb(jpi,jpj,jpvor_types) , vor_bn (jpi,jpj,jpvor_types) ,   &
77         &      rotot (jpi,jpj,jpvor_types) , intvor_tot(jpi,jpj)          ,   &
78         &      avrvor_tot(jpi,jpj)         , intvor_res(jpi,jpj)          ,   &
79         &      avrvor_res(jpi,jpj)         , intvortrd(jpi,jpj,jpltot_vor),   &
80         &      avrvortrd(jpi,jpj,jpltot_vor),              STAT= trd_vor_alloc )
81         !
82      IF( lk_mpp             )   CALL mpp_sum ( trd_vor_alloc )
83      IF( trd_vor_alloc /= 0 )   CALL ctl_warn('trd_vor_alloc: failed to allocate arrays')
84   END FUNCTION trd_vor_alloc
85
86
87   SUBROUTINE trd_vor( putrd, pvtrd, ktrd, kt )
88      !!----------------------------------------------------------------------
89      !!                  ***  ROUTINE trd_vor  ***
90      !!
91      !! ** Purpose :  computation of cumulated trends over analysis period
92      !!               and make outputs (NetCDF or DIMG format)
93      !!----------------------------------------------------------------------
94      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   putrd, pvtrd   ! U and V trends
95      INTEGER                   , INTENT(in   ) ::   ktrd           ! trend index
96      INTEGER                   , INTENT(in   ) ::   kt             ! time step
97      !
98      INTEGER ::   ji, jj   ! dummy loop indices
99      REAL(wp), POINTER, DIMENSION(:,:) ::   ztswu, ztswv    ! 2D workspace
100      !!----------------------------------------------------------------------
101
102      CALL wrk_alloc( jpi, jpj, ztswu, ztswv )
103
104      SELECT CASE( ktrd ) 
105      CASE( jpdyn_hpg )   ;   CALL trd_vor_zint( putrd, pvtrd, jpvor_prg )   ! Hydrostatique Pressure Gradient
106      CASE( jpdyn_keg )   ;   CALL trd_vor_zint( putrd, pvtrd, jpvor_keg )   ! KE Gradient
107      CASE( jpdyn_rvo )   ;   CALL trd_vor_zint( putrd, pvtrd, jpvor_rvo )   ! Relative Vorticity
108      CASE( jpdyn_pvo )   ;   CALL trd_vor_zint( putrd, pvtrd, jpvor_pvo )   ! Planetary Vorticity Term
109      CASE( jpdyn_ldf )   ;   CALL trd_vor_zint( putrd, pvtrd, jpvor_ldf )   ! Horizontal Diffusion
110      CASE( jpdyn_zad )   ;   CALL trd_vor_zint( putrd, pvtrd, jpvor_zad )   ! Vertical Advection
111      CASE( jpdyn_spg )   ;   CALL trd_vor_zint( putrd, pvtrd, jpvor_spg )   ! Surface Pressure Grad.
112      CASE( jpdyn_zdf )                                                      ! Vertical Diffusion
113         ztswu(:,:) = 0.e0   ;   ztswv(:,:) = 0.e0
114         DO jj = 2, jpjm1                                                             ! wind stress trends
115            DO ji = fs_2, fs_jpim1   ! vector opt.
116               ztswu(ji,jj) = 0.5 * ( utau_b(ji,jj) + utau(ji,jj) ) / ( fse3u(ji,jj,1) * rau0 )
117               ztswv(ji,jj) = 0.5 * ( vtau_b(ji,jj) + vtau(ji,jj) ) / ( fse3v(ji,jj,1) * rau0 )
118            END DO
119         END DO
120         !
121         CALL trd_vor_zint( putrd, pvtrd, jpvor_zdf )                             ! zdf trend including surf./bot. stresses
122         CALL trd_vor_zint( ztswu, ztswv, jpvor_swf )                             ! surface wind stress
123      CASE( jpdyn_bfr )
124         CALL trd_vor_zint( putrd, pvtrd, jpvor_bfr )                             ! Bottom stress
125         !
126      CASE( jpdyn_atf )       ! last trends: perform the output of 2D vorticity trends
127         CALL trd_vor_iom( kt )
128      END SELECT
129      CALL wrk_dealloc( jpi, jpj, ztswu, ztswv )
130      !
131   END SUBROUTINE trd_vor
132
133
134   SUBROUTINE trd_vor_zint_2d( putrdvor, pvtrdvor, ktrd )
135      !!----------------------------------------------------------------------------
136      !!                  ***  ROUTINE trd_vor_zint  ***
137      !!
138      !! ** Purpose :   computation of vertically integrated vorticity budgets
139      !!              from ocean surface down to control surface (NetCDF output)
140      !!
141      !! ** Method/usage :   integration done over nwrite-1 time steps
142      !!
143      !! ** Action :   trends :
144      !!                  intvortrd (,, 1) = Vertical integral of Pressure Gradient Trend
145      !!                  intvortrd (,, 2) = Vertical integral of KE Gradient Trend
146      !!                  intvortrd (,, 3) = Vertical integral of Relative Vorticity Trend
147      !!                  intvortrd (,, 4) = Vertical integral of Coriolis Term Trend
148      !!                  intvortrd (,, 5) = Vertical integral of Horizontal Diffusion Trend
149      !!                  intvortrd (,, 6) = Vertical integral of Vertical Advection Trend
150      !!                  intvortrd (,, 7) = Vertical integral of Vertical Diffusion Trend
151      !!                  intvortrd (,, 8) = Vertical integral of Surface Pressure Grad. Trend
152      !!                  intvortrd (,,10) = Vertical integral of forcing term
153      !!      intvortrd (,,11) = Vertical integral of bottom friction term
154      !!                  avrvortrd (,, 1) = Vertical average of Pressure Gradient Trend
155      !!                  avrvortrd (,, 2) = Vertical average of KE Gradient Trend
156      !!                  avrvortrd (,, 3) = Vertical average of Relative Vorticity Trend
157      !!                  avrvortrd (,, 4) = Vertical average of Coriolis Term Trend
158      !!                  avrvortrd (,, 5) = Vertical average of Horizontal Diffusion Trend
159      !!                  avrvortrd (,, 6) = Vertical average of Vertical Advection Trend
160      !!                  avrvortrd (,, 7) = Vertical average of Vertical Diffusion Trend
161      !!                  avrvortrd (,, 8) = Vertical average of Surface Pressure Grad. Trend
162      !!                  avrvortrd (,,10) = Vertical average of forcing term
163      !!      avrvortrd (,,11) = Vertical average of bottom friction term
164      !!                  rotot  (,,1) = total cumulative vertical integral trends over nwrite-1 time steps
165      !!                  rotot  (,,2) = total cumulative vertical average trends over nwrite-1 time steps
166      !!                  intvor_tot(,,) = first membre of vrticity equation for vertical integral
167      !!                  avrvor_tot(,,) = first membre of vrticity equation for vertical average
168      !!                  intvor_res(,,) = residual = dh/dt entrainment for vertical integral
169      !!                  avrvor_res(,,) = residual = dh/dt entrainment for vertical average
170      !!
171      !!      trends output in netCDF format using ioipsl
172      !!----------------------------------------------------------------------
173      INTEGER                     , INTENT(in   ) ::   ktrd       ! ocean trend index
174      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   putrdvor   ! u vorticity trend
175      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   pvtrdvor   ! v vorticity trend
176      !
177      INTEGER ::   ji, jj       ! dummy loop indices
178      INTEGER ::   ikbu, ikbv   ! local integers
179      REAL(wp), POINTER, DIMENSION(:,:) :: zudpvor, zvdpvor  ! total cmulative trends
180      !!----------------------------------------------------------------------
181
182      !
183      CALL wrk_alloc( jpi, jpj, zudpvor, zvdpvor )                                     ! Memory allocation
184      !
185
186      zudpvor(:,:) = 0._wp                 ;   zvdpvor(:,:) = 0._wp                    ! Initialisation
187      CALL lbc_lnk( putrdvor, 'U', -1. )   ;   CALL lbc_lnk( pvtrdvor, 'V', -1. )      ! lateral boundary condition
188     
189
190      !  =====================================
191      !  I vertical integration of 2D trends
192      !  =====================================
193
194      SELECT CASE( ktrd ) 
195      !
196      CASE( jpvor_bfr )        ! bottom friction
197         DO jj = 2, jpjm1
198            DO ji = fs_2, fs_jpim1 
199               ikbu = mbkv(ji,jj)
200               ikbv = mbkv(ji,jj)           
201               zudpvor(ji,jj) = putrdvor(ji,jj) * fse3u(ji,jj,ikbu) * e1u(ji,jj) * umask(ji,jj,ikbu)
202               zvdpvor(ji,jj) = pvtrdvor(ji,jj) * fse3v(ji,jj,ikbv) * e2v(ji,jj) * vmask(ji,jj,ikbv)
203            END DO
204         END DO
205         !
206      CASE( jpvor_swf )        ! wind stress
207         zudpvor(:,:) = putrdvor(:,:) * fse3u(:,:,1) * e1u(:,:) * umask(:,:,1)
208         zvdpvor(:,:) = pvtrdvor(:,:) * fse3v(:,:,1) * e2v(:,:) * vmask(:,:,1)
209         !
210      END SELECT
211
212      ! Curl of the vertical integral
213      DO ji = 1, jpim1
214         DO jj = 1, jpjm1
215            intvortrd(ji,jj,ktrd) = (    zvdpvor(ji+1,jj) - zvdpvor(ji,jj)       &
216                    &                - ( zudpvor(ji,jj+1) - zudpvor(ji,jj) )   ) / ( e1f(ji,jj) * e2f(ji,jj) )
217         END DO
218      END DO
219      intvortrd(:,:,ktrd) = intvortrd(:,:,ktrd) * fmask(:,:,1)      ! Surface mask
220
221      zudpvor(:,:) = zudpvor(:,:) * hur(:,:)
222      zvdpvor(:,:) = zvdpvor(:,:) * hvr(:,:)
223   
224      ! Curl of the vertical average
225      DO ji = 1, jpim1
226         DO jj = 1, jpjm1
227            avrvortrd(ji,jj,ktrd) = (    zvdpvor(ji+1,jj) - zvdpvor(ji,jj)       &
228                 &                - ( zudpvor(ji,jj+1) - zudpvor(ji,jj) )   ) / ( e1f(ji,jj) * e2f(ji,jj) )
229         END DO
230      END DO
231      avrvortrd(:,:,ktrd) = avrvortrd(:,:,ktrd) * fmask(:,:,1)      ! Surface mask
232
233      IF( ndebug /= 0 ) THEN
234         IF(lwp) WRITE(numout,*) ' debuging trd_vor_zint: I done'
235         CALL FLUSH(numout)
236      ENDIF
237      !
238      CALL wrk_dealloc( jpi, jpj, zudpvor, zvdpvor )                                   
239      !
240   END SUBROUTINE trd_vor_zint_2d
241
242
243   SUBROUTINE trd_vor_zint_3d( putrdvor, pvtrdvor, ktrd )
244      !!----------------------------------------------------------------------------
245      !!                  ***  ROUTINE trd_vor_zint  ***
246      !!
247      !! ** Purpose :   computation of vertically integrated vorticity budgets
248      !!              from ocean surface down to control surface (NetCDF output)
249      !!
250      !! ** Method/usage :   integration done over nwrite-1 time steps
251      !!
252      !! ** Action :     trends :
253      !!                  intvortrd (,, 1) = Vertical integral of Pressure Gradient Trend
254      !!                  intvortrd (,, 2) = Vertical integral of KE Gradient Trend
255      !!                  intvortrd (,, 3) = Vertical integral of Relative Vorticity Trend
256      !!                  intvortrd (,, 4) = Vertical integral of Coriolis Term Trend
257      !!                  intvortrd (,, 5) = Vertical integral of Horizontal Diffusion Trend
258      !!                  intvortrd (,, 6) = Vertical integral of Vertical Advection Trend
259      !!                  intvortrd (,, 7) = Vertical integral of Vertical Diffusion Trend
260      !!                  intvortrd (,, 8) = Vertical integral of Surface Pressure Grad. Trend
261      !!                  intvortrd (,,10) = Vertical integral of forcing term
262      !!      intvortrd (,,11) = Vertical integral of bottom friction term
263      !!                  avrvortrd (,, 1) = Vertical average of Pressure Gradient Trend
264      !!                  avrvortrd (,, 2) = Vertical average of KE Gradient Trend
265      !!                  avrvortrd (,, 3) = Vertical average of Relative Vorticity Trend
266      !!                  avrvortrd (,, 4) = Vertical average of Coriolis Term Trend
267      !!                  avrvortrd (,, 5) = Vertical average of Horizontal Diffusion Trend
268      !!                  avrvortrd (,, 6) = Vertical average of Vertical Advection Trend
269      !!                  avrvortrd (,, 7) = Vertical average of Vertical Diffusion Trend
270      !!                  avrvortrd (,, 8) = Vertical average of Surface Pressure Grad. Trend
271      !!                  avrvortrd (,,10) = Vertical average of forcing term
272      !!      avrvortrd (,,11) = Vertical average of bottom friction term
273      !!                  rotot  (,,1) = total cumulative vertical integral trends over nwrite-1 time steps
274      !!                  rotot  (,,2) = total cumulative vertical average trends over nwrite-1 time steps
275      !!                  intvor_tot(,,) = first membre of vrticity equation for vertical integral
276      !!                  avrvor_tot(,,) = first membre of vrticity equation for vertical average
277      !!                  intvor_res(,,) = residual = dh/dt entrainment for vertical integral
278      !!                  avrvor_res(,,) = residual = dh/dt entrainment for vertical average
279      !!
280      !!      trends output in netCDF format using iom
281      !!----------------------------------------------------------------------
282      !
283      INTEGER                         , INTENT(in   ) ::   ktrd       ! ocean trend index
284      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   putrdvor   ! u vorticity trend
285      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pvtrdvor   ! v vorticity trend
286      !
287      INTEGER ::   ji, jj, jk   ! dummy loop indices
288      REAL(wp), POINTER, DIMENSION(:,:) :: zudpvor, zvdpvor  ! total cmulative trends
289      !!----------------------------------------------------------------------
290     
291      CALL wrk_alloc( jpi,jpj, zudpvor, zvdpvor )                                   
292
293      ! Initialization
294      zudpvor(:,:) = 0._wp
295      zvdpvor(:,:) = 0._wp
296      !
297      CALL lbc_lnk( putrdvor, 'U', -1. )         ! lateral boundary condition on input momentum trends
298      CALL lbc_lnk( pvtrdvor, 'V', -1. )
299
300      !  =====================================
301      !  I vertical integration of 3D trends
302      !  =====================================
303      ! putrdvor and pvtrdvor terms
304      DO jk = 1,jpk
305        zudpvor(:,:) = zudpvor(:,:) + putrdvor(:,:,jk) * fse3u(:,:,jk) * e1u(:,:) * umask(:,:,jk)
306        zvdpvor(:,:) = zvdpvor(:,:) + pvtrdvor(:,:,jk) * fse3v(:,:,jk) * e2v(:,:) * vmask(:,:,jk)
307      END DO
308      !
309      ! Curl of the integral
310      DO ji=1,jpim1
311         DO jj=1,jpjm1
312            intvortrd(ji,jj,ktrd) = (    zvdpvor(ji+1,jj) - zvdpvor(ji,jj)     &
313                  &                  - ( zudpvor(ji,jj+1) - zudpvor(ji,jj) ) ) / ( e1f(ji,jj) * e2f(ji,jj) )
314         END DO
315      END DO
316      ! Surface mask
317      intvortrd(:,:,ktrd) = intvortrd(:,:,ktrd) * fmask(:,:,1)
318      !
319      ! Average
320      zudpvor(:,:) = zudpvor(:,:) * hur(:,:)
321      zvdpvor(:,:) = zvdpvor(:,:) * hvr(:,:)
322      !
323      ! Curl of the average
324      DO ji=1,jpim1
325         DO jj=1,jpjm1
326            avrvortrd(ji,jj,ktrd) = (    zvdpvor(ji+1,jj) - zvdpvor(ji,jj)     &
327                 &                  - ( zudpvor(ji,jj+1) - zudpvor(ji,jj) ) ) / ( e1f(ji,jj) * e2f(ji,jj) )
328         END DO
329      END DO
330      ! Surface mask
331      avrvortrd(:,:,ktrd) = avrvortrd(:,:,ktrd) * fmask(:,:,1)
332   
333      IF( ndebug /= 0 ) THEN
334         IF(lwp) WRITE(numout,*) ' debuging trd_vor_zint: I done'
335         CALL FLUSH(numout)
336      ENDIF
337      !
338      CALL wrk_dealloc( jpi,jpj, zudpvor, zvdpvor )                                   
339      !
340   END SUBROUTINE trd_vor_zint_3d
341
342
343   SUBROUTINE trd_vor_iom( kt )
344      !!----------------------------------------------------------------------
345      !!                  ***  ROUTINE trd_vor  ***
346      !!
347      !! ** Purpose :  computation of cumulated trends over analysis period
348      !!               and make outputs (NetCDF or DIMG format)
349      !!----------------------------------------------------------------------
350      INTEGER                   , INTENT(in   ) ::   kt             ! time step
351      !
352      INTEGER  ::   ji, jj, jk, jl   ! dummy loop indices
353      INTEGER  ::   it, itmod        ! local integers
354      REAL(wp) ::   zmean            ! local scalars
355      REAL(wp), POINTER, DIMENSION(:,:) :: zun, zvn
356      !!----------------------------------------------------------------------
357
358      CALL wrk_alloc( jpi, jpj, zun, zvn )                                   
359
360      !  =================
361      !  I. Initialization
362      !  =================
363     
364     
365      ! I.1 set before values of vertically average u and v
366      ! ---------------------------------------------------
367
368      IF( kt > nit000 ) THEN
369         vor_b(:,:,:) = vor(:,:,:)
370      ENDIF
371
372      ! I.2 vertically integrated vorticity
373      !  ----------------------------------
374
375      vor     (:,:,:) = 0._wp
376      zun       (:,:) = 0._wp
377      zvn       (:,:) = 0._wp
378      intvor_tot(:,:) = 0._wp
379      avrvor_tot(:,:) = 0._wp
380      intvor_res(:,:) = 0._wp
381      avrvor_res(:,:) = 0._wp
382     
383      ! Vertically integrated velocity
384      DO jk = 1, jpk - 1
385         zun(:,:) = zun(:,:) + e1u(:,:) * un(:,:,jk) * fse3u(:,:,jk)
386         zvn(:,:) = zvn(:,:) + e2v(:,:) * vn(:,:,jk) * fse3v(:,:,jk)
387      END DO
388 
389      ! Curl of the vertical integral
390      DO ji = 1, jpim1
391         DO jj = 1, jpjm1
392            vor(ji,jj,jpvor_int) = (  ( zvn(ji+1,jj) - zvn(ji,jj) )    &
393               &              - ( zun(ji,jj+1) - zun(ji,jj) ) ) / ( e1f(ji,jj) * e2f(ji,jj) ) * fmask(ji,jj,1)
394         END DO
395      END DO
396
397      ! Vertically averaged velocity
398      zun(:,:) = zun(:,:) * hur(:,:)
399      zvn(:,:) = zvn(:,:) * hvr(:,:)
400
401      ! Curl of the vertical average
402      DO ji = 1, jpim1
403         DO jj = 1, jpjm1
404            vor(ji,jj,jpvor_avr) = (  ( zvn(ji+1,jj) - zvn(ji,jj) )    &
405               &              - ( zun(ji,jj+1) - zun(ji,jj) ) ) / ( e1f(ji,jj) * e2f(ji,jj) ) * fmask(ji,jj,1)
406         END DO
407      END DO
408     
409      !  =================================
410      !   II. Cumulated trends
411      !  =================================
412
413      ! II.1 set `before' mixed layer values for kt = nit000+1
414      ! ------------------------------------------------------
415      IF( kt == nit000+1 ) THEN
416         vor_bb(:,:,:) = vor_b(:,:,:)
417         vor_bn(:,:,:) = vor  (:,:,:)
418      ENDIF
419
420      ! II.2 cumulated trends over analysis period (kt=2 to nwrite)
421      ! ----------------------
422      ! trends cumulated over nwrite-2 time steps
423
424      IF( kt >= nit000+2 ) THEN
425         nmoydpvor = nmoydpvor + 1
426         DO jl = 1, jpltot_vor
427            rotot(:,:,jpvor_int) = rotot(:,:,jpvor_int) + intvortrd(:,:,jl)
428            rotot(:,:,jpvor_avr) = rotot(:,:,jpvor_avr) + avrvortrd(:,:,jl)
429         END DO
430      ENDIF
431
432      !  =============================================
433      !   III. Output in netCDF + residual computation
434      !  =============================================
435
436      ! define time axis
437      it    = kt
438      itmod = kt - nit000 + 1
439
440      IF( MOD( it, nwrite ) == 0 ) THEN
441
442         ! III.1 compute total trend
443         ! ------------------------
444         zmean = 1._wp / (  REAL( nmoydpvor, wp ) * 2._wp * rdt  )
445         intvor_tot(:,:) = (  vor(:,:,jpvor_int) - vor_bn(:,:,jpvor_int)      &
446                    &        + vor_b(:,:,jpvor_int) - vor_bb(:,:,jpvor_int) ) * zmean
447         avrvor_tot(:,:) = (  vor(:,:,jpvor_avr) - vor_bn(:,:,jpvor_avr)      &
448                    &        + vor_b(:,:,jpvor_avr) - vor_bb(:,:,jpvor_avr) ) * zmean
449
450
451         ! III.2 compute residual
452         ! ---------------------
453         zmean = 1._wp / REAL( nmoydpvor, wp )
454         intvor_res(:,:) = intvor_tot(:,:) - rotot(:,:,jpvor_int) * zmean
455         avrvor_res(:,:) = avrvor_tot(:,:) - rotot(:,:,jpvor_avr) * zmean
456
457         ! Boundary conditions
458         CALL lbc_lnk( intvor_tot, 'F', 1. )
459         CALL lbc_lnk( avrvor_tot, 'F', 1. )
460         CALL lbc_lnk( intvor_res, 'F', 1. )
461         CALL lbc_lnk( avrvor_res, 'F', 1. )
462
463
464         ! III.3 time evolution array swap
465         ! ------------------------------
466         vor_bb(:,:,:) = vor_b(:,:,:)
467         vor_bn(:,:,:) = vor  (:,:,:)
468         !
469         nmoydpvor = 0
470         !
471      ENDIF
472
473      ! III.4 write trends to output
474      ! ---------------------------
475
476      IF( kt >=  nit000+1 ) THEN
477
478         IF( lwp .AND. MOD( itmod, nwrite ) == 0 ) THEN
479            WRITE(numout,*) ''
480            WRITE(numout,*) 'trd_vor : write trends in the NetCDF file at kt = ', kt
481            WRITE(numout,*) '~~~~~~~  '
482         ENDIF
483
484         ! Output the values for the vertical integral
485         CALL iom_put( "sovortPh_int", intvortrd (:,:,jpvor_prg) )  ! grad Ph
486         CALL iom_put( "sovortEk_int", intvortrd (:,:,jpvor_keg) )  ! Energy
487         CALL iom_put( "sovozeta_int", intvortrd (:,:,jpvor_rvo) )  ! rel vorticity
488         CALL iom_put( "sovortif_int", intvortrd (:,:,jpvor_pvo) )  ! coriolis
489         CALL iom_put( "sovodifl_int", intvortrd (:,:,jpvor_ldf) )  ! lat diff
490         CALL iom_put( "sovoadvv_int", intvortrd (:,:,jpvor_zad) )  ! vert adv
491         CALL iom_put( "sovodifv_int", intvortrd (:,:,jpvor_zdf) )  ! vert diff
492         CALL iom_put( "sovortPs_int", intvortrd (:,:,jpvor_spg) )  ! grad Ps
493         CALL iom_put( "sovowind_int", intvortrd (:,:,jpvor_swf) )  ! wind stress
494         CALL iom_put( "sovobfri_int", intvortrd (:,:,jpvor_bfr) )  ! bottom friction
495         CALL iom_put( "1st_mbre_int", intvor_tot(:,:)           )  ! First membre
496         CALL iom_put( "sovorgap_int", intvor_res(:,:)           )  ! gap between 1st and 2 nd mbre
497
498         ! Output the values for the vertical average
499         CALL iom_put( "sovortPh_avr", avrvortrd (:,:,jpvor_prg) )  ! grad Ph
500         CALL iom_put( "sovortEk_avr", avrvortrd (:,:,jpvor_keg) )  ! Energy
501         CALL iom_put( "sovozeta_avr", avrvortrd (:,:,jpvor_rvo) )  ! rel vorticity
502         CALL iom_put( "sovortif_avr", avrvortrd (:,:,jpvor_pvo) )  ! coriolis
503         CALL iom_put( "sovodifl_avr", avrvortrd (:,:,jpvor_ldf) )  ! lat diff
504         CALL iom_put( "sovoadvv_avr", avrvortrd (:,:,jpvor_zad) )  ! vert adv
505         CALL iom_put( "sovodifv_avr", avrvortrd (:,:,jpvor_zdf) )  ! vert diff
506         CALL iom_put( "sovortPs_avr", avrvortrd (:,:,jpvor_spg) )  ! grad Ps
507         CALL iom_put( "sovowind_avr", avrvortrd (:,:,jpvor_swf) )  ! wind stress
508         CALL iom_put( "sovobfri_avr", avrvortrd (:,:,jpvor_bfr) )  ! bottom friction
509         CALL iom_put( "1st_mbre_avr", avrvor_tot(:,:)           )  ! First membre
510         CALL iom_put( "sovorgap_avr", avrvor_res(:,:)           )  ! gap between 1st and 2 nd mbre
511
512         IF( ndebug /= 0 ) THEN
513            WRITE(numout,*) ' debuging trd_vor: III.4 done'
514            CALL FLUSH(numout)
515         ENDIF
516         !
517      ENDIF
518      !
519      IF( MOD( it, nwrite ) == 0 ) THEN
520         rotot(:,:,:)=0
521      ENDIF
522      !
523      CALL wrk_dealloc( jpi, jpj, zun, zvn )                                   
524      !
525   END SUBROUTINE trd_vor_iom
526
527
528   SUBROUTINE trd_vor_init
529      !!----------------------------------------------------------------------
530      !!                  ***  ROUTINE trd_vor_init  ***
531      !!
532      !! ** Purpose :   computation of vertically integrated T and S budgets
533      !!      from ocean surface down to control surface (NetCDF output)
534      !!----------------------------------------------------------------------
535      !REAL(wp) ::   zjulian, zsto, zout
536      !CHARACTER (len=40) ::   clhstnam
537      !CHARACTER (len=40) ::   clop
538      !!----------------------------------------------------------------------
539
540      !  ===================
541      !   I. initialization
542      !  ===================
543
544      cvort='averaged-vor'
545
546      ! Open specifier
547      ndebug = 0      ! set it to 1 in case of problem to have more Print
548
549      IF(lwp) THEN
550         WRITE(numout,*) ' '
551         WRITE(numout,*) ' trd_vor_init: vorticity trends'
552         WRITE(numout,*) ' ~~~~~~~~~~~~'
553         WRITE(numout,*) ' '
554         WRITE(numout,*) '               ##########################################################################'
555         WRITE(numout,*) '                CAUTION: The interpretation of the vorticity trends is'
556         WRITE(numout,*) '                not obvious, please contact Anne-Marie TREGUIER at: treguier@ifremer.fr '
557         WRITE(numout,*) '               ##########################################################################'
558         WRITE(numout,*) ' '
559      ENDIF
560
561      IF( trd_vor_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'trd_vor_init : unable to allocate trdvor arrays' )
562
563
564      ! cumulated trends array init
565      nmoydpvor = 0
566      rotot(:,:,:)=0
567      intvor_tot(:,:)=0
568      avrvor_tot(:,:)=0
569      intvor_res(:,:)=0
570      avrvor_res(:,:)=0
571
572      IF( ndebug /= 0 ) THEN
573         WRITE(numout,*) ' debuging trd_vor_init: I. done'
574         CALL FLUSH(numout)
575      ENDIF
576      !
577   END SUBROUTINE trd_vor_init
578
579   !!======================================================================
580END MODULE trdvor
Note: See TracBrowser for help on using the repository browser.