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

source: trunk/NEMO/OPA_SRC/TRD/trdvor.F90 @ 467

Last change on this file since 467 was 462, checked in by opalod, 18 years ago

nemo_v1_update_053:RB: light update of trends part (supppress key_partial_steps)

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 26.6 KB
Line 
1MODULE trdvor
2   !!======================================================================
3   !!                       ***  MODULE  trdvor  ***
4   !! Ocean diagnostics:  momentum trends
5   !!=====================================================================
6   
7#if defined key_trdvor   ||   defined key_esopa
8   !!----------------------------------------------------------------------
9   !!   'key_trdvor'   : momentum trend diagnostics
10   !!----------------------------------------------------------------------
11   !!   trd_vor      : momentum trends averaged over the depth
12   !!   trd_vor_zint : vorticity vertical integration
13   !!   trd_vor_init : initialization step
14   !!----------------------------------------------------------------------
15   !! * Modules used
16   USE oce             ! ocean dynamics and tracers variables
17   USE dom_oce         ! ocean space and time domain variables
18   USE trdmod_oce      ! ocean variables trends
19   USE zdf_oce         ! ocean vertical physics
20   USE in_out_manager  ! I/O manager
21   USE phycst          ! Define parameters for the routines
22   USE ldfdyn_oce      ! ocean active tracers: lateral physics
23   USE daymod          ! calandar
24   USE dianam          ! build the name of file (routine)
25   USE zdfmxl          ! mixed layer depth
26   USE ioipsl          ! NetCDF library
27   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
28
29
30   IMPLICIT NONE
31   PRIVATE
32
33   !! * Interfaces
34   INTERFACE trd_vor_zint
35      MODULE PROCEDURE trd_vor_zint_2d, trd_vor_zint_3d
36   END INTERFACE
37
38   !! * Accessibility
39   PUBLIC trd_vor        ! routine called by step.F90
40   PUBLIC trd_vor_zint   ! routine called by dynamics routines
41   PUBLIC trd_vor_init   ! routine called by opa.F90
42
43   !! * Shared module variables
44   LOGICAL, PUBLIC ::   lk_trdvor = .TRUE.   ! momentum trend flag
45
46   !! * Module variables
47   INTEGER ::                &
48      nh_t, nmoydpvor  ,     &
49      nidvor, nhoridvor,     &
50      ndexvor1(jpi*jpj),     &
51      ndimvor1, icount,      &
52      idebug                    ! (0/1) set it to 1 in case of problem to have more print
53
54   REAL(wp), DIMENSION(jpi,jpj) ::  &
55     vor_avr    ,     &  ! average
56     vor_avrb   ,     &  ! before vorticity (kt-1)
57     vor_avrbb  ,     &  ! vorticity at begining of the nwrite-1 timestep averaging period
58     vor_avrbn  ,     &  ! after vorticity at time step after the
59     rotot      ,     &  ! begining of the NWRITE-1 timesteps
60     vor_avrtot ,     &
61     vor_avrres
62
63   REAL(wp), DIMENSION(jpi,jpj,jplvor)::   &  !: curl of trends
64      vortrd   
65
66   CHARACTER(len=12) ::   cvort
67
68   !! * Substitutions
69#  include "domzgr_substitute.h90"
70#  include "ldfdyn_substitute.h90"
71#  include "vectopt_loop_substitute.h90"
72
73   !!----------------------------------------------------------------------
74   !!   OPA 9.0 , LOCEAN-IPSL (2005)
75   !! $Header$
76   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
77   !!----------------------------------------------------------------------
78 
79CONTAINS
80
81   SUBROUTINE trd_vor_zint_2d( putrdvor, pvtrdvor, ktrd )
82      !!----------------------------------------------------------------------------
83      !!                  ***  ROUTINE trd_vor_zint  ***
84      !!
85      !! ** Purpose :   computation of vertically integrated vorticity budgets
86      !!      from ocean surface down to control surface (NetCDF output)
87      !!
88      !! ** Method/usage :
89      !!      integration done over nwrite-1 time steps
90      !!
91      !!
92      !! ** Action :
93      !!            /comvor/   :
94      !!                         vor_avr          average
95      !!                         vor_avrb         vorticity at kt-1
96      !!                         vor_avrbb        vorticity at begining of the NWRITE-1
97      !!                                          time steps averaging period
98      !!                         vor_avrbn         vorticity at time step after the
99      !!                                          begining of the NWRITE-1 time
100      !!                                          steps averaging period
101      !!
102      !!                 trends :
103      !!
104      !!                  vortrd (,,1) = Pressure Gradient Trend
105      !!                  vortrd (,,2) = KE Gradient Trend
106      !!                  vortrd (,,3) = Relative Vorticity Trend
107      !!                  vortrd (,,4) = Coriolis Term Trend
108      !!                  vortrd (,,5) = Horizontal Diffusion Trend
109      !!                  vortrd (,,6) = Vertical Advection Trend
110      !!                  vortrd (,,7) = Vertical Diffusion Trend
111      !!                  vortrd (,,8) = Surface Pressure Grad. Trend
112      !!                  vortrd (,,9) = Beta V
113      !!                  vortrd (,,10) = forcing term
114      !!      vortrd (,,11) = bottom friction term
115      !!                  rotot(,) : total cumulative trends over nwrite-1 time steps
116      !!                  vor_avrtot(,) : first membre of vrticity equation
117      !!                  vor_avrres(,) : residual = dh/dt entrainment
118      !!
119      !!      trends output in netCDF format using ioipsl
120      !!
121      !! History :
122      !!   9.0  !  04-06  (L. Brunier, A-M. Treguier) Original code
123      !!        !  04-08  (C. Talandier) New trends organization
124      !!----------------------------------------------------------------------
125      !! * Arguments
126      INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index
127
128      REAL(wp), DIMENSION(jpi,jpj), INTENT( inout ) ::   &
129         putrdvor,                         &  ! u vorticity trend
130         pvtrdvor                             ! v vorticity trend
131
132      !! * Local declarations
133      INTEGER ::   ji, jj
134      INTEGER ::   ikbu, ikbum1, ikbv, ikbvm1
135      REAL(wp), DIMENSION(jpi,jpj) ::   &
136         zudpvor,                       &  ! total cmulative trends
137         zvdpvor                           !   "      "        "
138      !!----------------------------------------------------------------------
139
140      ! Initialization
141      zudpvor(:,:) = 0.e0
142      zvdpvor(:,:) = 0.e0
143
144      CALL lbc_lnk( putrdvor,  'U' , -1. )
145      CALL lbc_lnk( pvtrdvor,  'V' , -1. )
146
147      !  =====================================
148      !  I vertical integration of 2D trends
149      !  =====================================
150
151      SELECT CASE (ktrd) 
152
153      CASE (jpvorbfr)        ! bottom friction
154
155         DO jj = 2, jpjm1
156            DO ji = fs_2, fs_jpim1 
157               ikbu   = min( mbathy(ji+1,jj), mbathy(ji,jj) )
158               ikbum1 = max( ikbu-1, 1 )
159               ikbv   = min( mbathy(ji,jj+1), mbathy(ji,jj) )
160               ikbvm1 = max( ikbv-1, 1 )
161           
162               zudpvor(ji,jj) = putrdvor(ji,jj) * fse3u(ji,jj,ikbum1) * e1u(ji,jj) * umask(ji,jj,ikbum1)
163               zvdpvor(ji,jj) = pvtrdvor(ji,jj) * fse3v(ji,jj,ikbvm1) * e2v(ji,jj) * vmask(ji,jj,ikbvm1)
164            END DO
165         END DO
166
167      CASE (jpvorswf)        ! wind stress
168
169         zudpvor(:,:) = putrdvor(:,:) * fse3u(:,:,1) * e1u(:,:) * umask(:,:,1)
170         zvdpvor(:,:) = pvtrdvor(:,:) * fse3v(:,:,1) * e2v(:,:) * vmask(:,:,1)
171
172      END SELECT
173
174      ! Average except for Beta.V
175      zudpvor(:,:) = zudpvor(:,:) * hur(:,:)
176      zvdpvor(:,:) = zvdpvor(:,:) * hvr(:,:)
177   
178      ! Curl
179      DO ji=1,jpim1
180         DO jj=1,jpjm1
181            vortrd(ji,jj,ktrd) = ( zvdpvor(ji+1,jj) - zvdpvor(ji,jj)        &
182                 &                - ( zudpvor(ji,jj+1) - zudpvor(ji,jj) ) ) &
183                 &               / ( e1f(ji,jj) * e2f(ji,jj) )
184         END DO
185      END DO
186
187      ! Surface mask
188      vortrd(:,:,ktrd) = vortrd(:,:,ktrd) * fmask(:,:,1)
189
190      IF( idebug /= 0 ) THEN
191         IF(lwp) WRITE(numout,*) ' debuging trd_vor_zint: I done'
192         CALL FLUSH(numout)
193      ENDIF
194
195   END SUBROUTINE trd_vor_zint_2d
196
197
198
199   SUBROUTINE trd_vor_zint_3d( putrdvor, pvtrdvor, ktrd )
200      !!----------------------------------------------------------------------------
201      !!                  ***  ROUTINE trd_vor_zint  ***
202      !!
203      !! ** Purpose :   computation of vertically integrated vorticity budgets
204      !!      from ocean surface down to control surface (NetCDF output)
205      !!
206      !! ** Method/usage :
207      !!      integration done over nwrite-1 time steps
208      !!
209      !!
210      !! ** Action :
211      !!            /comvor/   :
212      !!                         vor_avr          average
213      !!                         vor_avrb         vorticity at kt-1
214      !!                         vor_avrbb        vorticity at begining of the NWRITE-1
215      !!                                          time steps averaging period
216      !!                         vor_avrbn         vorticity at time step after the
217      !!                                          begining of the NWRITE-1 time
218      !!                                          steps averaging period
219      !!
220      !!                 trends :
221      !!
222      !!                  vortrd (,,1) = Pressure Gradient Trend
223      !!                  vortrd (,,2) = KE Gradient Trend
224      !!                  vortrd (,,3) = Relative Vorticity Trend
225      !!                  vortrd (,,4) = Coriolis Term Trend
226      !!                  vortrd (,,5) = Horizontal Diffusion Trend
227      !!                  vortrd (,,6) = Vertical Advection Trend
228      !!                  vortrd (,,7) = Vertical Diffusion Trend
229      !!                  vortrd (,,8) = Surface Pressure Grad. Trend
230      !!                  vortrd (,,9) = Beta V
231      !!                  vortrd (,,10) = forcing term
232      !!      vortrd (,,11) = bottom friction term
233      !!                  rotot(,) : total cumulative trends over nwrite-1 time steps
234      !!                  vor_avrtot(,) : first membre of vrticity equation
235      !!                  vor_avrres(,) : residual = dh/dt entrainment
236      !!
237      !!      trends output in netCDF format using ioipsl
238      !!
239      !! History :
240      !!   9.0  !  04-06  (L. Brunier, A-M. Treguier) Original code
241      !!        !  04-08  (C. Talandier) New trends organization
242      !!----------------------------------------------------------------------
243      !! * Arguments
244      INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index
245
246      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   &
247         putrdvor,                         &  ! u vorticity trend
248         pvtrdvor                             ! v vorticity trend
249
250      !! * Local declarations
251      INTEGER ::   ji, jj, jk
252
253      REAL(wp), DIMENSION(jpi,jpj) ::   &
254         zubet,                         &  ! u Beta.V case
255         zvbet,                         &  ! v Beta.V case
256         zudpvor,                       &  ! total cmulative trends
257         zvdpvor                           !   "      "        "
258      !!----------------------------------------------------------------------
259     
260      ! Initialization
261      zubet(:,:) = 0.e0
262      zvbet(:,:) = 0.e0
263      zudpvor(:,:) = 0.e0
264      zvdpvor(:,:) = 0.e0
265
266      !  =====================================
267      !  I vertical integration of 3D trends
268      !  =====================================
269
270      CALL lbc_lnk( putrdvor, 'U' , -1. )
271      CALL lbc_lnk( pvtrdvor, 'V' , -1. )
272
273      ! putrdvor and pvtrdvor terms
274      DO jk = 1,jpk
275        zudpvor(:,:) = zudpvor(:,:) + putrdvor(:,:,jk) * fse3u(:,:,jk) * e1u(:,:) * umask(:,:,jk)
276        zvdpvor(:,:) = zvdpvor(:,:) + pvtrdvor(:,:,jk) * fse3v(:,:,jk) * e2v(:,:) * vmask(:,:,jk)
277      END DO
278
279      ! Save Beta.V term to avoid average before Curl
280      ! Beta.V : intergration, no average
281      IF( ktrd == jpvorbev ) THEN
282         zubet(:,:) = zudpvor(:,:)
283         zvbet(:,:) = zvdpvor(:,:)
284      ENDIF
285
286      ! Average except for Beta.V
287      zudpvor(:,:) = zudpvor(:,:) * hur(:,:)
288      zvdpvor(:,:) = zvdpvor(:,:) * hvr(:,:)
289   
290      ! Curl
291      DO ji=1,jpim1
292         DO jj=1,jpjm1
293            vortrd(ji,jj,ktrd) = (  zvdpvor(ji+1,jj) - zvdpvor(ji,jj) -   &
294                 &                ( zudpvor(ji,jj+1) - zudpvor(ji,jj) ) ) &
295                 &               / ( e1f(ji,jj) * e2f(ji,jj) )
296         END DO
297      END DO
298
299      ! Surface mask
300      vortrd(:,:,ktrd) = vortrd(:,:,ktrd) * fmask(:,:,1)
301
302      ! Special treatement for the Beta.V term
303      ! Compute the Curl of the Beta.V term which is not averaged
304      IF( ktrd == jpvorbev ) THEN
305         DO ji=1,jpim1
306            DO jj=1,jpjm1
307               vortrd(ji,jj,jpvorbev) = (  zvbet(ji+1,jj) - zvbet(ji,jj) -   &
308                    &                    ( zubet(ji,jj+1) - zubet(ji,jj) ) ) &
309                    &                   / ( e1f(ji,jj) * e2f(ji,jj) )
310            END DO
311         END DO
312
313         ! Average on the Curl
314         vortrd(:,:,jpvorbev) = vortrd(:,:,jpvorbev) * hur(:,:)
315
316         ! Surface mask
317         vortrd(:,:,jpvorbev) = vortrd(:,:,jpvorbev) * fmask(:,:,1)
318      ENDIF
319   
320      IF( idebug /= 0 ) THEN
321         IF(lwp) WRITE(numout,*) ' debuging trd_vor_zint: I done'
322         CALL FLUSH(numout)
323      ENDIF
324
325   END SUBROUTINE trd_vor_zint_3d
326
327
328
329   SUBROUTINE trd_vor( kt )
330      !!----------------------------------------------------------------------
331      !!                  ***  ROUTINE trd_vor  ***
332      !!
333      !! ** Purpose :  computation of cumulated trends over analysis period
334      !!               and make outputs (NetCDF or DIMG format)
335      !!
336      !! ** Method/usage :
337      !!
338      !! History :
339      !!   9.0  !  04-06  (L. Brunier, A-M. Treguier) Original code
340      !!        !  04-08  (C. Talandier) New trends organization
341      !!----------------------------------------------------------------------
342      !! * Arguments
343      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
344
345      !! * Local declarations
346      INTEGER :: ji, jj, jk, jl, it
347
348      REAL(wp) :: zmean
349
350      REAL(wp) ,DIMENSION(jpi,jpj) ::   &
351         zun, zvn
352      !!----------------------------------------------------------------------
353
354      !  =================
355      !  I. Initialization
356      !  =================
357     
358     
359      ! I.1 set before values of vertically average u and v
360      ! ---------------------------------------------------
361
362      IF( kt > nit000 ) THEN
363         vor_avrb(:,:) = vor_avr(:,:)
364      ENDIF
365
366       IF( idebug /= 0 ) THEN
367          WRITE(numout,*) ' debuging trd_vor: I.1 done '
368          CALL FLUSH(numout)
369      ENDIF
370
371      ! I.2 vertically integrated vorticity
372      !  ----------------------------------
373
374      vor_avr(:,:) = 0.
375      zun(:,:)=0
376      zvn(:,:)=0
377      vor_avrtot(:,:)=0
378      vor_avrres(:,:)=0
379     
380      ! Vertically averaged velocity
381      DO jk = 1, jpk - 1
382         zun(:,:)=zun(:,:) + e1u(:,:)*un(:,:,jk)*fse3u(:,:,jk)
383         zvn(:,:)=zvn(:,:) + e2v(:,:)*vn(:,:,jk)*fse3v(:,:,jk)
384      END DO
385 
386      zun(:,:)=zun(:,:)*hur(:,:)
387      zvn(:,:)=zvn(:,:)*hvr(:,:)
388
389      ! Curl
390      DO ji=1,jpim1
391         DO jj=1,jpjm1
392            vor_avr(ji,jj) = ((zvn(ji+1,jj)-zvn(ji,jj))-   &
393                              (zun(ji,jj+1)-zun(ji,jj)))   &
394                             /( e1f(ji,jj) * e2f(ji,jj) )
395            vor_avr(ji,jj) = vor_avr(ji,jj)*fmask(ji,jj,1)
396         END DO
397      END DO
398     
399      IF(idebug /= 0) THEN
400         WRITE(numout,*) ' debuging trd_vor: I.2 done'
401         CALL FLUSH(numout)
402      ENDIF
403
404      !  =================================
405      !   II. Cumulated trends
406      !  =================================
407
408      ! II.1 set `before' mixed layer values for kt = nit000+1
409      ! ------------------------------------------------------
410      IF( kt == nit000+1 ) THEN
411         vor_avrbb(:,:) = vor_avrb(:,:)
412         vor_avrbn(:,:) = vor_avr (:,:)
413      ENDIF
414
415      IF( idebug /= 0 ) THEN
416         WRITE(numout,*) ' debuging trd_vor: I1.1 done'
417         CALL FLUSH(numout)
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, jplvor
427            IF( jl /= 9 ) THEN
428               rotot(:,:) = rotot(:,:) + vortrd(:,:,jl)
429            ENDIF
430         END DO
431      ENDIF
432
433      IF( idebug /= 0 ) THEN
434         WRITE(numout,*) ' debuging trd_vor: II.2 done'
435         CALL FLUSH(numout)
436      ENDIF
437
438      !  =============================================
439      !   III. Output in netCDF + residual computation
440      !  =============================================
441
442      IF( MOD( kt - nit000+1, ntrd ) == 0 ) THEN
443
444         ! III.1 compute total trend
445         ! ------------------------
446         zmean = float(nmoydpvor)
447
448         vor_avrtot(:,:) = ( vor_avr(:,:) - vor_avrbn(:,:) + vor_avrb(:,:) - &
449                             vor_avrbb(:,:) ) /  (zmean * 2. * rdt)
450
451         IF( idebug /= 0 ) THEN
452             WRITE(numout,*) ' zmean = ',zmean
453             WRITE(numout,*) ' debuging trd_vor: III.1 done'
454             CALL FLUSH(numout)
455         ENDIF
456
457         ! III.2 compute residual
458         ! ---------------------
459         vor_avrres(:,:) = vor_avrtot(:,:) - rotot(:,:) / zmean
460
461         ! Boundary conditions
462         CALL lbc_lnk( vor_avrtot, 'F', 1. )
463         CALL lbc_lnk( vor_avrres, 'F', 1. )
464
465         IF( idebug /= 0 ) THEN
466            WRITE(numout,*) ' debuging trd_vor: III.2 done'
467            CALL FLUSH(numout)
468         ENDIF
469
470         ! III.3 time evolution array swap
471         ! ------------------------------
472         vor_avrbb(:,:) = vor_avrb(:,:)
473         vor_avrbn(:,:) = vor_avr(:,:)
474
475         IF( idebug /= 0 ) THEN
476            WRITE(numout,*) ' debuging trd_vor: III.3 done'
477            CALL FLUSH(numout)
478         ENDIF
479
480         nmoydpvor=0
481
482      ENDIF
483
484      ! III.4 write trends to output
485      ! ---------------------------
486
487      IF( kt >=  nit000+1 ) THEN
488
489         ! define time axis
490         it= kt-nit000+1
491         IF( lwp .AND. MOD( kt, ntrd ) == 0 ) THEN
492            WRITE(numout,*) '     trdvor_ncwrite : write NetCDF fields'
493         ENDIF
494 
495         CALL histwrite( nidvor,"sovortPh",it,vortrd(:,:,1),ndimvor1,ndexvor1)  ! grad Ph
496         CALL histwrite( nidvor,"sovortEk",it,vortrd(:,:,2),ndimvor1,ndexvor1)  ! Energy
497         CALL histwrite( nidvor,"sovozeta",it,vortrd(:,:,3),ndimvor1,ndexvor1)  ! rel vorticity
498         CALL histwrite( nidvor,"sovortif",it,vortrd(:,:,4),ndimvor1,ndexvor1)  ! coriolis
499         CALL histwrite( nidvor,"sovodifl",it,vortrd(:,:,5),ndimvor1,ndexvor1)  ! lat diff
500         CALL histwrite( nidvor,"sovoadvv",it,vortrd(:,:,6),ndimvor1,ndexvor1)  ! vert adv
501         CALL histwrite( nidvor,"sovodifv",it,vortrd(:,:,7),ndimvor1,ndexvor1)  ! vert diff
502         CALL histwrite( nidvor,"sovortPs",it,vortrd(:,:,8),ndimvor1,ndexvor1)  ! grad Ps
503         CALL histwrite( nidvor,"sovortbv",it,vortrd(:,:,9),ndimvor1,ndexvor1)  ! beta.V
504         CALL histwrite( nidvor,"sovowind",it,vortrd(:,:,10),ndimvor1,ndexvor1) ! wind stress
505         CALL histwrite( nidvor,"sovobfri",it,vortrd(:,:,11),ndimvor1,ndexvor1) ! bottom friction
506         CALL histwrite( nidvor,"1st_mbre",it,vor_avrtot    ,ndimvor1,ndexvor1) ! First membre
507         CALL histwrite( nidvor,"sovorgap",it,vor_avrres    ,ndimvor1,ndexvor1) ! gap between 1st and 2 nd mbre
508
509         IF( idebug /= 0 ) THEN
510            WRITE(numout,*) ' debuging trd_vor: III.4 done'
511            CALL FLUSH(numout)
512         ENDIF
513
514      ENDIF
515
516      IF( MOD( kt - nit000+1, ntrd ) == 0 ) rotot(:,:)=0
517
518      IF( kt == nitend )   CALL histclo( nidvor )
519
520   END SUBROUTINE trd_vor
521
522
523
524   SUBROUTINE trd_vor_init
525      !!----------------------------------------------------------------------
526      !!                  ***  ROUTINE trd_vor_init  ***
527      !!
528      !! ** Purpose :   computation of vertically integrated T and S budgets
529      !!      from ocean surface down to control surface (NetCDF output)
530      !!
531      !! ** Method/usage :
532      !!
533      !! History :
534      !!   9.0  !  04-06  (L. Brunier, A-M. Treguier) Original code
535      !!        !  04-08  (C. Talandier) New trends organization
536      !!----------------------------------------------------------------------
537      !! * Local declarations
538      REAL(wp) :: zjulian, zsto, zout
539
540      CHARACTER (len=40) ::   clhstnam
541      CHARACTER (len=40) ::   clop
542
543      NAMELIST/namtrd/ ntrd,nctls
544      !!----------------------------------------------------------------------
545
546      !  ===================
547      !   I. initialization
548      !  ===================
549
550      cvort='averaged-vor'
551
552      ! Open specifier
553      idebug = 0      ! set it to 1 in case of problem to have more Print
554
555      ! namelist namtrd : trend diagnostic
556      REWIND( numnam )
557      READ  ( numnam, namtrd )
558
559      IF(lwp) THEN
560         WRITE(numout,*) ' '
561         WRITE(numout,*) 'trd_vor_init: vorticity trends'
562         WRITE(numout,*) '~~~~~~~~~~~~~'
563         WRITE(numout,*) ' '
564         WRITE(numout,*) '          Namelist namtrd : '
565         WRITE(numout,*) '             time step frequency trend       ntrd  = ',ntrd
566         WRITE(numout,*) ' '
567         WRITE(numout,*) '##########################################################################'
568         WRITE(numout,*) ' CAUTION: The interpretation of the vorticity trends is'
569         WRITE(numout,*) ' not obvious, please contact Anne-Marie TREGUIER at: treguier@ifremer.fr '
570         WRITE(numout,*) '##########################################################################'
571         WRITE(numout,*) ' '
572      ENDIF
573
574      ! cumulated trends array init
575      nmoydpvor = 0
576      rotot(:,:)=0
577      vor_avrtot(:,:)=0
578      vor_avrres(:,:)=0
579
580      IF( idebug /= 0 ) THEN
581         WRITE(numout,*) ' debuging trd_vor_init: I. done'
582         CALL FLUSH(numout)
583      ENDIF
584
585      !  =================================
586      !   II. netCDF output initialization
587      !  =================================
588
589      !-----------------------------------------
590      ! II.1 Define frequency of output and means
591      ! -----------------------------------------
592#if defined key_diainstant
593      zsto = nwrite*rdt
594      clop ="inst(x)"
595#else
596      zsto = rdt
597      clop ="ave(x)"
598#endif
599      zout = ntrd*rdt
600
601      IF(lwp) WRITE (numout,*) ' trdvor_ncinit: netCDF initialization'
602
603      ! II.2 Compute julian date from starting date of the run
604      ! ------------------------
605      CALL ymds2ju( nyear, nmonth, nday, 0.e0, zjulian )
606      IF (lwp) WRITE(numout,*)' ' 
607      IF (lwp) WRITE(numout,*)' Date 0 used :',nit000         &
608           ,' YEAR ', nyear,' MONTH ', nmonth,' DAY ', nday   &
609           ,'Julian day : ', zjulian
610
611      ! II.3 Define the T grid trend file (nidvor)
612      ! ---------------------------------
613      CALL dia_nam( clhstnam, ntrd, 'vort' )                  ! filename
614      IF(lwp) WRITE(numout,*) ' Name of NETCDF file ', clhstnam
615      CALL histbeg( clhstnam, jpi, glamf, jpj, gphif,1, jpi,   &  ! Horizontal grid : glamt and gphit
616         &          1, jpj, 0, zjulian, rdt, nh_t, nidvor, domain_id=nidom )
617      CALL wheneq( jpi*jpj, fmask, 1, 1., ndexvor1, ndimvor1 )    ! surface
618
619      ! Declare output fields as netCDF variables
620      CALL histdef( nidvor, "sovortPh", cvort//"grad Ph" , "s-2",        & ! grad Ph
621         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
622      CALL histdef( nidvor, "sovortEk", cvort//"Energy", "s-2",          & ! Energy
623         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
624      CALL histdef( nidvor, "sovozeta", cvort//"rel vorticity", "s-2",   & ! rel vorticity
625         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
626      CALL histdef( nidvor, "sovortif", cvort//"coriolis", "s-2",        & ! coriolis
627         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
628      CALL histdef( nidvor, "sovodifl", cvort//"lat diff ", "s-2",       & ! lat diff
629         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
630      CALL histdef( nidvor, "sovoadvv", cvort//"vert adv", "s-2",        & ! vert adv
631         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
632      CALL histdef( nidvor, "sovodifv", cvort//"vert diff" , "s-2",      & ! vert diff
633         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
634      CALL histdef( nidvor, "sovortPs", cvort//"grad Ps", "s-2",         & ! grad Ps
635         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
636      CALL histdef( nidvor, "sovortbv", cvort//"Beta V", "s-2",          & ! beta.V
637         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
638      CALL histdef( nidvor, "sovowind", cvort//"wind stress", "s-2",     & ! wind stress
639         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
640      CALL histdef( nidvor, "sovobfri", cvort//"bottom friction", "s-2", & ! bottom friction
641         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
642      CALL histdef( nidvor, "1st_mbre", cvort//"1st mbre", "s-2",        & ! First membre
643         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
644      CALL histdef( nidvor, "sovorgap", cvort//"gap", "s-2",             & ! gap between 1st and 2 nd mbre
645         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout)
646      CALL histend( nidvor )
647
648      IF( idebug /= 0 ) THEN
649         WRITE(numout,*) ' debuging trd_vor_init: II. done'
650         CALL FLUSH(numout)
651      ENDIF
652
653   END SUBROUTINE trd_vor_init
654
655#else
656   !!----------------------------------------------------------------------
657   !!   Default option :                                       Empty module
658   !!----------------------------------------------------------------------
659   LOGICAL, PUBLIC ::   lk_trdvor = .FALSE.   ! momentum trend flag
660
661   !! * Interfaces
662   INTERFACE trd_vor_zint
663      MODULE PROCEDURE trd_vor_zint_2d, trd_vor_zint_3d
664   END INTERFACE
665
666CONTAINS
667   SUBROUTINE trd_vor( kt )        ! Empty routine
668      WRITE(*,*) 'trd_vor: You should not have seen this print! error?', kt
669   END SUBROUTINE trd_vor
670   SUBROUTINE trd_vor_zint_2d( putrdvor, pvtrdvor, ktrd )
671      REAL, DIMENSION(:,:), INTENT( inout ) ::   &
672         putrdvor, pvtrdvor                  ! U and V momentum trends
673      INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index
674      WRITE(*,*) 'trd_vor_zint_2d: You should not have seen this print! error?', putrdvor(1,1)
675      WRITE(*,*) '  "      "     : You should not have seen this print! error?', pvtrdvor(1,1)
676      WRITE(*,*) '  "      "     : You should not have seen this print! error?', ktrd
677   END SUBROUTINE trd_vor_zint_2d
678   SUBROUTINE trd_vor_zint_3d( putrdvor, pvtrdvor, ktrd )
679      REAL, DIMENSION(:,:,:), INTENT( inout ) ::   &
680         putrdvor, pvtrdvor                  ! U and V momentum trends
681      INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index
682      WRITE(*,*) 'trd_vor_zint_3d: You should not have seen this print! error?', putrdvor(1,1,1)
683      WRITE(*,*) '  "      "     : You should not have seen this print! error?', pvtrdvor(1,1,1)
684      WRITE(*,*) '  "      "     : You should not have seen this print! error?', ktrd
685   END SUBROUTINE trd_vor_zint_3d
686   SUBROUTINE trd_vor_init              ! Empty routine
687      WRITE(*,*) 'trd_vor_init: You should not have seen this print! error?'
688   END SUBROUTINE trd_vor_init
689#endif
690   !!======================================================================
691END MODULE trdvor
Note: See TracBrowser for help on using the repository browser.