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 @ 1312

Last change on this file since 1312 was 1312, checked in by smasson, 15 years ago

add a namelist logical to mask land points in NetCDF outputs, see ticket:322

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