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 NEMO/trunk/src/OCE/TRD – NEMO

source: NEMO/trunk/src/OCE/TRD/trdvor.F90

Last change on this file was 15033, checked in by smasson, 3 years ago

trunk: suppress jpim1 et jpjm1, #2699

  • Property svn:keywords set to Id
File size: 25.2 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          ! ocean active tracers: lateral physics
23   USE dianam          ! build the name of file (routine)
24   USE zdfmxl          ! mixed layer depth
25   !
26   USE in_out_manager  ! I/O manager
27   USE ioipsl          ! NetCDF library
28   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
29   USE lib_mpp         ! MPP library
30
31   IMPLICIT NONE
32   PRIVATE
33
34   INTERFACE trd_vor_zint
35      MODULE PROCEDURE trd_vor_zint_2d, trd_vor_zint_3d
36   END INTERFACE
37
38   PUBLIC   trd_vor        ! routine called by trddyn.F90
39   PUBLIC   trd_vor_init   ! routine called by opa.F90
40   PUBLIC   trd_vor_alloc  ! routine called by nemogcm.F90
41
42   INTEGER ::   nh_t, nmoydpvor, nidvor, nhoridvor, ndimvor1, icount   ! needs for IOIPSL output
43   INTEGER, SAVE, ALLOCATABLE, DIMENSION(:) ::   ndexvor1   ! needed 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_avr      ! average
47   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   vor_avrb     ! before vorticity (kt-1)
48   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   vor_avrbb    ! vorticity at begining of the nn_write-1 timestep averaging period
49   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   vor_avrbn    ! after vorticity at time step after the
50   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   rotot        ! begining of the NN_WRITE-1 timesteps
51   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   vor_avrtot   !
52   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   vor_avrres   !
53   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   vortrd       ! curl of trends
54         
55   CHARACTER(len=12) ::   cvort
56
57   !! * Substitutions
58#  include "do_loop_substitute.h90"
59#  include "domzgr_substitute.h90"
60   !!----------------------------------------------------------------------
61   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
62   !! $Id$
63   !! Software governed by the CeCILL license (see ./LICENSE)
64   !!----------------------------------------------------------------------
65CONTAINS
66
67   INTEGER FUNCTION trd_vor_alloc()
68      !!----------------------------------------------------------------------------
69      !!                  ***  ROUTINE trd_vor_alloc  ***
70      !!----------------------------------------------------------------------------
71      ALLOCATE( vor_avr   (jpi,jpj) , vor_avrb(jpi,jpj) , vor_avrbb (jpi,jpj) ,   &
72         &      vor_avrbn (jpi,jpj) , rotot   (jpi,jpj) , vor_avrtot(jpi,jpj) ,   &
73         &      vor_avrres(jpi,jpj) , vortrd  (jpi,jpj,jpltot_vor) ,              &
74         &      ndexvor1  (jpi*jpj)                                ,   STAT= trd_vor_alloc )
75         !
76      CALL mpp_sum ( 'trdvor', trd_vor_alloc )
77      IF( trd_vor_alloc /= 0 )   CALL ctl_stop( 'STOP', 'trd_vor_alloc: failed to allocate arrays' )
78   END FUNCTION trd_vor_alloc
79
80
81   SUBROUTINE trd_vor( putrd, pvtrd, ktrd, kt, Kmm )
82      !!----------------------------------------------------------------------
83      !!                  ***  ROUTINE trd_vor  ***
84      !!
85      !! ** Purpose :  computation of cumulated trends over analysis period
86      !!               and make outputs (NetCDF format)
87      !!----------------------------------------------------------------------
88      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   putrd, pvtrd   ! U and V trends
89      INTEGER                   , INTENT(in   ) ::   ktrd           ! trend index
90      INTEGER                   , INTENT(in   ) ::   kt             ! time step
91      INTEGER                   , INTENT(in   ) ::   Kmm            ! time level index
92      !
93      INTEGER ::   ji, jj   ! dummy loop indices
94      REAL(wp), DIMENSION(jpi,jpj) ::   ztswu, ztswv    ! 2D workspace
95      !!----------------------------------------------------------------------
96
97      CALL lbc_lnk( 'trdvor', putrd, 'U', -1.0_wp , pvtrd, 'V', -1.0_wp )      ! lateral boundary condition
98
99      SELECT CASE( ktrd ) 
100      CASE( jpdyn_hpg )   ;   CALL trd_vor_zint( putrd, pvtrd, jpvor_prg, Kmm )   ! Hydrostatique Pressure Gradient
101      CASE( jpdyn_keg )   ;   CALL trd_vor_zint( putrd, pvtrd, jpvor_keg, Kmm )   ! KE Gradient
102      CASE( jpdyn_rvo )   ;   CALL trd_vor_zint( putrd, pvtrd, jpvor_rvo, Kmm )   ! Relative Vorticity
103      CASE( jpdyn_pvo )   ;   CALL trd_vor_zint( putrd, pvtrd, jpvor_pvo, Kmm )   ! Planetary Vorticity Term
104      CASE( jpdyn_ldf )   ;   CALL trd_vor_zint( putrd, pvtrd, jpvor_ldf, Kmm )   ! Horizontal Diffusion
105      CASE( jpdyn_zad )   ;   CALL trd_vor_zint( putrd, pvtrd, jpvor_zad, Kmm )   ! Vertical Advection
106      CASE( jpdyn_spg )   ;   CALL trd_vor_zint( putrd, pvtrd, jpvor_spg, Kmm )   ! Surface Pressure Grad.
107      CASE( jpdyn_zdf )                                                           ! Vertical Diffusion
108         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )                                                               ! wind stress trends
109            ztswu(ji,jj) = 0.5 * ( utau_b(ji,jj) + utau(ji,jj) ) / ( e3u(ji,jj,1,Kmm) * rho0 )
110            ztswv(ji,jj) = 0.5 * ( vtau_b(ji,jj) + vtau(ji,jj) ) / ( e3v(ji,jj,1,Kmm) * rho0 )
111         END_2D
112         CALL trd_vor_zint( putrd, pvtrd, jpvor_zdf, Kmm )                             ! zdf trend including surf./bot. stresses
113         CALL trd_vor_zint( ztswu, ztswv, jpvor_swf, Kmm )                             ! surface wind stress
114      CASE( jpdyn_bfr )
115         CALL trd_vor_zint( putrd, pvtrd, jpvor_bfr, Kmm )                             ! Bottom stress
116         !
117      CASE( jpdyn_atf )       ! last trends: perform the output of 2D vorticity trends
118         CALL trd_vor_iom( kt, Kmm )
119      END SELECT
120      !
121   END SUBROUTINE trd_vor
122
123
124   SUBROUTINE trd_vor_zint_2d( putrdvor, pvtrdvor, ktrd, Kmm )
125      !!----------------------------------------------------------------------------
126      !!                  ***  ROUTINE trd_vor_zint  ***
127      !!
128      !! ** Purpose :   computation of vertically integrated vorticity budgets
129      !!              from ocean surface down to control surface (NetCDF output)
130      !!
131      !! ** Method/usage :   integration done over nn_write-1 time steps
132      !!
133      !! ** Action :   trends :
134      !!                  vortrd (,, 1) = Pressure Gradient Trend
135      !!                  vortrd (,, 2) = KE Gradient Trend
136      !!                  vortrd (,, 3) = Relative Vorticity Trend
137      !!                  vortrd (,, 4) = Coriolis Term Trend
138      !!                  vortrd (,, 5) = Horizontal Diffusion Trend
139      !!                  vortrd (,, 6) = Vertical Advection Trend
140      !!                  vortrd (,, 7) = Vertical Diffusion Trend
141      !!                  vortrd (,, 8) = Surface Pressure Grad. Trend
142      !!                  vortrd (,, 9) = Beta V
143      !!                  vortrd (,,10) = forcing term
144      !!      vortrd (,,11) = bottom friction term
145      !!                  rotot(,) : total cumulative trends over nn_write-1 time steps
146      !!                  vor_avrtot(,) : first membre of vrticity equation
147      !!                  vor_avrres(,) : residual = dh/dt entrainment
148      !!
149      !!      trends output in netCDF format using ioipsl
150      !!----------------------------------------------------------------------
151      INTEGER                     , INTENT(in) ::   ktrd       ! ocean trend index
152      INTEGER                     , INTENT(in) ::   Kmm        ! time level index
153      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   putrdvor   ! u vorticity trend
154      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   pvtrdvor   ! v vorticity trend
155      !
156      INTEGER ::   ji, jj       ! dummy loop indices
157      INTEGER ::   ikbu, ikbv   ! local integers
158      REAL(wp), DIMENSION(jpi,jpj) :: zudpvor, zvdpvor  ! total cmulative trends
159      !!----------------------------------------------------------------------
160
161      !  =====================================
162      !  I vertical integration of 2D trends
163      !  =====================================
164
165      SELECT CASE( ktrd ) 
166      !
167      CASE( jpvor_bfr )        ! bottom friction
168         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )
169            ikbu = mbkv(ji,jj)
170            ikbv = mbkv(ji,jj)           
171            zudpvor(ji,jj) = putrdvor(ji,jj) * e3u(ji,jj,ikbu,Kmm) * e1u(ji,jj) * umask(ji,jj,ikbu)
172            zvdpvor(ji,jj) = pvtrdvor(ji,jj) * e3v(ji,jj,ikbv,Kmm) * e2v(ji,jj) * vmask(ji,jj,ikbv)
173         END_2D
174         !
175      CASE( jpvor_swf )        ! wind stress
176         zudpvor(:,:) = putrdvor(:,:) * e3u(:,:,1,Kmm) * e1u(:,:) * umask(:,:,1)
177         zvdpvor(:,:) = pvtrdvor(:,:) * e3v(:,:,1,Kmm) * e2v(:,:) * vmask(:,:,1)
178         !
179      END SELECT
180
181      ! Average except for Beta.V
182      zudpvor(:,:) = zudpvor(:,:) * r1_hu(:,:,Kmm)
183      zvdpvor(:,:) = zvdpvor(:,:) * r1_hv(:,:,Kmm)
184   
185      ! Curl
186      DO_2D( 0, 0, 0, 0 )
187         vortrd(ji,jj,ktrd) = (    zvdpvor(ji+1,jj) - zvdpvor(ji,jj)       &
188            &                  - ( zudpvor(ji,jj+1) - zudpvor(ji,jj) )   ) &
189            &                  / ( e1f(ji,jj) * e2f(ji,jj) ) * fmask(ji,jj,1)
190      END_2D
191
192      IF( ndebug /= 0 ) THEN
193         IF(lwp) WRITE(numout,*) ' debuging trd_vor_zint: I done'
194         CALL FLUSH(numout)
195      ENDIF
196      !
197   END SUBROUTINE trd_vor_zint_2d
198
199
200   SUBROUTINE trd_vor_zint_3d( putrdvor, pvtrdvor, ktrd , Kmm )
201      !!----------------------------------------------------------------------------
202      !!                  ***  ROUTINE trd_vor_zint  ***
203      !!
204      !! ** Purpose :   computation of vertically integrated vorticity budgets
205      !!              from ocean surface down to control surface (NetCDF output)
206      !!
207      !! ** Method/usage :   integration done over nn_write-1 time steps
208      !!
209      !! ** Action :     trends :
210      !!                  vortrd (,,1) = Pressure Gradient Trend
211      !!                  vortrd (,,2) = KE Gradient Trend
212      !!                  vortrd (,,3) = Relative Vorticity Trend
213      !!                  vortrd (,,4) = Coriolis Term Trend
214      !!                  vortrd (,,5) = Horizontal Diffusion Trend
215      !!                  vortrd (,,6) = Vertical Advection Trend
216      !!                  vortrd (,,7) = Vertical Diffusion Trend
217      !!                  vortrd (,,8) = Surface Pressure Grad. Trend
218      !!                  vortrd (,,9) = Beta V
219      !!                  vortrd (,,10) = forcing term
220      !!      vortrd (,,11) = bottom friction term
221      !!                  rotot(,) : total cumulative trends over nn_write-1 time steps
222      !!                  vor_avrtot(,) : first membre of vrticity equation
223      !!                  vor_avrres(,) : residual = dh/dt entrainment
224      !!
225      !!      trends output in netCDF format using ioipsl
226      !!----------------------------------------------------------------------
227      !
228      INTEGER                         , INTENT(in) ::   ktrd       ! ocean trend index
229      INTEGER                         , INTENT(in) ::   Kmm        ! time level index
230      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in) ::   putrdvor   ! u vorticity trend
231      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in) ::   pvtrdvor   ! v vorticity trend
232      !
233      INTEGER ::   ji, jj, jk   ! dummy loop indices
234      REAL(wp), DIMENSION(jpi,jpj) :: zudpvor, zvdpvor  ! total cmulative trends
235      !!----------------------------------------------------------------------
236
237      !  =====================================
238      !  I vertical integration of 3D trends
239      !  =====================================
240      ! putrdvor and pvtrdvor terms
241      DO jk = 1,jpk
242        zudpvor(:,:) = zudpvor(:,:) + putrdvor(:,:,jk) * e3u(:,:,jk,Kmm) * e1u(:,:) * umask(:,:,jk)
243        zvdpvor(:,:) = zvdpvor(:,:) + pvtrdvor(:,:,jk) * e3v(:,:,jk,Kmm) * e2v(:,:) * vmask(:,:,jk)
244      END DO
245
246      ! Planetary vorticity: 2nd computation (Beta.V term) store the vertical sum
247      ! as Beta.V term need intergration, not average
248      IF( ktrd == jpvor_pvo ) THEN
249         DO_2D( 0, 0, 0, 0 )
250            vortrd(ji,jj,jpvor_bev) = (    zvdpvor(ji+1,jj) - zvdpvor(ji,jj)     &
251               &                       - ( zudpvor(ji,jj+1) - zudpvor(ji,jj) ) ) &
252               &                           / ( e1f(ji,jj) * e2f(ji,jj) ) * r1_hu(ji,jj,Kmm) * fmask(ji,jj,1)
253         END_2D
254      ENDIF
255      !
256      ! Average
257      zudpvor(:,:) = zudpvor(:,:) * r1_hu(:,:,Kmm)
258      zvdpvor(:,:) = zvdpvor(:,:) * r1_hv(:,:,Kmm)
259      !
260      ! Curl
261      DO_2D( 0, 0, 0, 0 )
262         vortrd(ji,jj,ktrd) = (    zvdpvor(ji+1,jj) - zvdpvor(ji,jj)     &
263            &                  - ( zudpvor(ji,jj+1) - zudpvor(ji,jj) ) ) &
264            &                         / ( e1f(ji,jj) * e2f(ji,jj) ) * fmask(ji,jj,1)
265      END_2D
266   
267      IF( ndebug /= 0 ) THEN
268         IF(lwp) WRITE(numout,*) ' debuging trd_vor_zint: I done'
269         CALL FLUSH(numout)
270      ENDIF
271      !
272   END SUBROUTINE trd_vor_zint_3d
273
274
275   SUBROUTINE trd_vor_iom( kt , Kmm )
276      !!----------------------------------------------------------------------
277      !!                  ***  ROUTINE trd_vor  ***
278      !!
279      !! ** Purpose :  computation of cumulated trends over analysis period
280      !!               and make outputs (NetCDF format)
281      !!----------------------------------------------------------------------
282      INTEGER                   , INTENT(in   ) ::   kt             ! time step
283      INTEGER                   , INTENT(in   ) ::   Kmm            ! time level index
284      !
285      INTEGER  ::   ji, jj, jk, jl   ! dummy loop indices
286      INTEGER  ::   it, itmod        ! local integers
287      REAL(wp) ::   zmean            ! local scalars
288      REAL(wp), DIMENSION(jpi,jpj) :: zuu, zvv
289      !!----------------------------------------------------------------------
290
291      !  =================
292      !  I. Initialization
293      !  =================
294     
295     
296      ! I.1 set before values of vertically average u and v
297      ! ---------------------------------------------------
298
299      IF( kt > nit000 )   vor_avrb(:,:) = vor_avr(:,:)
300
301      ! I.2 vertically integrated vorticity
302      !  ----------------------------------
303
304      vor_avr   (:,:) = 0._wp
305      zuu       (:,:) = 0._wp
306      zvv       (:,:) = 0._wp
307      vor_avrtot(:,:) = 0._wp
308      vor_avrres(:,:) = 0._wp
309     
310      ! Vertically averaged velocity
311      DO jk = 1, jpk - 1
312         zuu(:,:) = zuu(:,:) + e1u(:,:) * uu(:,:,jk,Kmm) * e3u(:,:,jk,Kmm)
313         zvv(:,:) = zvv(:,:) + e2v(:,:) * vv(:,:,jk,Kmm) * e3v(:,:,jk,Kmm)
314      END DO
315 
316      zuu(:,:) = zuu(:,:) * r1_hu(:,:,Kmm)
317      zvv(:,:) = zvv(:,:) * r1_hv(:,:,Kmm)
318
319      ! Curl
320      DO_2D( 0, 0, 0, 0 )
321         vor_avr(ji,jj) = (  ( zvv(ji+1,jj) - zvv(ji,jj) )    &
322            &              - ( zuu(ji,jj+1) - zuu(ji,jj) ) )  &
323            &             / ( e1f(ji,jj) * e2f(ji,jj) ) * fmask(ji,jj,1)
324      END_2D
325     
326      !  =================================
327      !   II. Cumulated trends
328      !  =================================
329
330      ! II.1 set `before' mixed layer values for kt = nit000+1
331      ! ------------------------------------------------------
332      IF( kt == nit000+1 ) THEN
333         vor_avrbb(:,:) = vor_avrb(:,:)
334         vor_avrbn(:,:) = vor_avr (:,:)
335      ENDIF
336
337      ! II.2 cumulated trends over analysis period (kt=2 to nn_write)
338      ! ----------------------
339      ! trends cumulated over nn_write-2 time steps
340
341      IF( kt >= nit000+2 ) THEN
342         nmoydpvor = nmoydpvor + 1
343         DO jl = 1, jpltot_vor
344            IF( jl /= 9 ) THEN
345               rotot(:,:) = rotot(:,:) + vortrd(:,:,jl)
346            ENDIF
347         END DO
348      ENDIF
349
350      !  =============================================
351      !   III. Output in netCDF + residual computation
352      !  =============================================
353     
354      ! define time axis
355      it    = kt
356      itmod = kt - nit000 + 1
357
358      IF( MOD( it, nn_trd ) == 0 ) THEN
359
360         ! III.1 compute total trend
361         ! ------------------------
362         zmean = 1._wp / (  REAL( nmoydpvor, wp ) * 2._wp * rn_Dt  )
363         vor_avrtot(:,:) = (  vor_avr(:,:) - vor_avrbn(:,:) + vor_avrb(:,:) - vor_avrbb(:,:) ) * zmean
364
365
366         ! III.2 compute residual
367         ! ---------------------
368         zmean = 1._wp / REAL( nmoydpvor, wp )
369         vor_avrres(:,:) = vor_avrtot(:,:) - rotot(:,:) / zmean
370
371         ! Boundary conditions
372         CALL lbc_lnk( 'trdvor', vor_avrtot, 'F', 1.0_wp , vor_avrres, 'F', 1.0_wp )
373
374
375         ! III.3 time evolution array swap
376         ! ------------------------------
377         vor_avrbb(:,:) = vor_avrb(:,:)
378         vor_avrbn(:,:) = vor_avr (:,:)
379         !
380         nmoydpvor = 0
381         !
382      ENDIF
383
384      ! III.4 write trends to output
385      ! ---------------------------
386
387      IF( kt >=  nit000+1 ) THEN
388
389         IF( lwp .AND. MOD( itmod, nn_trd ) == 0 ) THEN
390            WRITE(numout,*) ''
391            WRITE(numout,*) 'trd_vor : write trends in the NetCDF file at kt = ', kt
392            WRITE(numout,*) '~~~~~~~  '
393         ENDIF
394 
395         CALL histwrite( nidvor,"sovortPh",it,vortrd(:,:,jpvor_prg),ndimvor1,ndexvor1)  ! grad Ph
396         CALL histwrite( nidvor,"sovortEk",it,vortrd(:,:,jpvor_keg),ndimvor1,ndexvor1)  ! Energy
397         CALL histwrite( nidvor,"sovozeta",it,vortrd(:,:,jpvor_rvo),ndimvor1,ndexvor1)  ! rel vorticity
398         CALL histwrite( nidvor,"sovortif",it,vortrd(:,:,jpvor_pvo),ndimvor1,ndexvor1)  ! coriolis
399         CALL histwrite( nidvor,"sovodifl",it,vortrd(:,:,jpvor_ldf),ndimvor1,ndexvor1)  ! lat diff
400         CALL histwrite( nidvor,"sovoadvv",it,vortrd(:,:,jpvor_zad),ndimvor1,ndexvor1)  ! vert adv
401         CALL histwrite( nidvor,"sovodifv",it,vortrd(:,:,jpvor_zdf),ndimvor1,ndexvor1)  ! vert diff
402         CALL histwrite( nidvor,"sovortPs",it,vortrd(:,:,jpvor_spg),ndimvor1,ndexvor1)  ! grad Ps
403         CALL histwrite( nidvor,"sovortbv",it,vortrd(:,:,jpvor_bev),ndimvor1,ndexvor1)  ! beta.V
404         CALL histwrite( nidvor,"sovowind",it,vortrd(:,:,jpvor_swf),ndimvor1,ndexvor1) ! wind stress
405         CALL histwrite( nidvor,"sovobfri",it,vortrd(:,:,jpvor_bfr),ndimvor1,ndexvor1) ! bottom friction
406         CALL histwrite( nidvor,"1st_mbre",it,vor_avrtot    ,ndimvor1,ndexvor1) ! First membre
407         CALL histwrite( nidvor,"sovorgap",it,vor_avrres    ,ndimvor1,ndexvor1) ! gap between 1st and 2 nd mbre
408         !
409         IF( ndebug /= 0 ) THEN
410            WRITE(numout,*) ' debuging trd_vor: III.4 done'
411            CALL FLUSH(numout)
412         ENDIF
413         !
414      ENDIF
415      !
416      IF( MOD( it, nn_trd ) == 0 ) rotot(:,:)=0
417      !
418      IF( kt == nitend )   CALL histclo( nidvor )
419      !
420   END SUBROUTINE trd_vor_iom
421
422
423   SUBROUTINE trd_vor_init
424      !!----------------------------------------------------------------------
425      !!                  ***  ROUTINE trd_vor_init  ***
426      !!
427      !! ** Purpose :   computation of vertically integrated T and S budgets
428      !!      from ocean surface down to control surface (NetCDF output)
429      !!----------------------------------------------------------------------
430      REAL(wp) ::   zjulian, zsto, zout
431      CHARACTER (len=40) ::   clhstnam
432      CHARACTER (len=40) ::   clop
433      !!----------------------------------------------------------------------
434
435      !  ===================
436      !   I. initialization
437      !  ===================
438
439      cvort='averaged-vor'
440
441      ! Open specifier
442      ndebug = 0      ! set it to 1 in case of problem to have more Print
443
444      IF(lwp) THEN
445         WRITE(numout,*) ' '
446         WRITE(numout,*) ' trd_vor_init: vorticity trends'
447         WRITE(numout,*) ' ~~~~~~~~~~~~'
448         WRITE(numout,*) ' '
449         WRITE(numout,*) '               ##########################################################################'
450         WRITE(numout,*) '                CAUTION: The interpretation of the vorticity trends is'
451         WRITE(numout,*) '                not obvious, please contact Anne-Marie TREGUIER at: treguier@ifremer.fr '
452         WRITE(numout,*) '               ##########################################################################'
453         WRITE(numout,*) ' '
454      ENDIF
455
456      IF( trd_vor_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'trd_vor_init : unable to allocate trdvor arrays' )
457
458
459      ! cumulated trends array init
460      nmoydpvor = 0
461      rotot(:,:)=0
462      vor_avrtot(:,:)=0
463      vor_avrres(:,:)=0
464
465      IF( ndebug /= 0 ) THEN
466         WRITE(numout,*) ' debuging trd_vor_init: I. done'
467         CALL FLUSH(numout)
468      ENDIF
469
470      !  =================================
471      !   II. netCDF output initialization
472      !  =================================
473
474      !-----------------------------------------
475      ! II.1 Define frequency of output and means
476      ! -----------------------------------------
477      IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!)
478      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time)
479      ENDIF
480#if defined key_diainstant
481      zsto = nn_write*rn_Dt
482      clop = "inst("//TRIM(clop)//")"
483#else
484      zsto = rn_Dt
485      clop = "ave("//TRIM(clop)//")"
486#endif
487      zout = nn_trd*rn_Dt
488
489      IF(lwp) WRITE(numout,*) '               netCDF initialization'
490
491      ! II.2 Compute julian date from starting date of the run
492      ! ------------------------
493      CALL ymds2ju( nyear, nmonth, nday, rn_Dt, zjulian )
494      zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment
495      IF(lwp) WRITE(numout,*)' ' 
496      IF(lwp) WRITE(numout,*)'               Date 0 used :',nit000,    &
497         &                   ' YEAR ', nyear,' MONTH '      , nmonth,   &
498         &                   ' DAY ' , nday, 'Julian day : ', zjulian
499
500      ! II.3 Define the T grid trend file (nidvor)
501      ! ---------------------------------
502      CALL dia_nam( clhstnam, nn_trd, 'vort' )                  ! filename
503      IF(lwp) WRITE(numout,*) ' Name of NETCDF file ', clhstnam
504      CALL histbeg( clhstnam, jpi, glamf, jpj, gphif,1, jpi,   &  ! Horizontal grid : glamt and gphit
505         &          1, jpj, nit000-1, zjulian, rn_Dt, nh_t, nidvor, domain_id=nidom, snc4chunks=snc4set )
506      CALL wheneq( jpi*jpj, fmask, 1, 1., ndexvor1, ndimvor1 )    ! surface
507
508      ! Declare output fields as netCDF variables
509      CALL histdef( nidvor, "sovortPh", cvort//"grad Ph" , "s-2",        & ! grad Ph
510         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
511      CALL histdef( nidvor, "sovortEk", cvort//"Energy", "s-2",          & ! Energy
512         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
513      CALL histdef( nidvor, "sovozeta", cvort//"rel vorticity", "s-2",   & ! rel vorticity
514         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
515      CALL histdef( nidvor, "sovortif", cvort//"coriolis", "s-2",        & ! coriolis
516         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
517      CALL histdef( nidvor, "sovodifl", cvort//"lat diff ", "s-2",       & ! lat diff
518         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
519      CALL histdef( nidvor, "sovoadvv", cvort//"vert adv", "s-2",        & ! vert adv
520         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
521      CALL histdef( nidvor, "sovodifv", cvort//"vert diff" , "s-2",      & ! vert diff
522         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
523      CALL histdef( nidvor, "sovortPs", cvort//"grad Ps", "s-2",         & ! grad Ps
524         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
525      CALL histdef( nidvor, "sovortbv", cvort//"Beta V", "s-2",          & ! beta.V
526         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
527      CALL histdef( nidvor, "sovowind", cvort//"wind stress", "s-2",     & ! wind stress
528         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
529      CALL histdef( nidvor, "sovobfri", cvort//"bottom friction", "s-2", & ! bottom friction
530         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
531      CALL histdef( nidvor, "1st_mbre", cvort//"1st mbre", "s-2",        & ! First membre
532         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
533      CALL histdef( nidvor, "sovorgap", cvort//"gap", "s-2",             & ! gap between 1st and 2 nd mbre
534         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
535      CALL histend( nidvor, snc4set )
536
537      IF( ndebug /= 0 ) THEN
538         WRITE(numout,*) ' debuging trd_vor_init: II. done'
539         CALL FLUSH(numout)
540      ENDIF
541      !
542   END SUBROUTINE trd_vor_init
543
544   !!======================================================================
545END MODULE trdvor
Note: See TracBrowser for help on using the repository browser.