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

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/TRD/trdvor.F90 @ 2287

Last change on this file since 2287 was 2287, checked in by smasson, 14 years ago

update licence of all NEMO files...

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