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

Last change on this file since 12377 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

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