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.
trdtra.F90 in NEMO/trunk/src/OCE/TRD – NEMO

source: NEMO/trunk/src/OCE/TRD/trdtra.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: 21.9 KB
RevLine 
[2026]1MODULE trdtra
2   !!======================================================================
3   !!                       ***  MODULE  trdtra  ***
[4990]4   !! Ocean diagnostics:  ocean tracers trends pre-processing
[2026]5   !!=====================================================================
[4990]6   !! History :  3.3  !  2010-06  (C. Ethe) creation for the TRA/TRC merge
7   !!            3.5  !  2012-02  (G. Madec) update the comments
[2026]8   !!----------------------------------------------------------------------
[4990]9
[2026]10   !!----------------------------------------------------------------------
[4990]11   !!   trd_tra       : pre-process the tracer trends
12   !!   trd_tra_adv   : transform a div(U.T) trend into a U.grad(T) trend
13   !!   trd_tra_mng   : tracer trend manager: dispatch to the diagnostic modules
14   !!   trd_tra_iom   : output 3D tracer trends using IOM
[2026]15   !!----------------------------------------------------------------------
[4990]16   USE oce            ! ocean dynamics and tracers variables
17   USE dom_oce        ! ocean domain
18   USE sbc_oce        ! surface boundary condition: ocean
19   USE zdf_oce        ! ocean vertical physics
20   USE trd_oce        ! trends: ocean variables
21   USE trdtrc         ! ocean passive mixed layer tracers trends
22   USE trdglo         ! trends: global domain averaged
23   USE trdpen         ! trends: Potential ENergy
24   USE trdmxl         ! ocean active mixed layer tracers trends
[5836]25   USE ldftra         ! ocean active tracers lateral physics
26   USE ldfslp
[4990]27   USE zdfddm         ! vertical physics: double diffusion
28   USE phycst         ! physical constants
[5836]29   !
[4990]30   USE in_out_manager ! I/O manager
31   USE iom            ! I/O manager library
32   USE lib_mpp        ! MPP library
[2026]33
34   IMPLICIT NONE
35   PRIVATE
36
[4990]37   PUBLIC   trd_tra   ! called by all tra_... modules
[2026]38
[4990]39   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   trdtx, trdty, trdt   ! use to store the temperature trends
[7646]40   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   avt_evd  ! store avt_evd to calculate EVD trend
[4990]41
[2026]42   !! * Substitutions
[12377]43#  include "do_loop_substitute.h90"
[2026]44   !!----------------------------------------------------------------------
[9598]45   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[2281]46   !! $Id$
[10068]47   !! Software governed by the CeCILL license (see ./LICENSE)
[2026]48   !!----------------------------------------------------------------------
49CONTAINS
50
[2715]51   INTEGER FUNCTION trd_tra_alloc()
[4990]52      !!---------------------------------------------------------------------
[2715]53      !!                  ***  FUNCTION trd_tra_alloc  ***
[4990]54      !!---------------------------------------------------------------------
[7646]55      ALLOCATE( trdtx(jpi,jpj,jpk) , trdty(jpi,jpj,jpk) , trdt(jpi,jpj,jpk) , avt_evd(jpi,jpj,jpk), STAT= trd_tra_alloc )
[2715]56      !
[10425]57      CALL mpp_sum ( 'trdtra', trd_tra_alloc )
58      IF( trd_tra_alloc /= 0 )   CALL ctl_stop( 'STOP', 'trd_tra_alloc: failed to allocate arrays' )
[2715]59   END FUNCTION trd_tra_alloc
60
61
[12377]62   SUBROUTINE trd_tra( kt, Kmm, Krhs, ctype, ktra, ktrd, ptrd, pu, ptra )
[2026]63      !!---------------------------------------------------------------------
64      !!                  ***  ROUTINE trd_tra  ***
65      !!
[4990]66      !! ** Purpose : pre-process tracer trends
[2026]67      !!
[4990]68      !! ** Method  : - mask the trend
69      !!              - advection (ptra present) converte the incoming flux (U.T)
70      !!              into trend (U.T => -U.grat(T)=div(U.T)-T.div(U)) through a
71      !!              call to trd_tra_adv
72      !!              - 'TRA' case : regroup T & S trends
73      !!              - send the trends to trd_tra_mng (trdtrc) for further processing
[2026]74      !!----------------------------------------------------------------------
[4990]75      INTEGER                         , INTENT(in)           ::   kt      ! time step
76      CHARACTER(len=3)                , INTENT(in)           ::   ctype   ! tracers trends type 'TRA'/'TRC'
77      INTEGER                         , INTENT(in)           ::   ktra    ! tracer index
78      INTEGER                         , INTENT(in)           ::   ktrd    ! tracer trend index
[12377]79      INTEGER                         , INTENT(in)           ::   Kmm, Krhs ! time level indices
[4990]80      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in)           ::   ptrd    ! tracer trend  or flux
[12377]81      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in), OPTIONAL ::   pu      ! now velocity
[4990]82      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in), OPTIONAL ::   ptra    ! now tracer variable
[2715]83      !
[9019]84      INTEGER ::   jk   ! loop indices
85      REAL(wp),        DIMENSION(jpi,jpj,jpk) ::   ztrds             ! 3D workspace
86      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   zwt, zws, ztrdt   ! 3D workspace
[4990]87      !!----------------------------------------------------------------------
88      !     
89      IF( .NOT. ALLOCATED( trdtx ) ) THEN      ! allocate trdtra arrays
[2715]90         IF( trd_tra_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'trd_tra : unable to allocate arrays' )
91      ENDIF
[2026]92
[4990]93      IF( ctype == 'TRA' .AND. ktra == jp_tem ) THEN   !==  Temperature trend  ==!
94         !
95         SELECT CASE( ktrd )
96         !                            ! advection: transform the advective flux into a trend
[12377]97         CASE( jptra_xad )   ;   CALL trd_tra_adv( ptrd, pu, ptra, 'X', trdtx, Kmm ) 
98         CASE( jptra_yad )   ;   CALL trd_tra_adv( ptrd, pu, ptra, 'Y', trdty, Kmm ) 
99         CASE( jptra_zad )   ;   CALL trd_tra_adv( ptrd, pu, ptra, 'Z', trdt, Kmm )
[4990]100         CASE( jptra_bbc,    &        ! qsr, bbc: on temperature only, send to trd_tra_mng
101            &  jptra_qsr )   ;   trdt(:,:,:) = ptrd(:,:,:) * tmask(:,:,:)
102                                 ztrds(:,:,:) = 0._wp
[12377]103                                 CALL trd_tra_mng( trdt, ztrds, ktrd, kt, Kmm )
[9019]104 !!gm Gurvan, verify the jptra_evd trend please !
[8698]105         CASE( jptra_evd )   ;   avt_evd(:,:,:) = ptrd(:,:,:) * tmask(:,:,:)
[4990]106         CASE DEFAULT                 ! other trends: masked trends
107            trdt(:,:,:) = ptrd(:,:,:) * tmask(:,:,:)              ! mask & store
108         END SELECT
109         !
110      ENDIF
[2026]111
[4990]112      IF( ctype == 'TRA' .AND. ktra == jp_sal ) THEN      !==  Salinity trends  ==!
[2026]113         !
[4990]114         SELECT CASE( ktrd )
115         !                            ! advection: transform the advective flux into a trend
116         !                            !            and send T & S trends to trd_tra_mng
[12377]117         CASE( jptra_xad  )   ;   CALL trd_tra_adv( ptrd , pu  , ptra, 'X'  , ztrds, Kmm ) 
118                                  CALL trd_tra_mng( trdtx, ztrds, ktrd, kt, Kmm   )
119         CASE( jptra_yad  )   ;   CALL trd_tra_adv( ptrd , pu  , ptra, 'Y'  , ztrds, Kmm ) 
120                                  CALL trd_tra_mng( trdty, ztrds, ktrd, kt, Kmm   )
121         CASE( jptra_zad  )   ;   CALL trd_tra_adv( ptrd , pu  , ptra, 'Z'  , ztrds, Kmm ) 
122                                  CALL trd_tra_mng( trdt , ztrds, ktrd, kt, Kmm   )
[4990]123         CASE( jptra_zdfp )           ! diagnose the "PURE" Kz trend (here: just before the swap)
124            !                         ! iso-neutral diffusion case otherwise jptra_zdf is "PURE"
[9019]125            ALLOCATE( zwt(jpi,jpj,jpk), zws(jpi,jpj,jpk), ztrdt(jpi,jpj,jpk) )
[4990]126            !
127            zwt(:,:, 1 ) = 0._wp   ;   zws(:,:, 1 ) = 0._wp            ! vertical diffusive fluxes
128            zwt(:,:,jpk) = 0._wp   ;   zws(:,:,jpk) = 0._wp
129            DO jk = 2, jpk
[12377]130               zwt(:,:,jk) = avt(:,:,jk) * ( ts(:,:,jk-1,jp_tem,Krhs) - ts(:,:,jk,jp_tem,Krhs) ) / e3w(:,:,jk,Kmm) * tmask(:,:,jk)
131               zws(:,:,jk) = avs(:,:,jk) * ( ts(:,:,jk-1,jp_sal,Krhs) - ts(:,:,jk,jp_sal,Krhs) ) / e3w(:,:,jk,Kmm) * tmask(:,:,jk)
[4990]132            END DO
133            !
134            ztrdt(:,:,jpk) = 0._wp   ;   ztrds(:,:,jpk) = 0._wp
135            DO jk = 1, jpkm1
[12377]136               ztrdt(:,:,jk) = ( zwt(:,:,jk) - zwt(:,:,jk+1) ) / e3t(:,:,jk,Kmm)
137               ztrds(:,:,jk) = ( zws(:,:,jk) - zws(:,:,jk+1) ) / e3t(:,:,jk,Kmm) 
[4990]138            END DO
[12377]139            CALL trd_tra_mng( ztrdt, ztrds, jptra_zdfp, kt, Kmm ) 
[4990]140            !
[7646]141            !                         ! Also calculate EVD trend at this point.
142            zwt(:,:,:) = 0._wp   ;   zws(:,:,:) = 0._wp            ! vertical diffusive fluxes
143            DO jk = 2, jpk
[12377]144               zwt(:,:,jk) = avt_evd(:,:,jk) * ( ts(:,:,jk-1,jp_tem,Krhs) - ts(:,:,jk,jp_tem,Krhs) ) / e3w(:,:,jk,Kmm) * tmask(:,:,jk)
145               zws(:,:,jk) = avt_evd(:,:,jk) * ( ts(:,:,jk-1,jp_sal,Krhs) - ts(:,:,jk,jp_sal,Krhs) ) / e3w(:,:,jk,Kmm) * tmask(:,:,jk)
[7646]146            END DO
147            !
148            ztrdt(:,:,jpk) = 0._wp   ;   ztrds(:,:,jpk) = 0._wp
149            DO jk = 1, jpkm1
[12377]150               ztrdt(:,:,jk) = ( zwt(:,:,jk) - zwt(:,:,jk+1) ) / e3t(:,:,jk,Kmm)
151               ztrds(:,:,jk) = ( zws(:,:,jk) - zws(:,:,jk+1) ) / e3t(:,:,jk,Kmm) 
[7646]152            END DO
[12377]153            CALL trd_tra_mng( ztrdt, ztrds, jptra_evd, kt, Kmm ) 
[7646]154            !
[9019]155            DEALLOCATE( zwt, zws, ztrdt )
[4990]156            !
157         CASE DEFAULT                 ! other trends: mask and send T & S trends to trd_tra_mng
158            ztrds(:,:,:) = ptrd(:,:,:) * tmask(:,:,:)
[12377]159            CALL trd_tra_mng( trdt, ztrds, ktrd, kt, Kmm ) 
[4990]160         END SELECT
161      ENDIF
162
163      IF( ctype == 'TRC' ) THEN                           !==  passive tracer trend  ==!
[2026]164         !
[4990]165         SELECT CASE( ktrd )
166         !                            ! advection: transform the advective flux into a masked trend
[12377]167         CASE( jptra_xad )   ;   CALL trd_tra_adv( ptrd , pu , ptra, 'X', ztrds, Kmm ) 
168         CASE( jptra_yad )   ;   CALL trd_tra_adv( ptrd , pu , ptra, 'Y', ztrds, Kmm ) 
169         CASE( jptra_zad )   ;   CALL trd_tra_adv( ptrd , pu , ptra, 'Z', ztrds, Kmm ) 
[4990]170         CASE DEFAULT                 ! other trends: just masked
171                                 ztrds(:,:,:) = ptrd(:,:,:) * tmask(:,:,:)
172         END SELECT
173         !                            ! send trend to trd_trc
[12377]174         CALL trd_trc( ztrds, ktra, ktrd, kt, Kmm ) 
[4990]175         !
[2026]176      ENDIF
177      !
178   END SUBROUTINE trd_tra
179
[2715]180
[12377]181   SUBROUTINE trd_tra_adv( pf, pu, pt, cdir, ptrd, Kmm )
[2026]182      !!---------------------------------------------------------------------
183      !!                  ***  ROUTINE trd_tra_adv  ***
184      !!
[4990]185      !! ** Purpose :   transformed a advective flux into a masked advective trends
186      !!
187      !! ** Method  :   use the following transformation: -div(U.T) = - U grad(T) + T.div(U)
188      !!       i-advective trends = -un. di-1[T] = -( di-1[fi] - tn di-1[un] )
189      !!       j-advective trends = -un. di-1[T] = -( dj-1[fi] - tn dj-1[un] )
190      !!       k-advective trends = -un. di+1[T] = -( dk+1[fi] - tn dk+1[un] )
191      !!                where fi is the incoming advective flux.
[2026]192      !!----------------------------------------------------------------------
[4990]193      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in   ) ::   pf      ! advective flux in one direction
[12377]194      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in   ) ::   pu      ! now velocity   in one direction
195      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in   ) ::   pt      ! now or before tracer
[4990]196      CHARACTER(len=1)                , INTENT(in   ) ::   cdir    ! X/Y/Z direction
197      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(  out) ::   ptrd    ! advective trend in one direction
[12377]198      INTEGER,  INTENT(in)                            ::   Kmm     ! time level index
[2715]199      !
200      INTEGER  ::   ji, jj, jk   ! dummy loop indices
[4990]201      INTEGER  ::   ii, ij, ik   ! index shift as function of the direction
[2026]202      !!----------------------------------------------------------------------
[4990]203      !
204      SELECT CASE( cdir )      ! shift depending on the direction
205      CASE( 'X' )   ;   ii = 1   ;   ij = 0   ;   ik = 0      ! i-trend
206      CASE( 'Y' )   ;   ii = 0   ;   ij = 1   ;   ik = 0      ! j-trend
207      CASE( 'Z' )   ;   ii = 0   ;   ij = 0   ;   ik =-1      ! k-trend
[2026]208      END SELECT
209      !
[4990]210      !                        ! set to zero uncomputed values
211      ptrd(jpi,:,:) = 0._wp   ;   ptrd(1,:,:) = 0._wp
212      ptrd(:,jpj,:) = 0._wp   ;   ptrd(:,1,:) = 0._wp
213      ptrd(:,:,jpk) = 0._wp
[2026]214      !
[12377]215      DO_3D_00_00( 1, jpkm1 )
216         ptrd(ji,jj,jk) = - (     pf (ji,jj,jk) - pf (ji-ii,jj-ij,jk-ik)                        &
217           &                  - ( pu(ji,jj,jk) - pu(ji-ii,jj-ij,jk-ik) ) * pt(ji,jj,jk)  )   &
218           &              * r1_e1e2t(ji,jj) / e3t(ji,jj,jk,Kmm) * tmask(ji,jj,jk)
219      END_3D
[2026]220      !
221   END SUBROUTINE trd_tra_adv
222
[4990]223
[12377]224   SUBROUTINE trd_tra_mng( ptrdx, ptrdy, ktrd, kt, Kmm )
[4990]225      !!---------------------------------------------------------------------
226      !!                  ***  ROUTINE trd_tra_mng  ***
227      !!
228      !! ** Purpose :   Dispatch all tracer trends computation, e.g. 3D output,
229      !!                integral constraints, potential energy, and/or
230      !!                mixed layer budget.
[2026]231      !!----------------------------------------------------------------------
[4990]232      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptrdx   ! Temperature or U trend
233      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptrdy   ! Salinity    or V trend
234      INTEGER                   , INTENT(in   ) ::   ktrd    ! tracer trend index
235      INTEGER                   , INTENT(in   ) ::   kt      ! time step
[12377]236      INTEGER                   , INTENT(in   ) ::   Kmm     ! time level index
[4990]237      !!----------------------------------------------------------------------
238
[6140]239      IF( neuler == 0 .AND. kt == nit000    ) THEN   ;   r2dt =      rdt      ! = rdt (restart with Euler time stepping)
240      ELSEIF(               kt <= nit000 + 1) THEN   ;   r2dt = 2. * rdt      ! = 2 rdt (leapfrog)
[4990]241      ENDIF
242
243      !                   ! 3D output of tracers trends using IOM interface
[12377]244      IF( ln_tra_trd )   CALL trd_tra_iom ( ptrdx, ptrdy, ktrd, kt, Kmm )
[4990]245
246      !                   ! Integral Constraints Properties for tracers trends                                       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
[12377]247      IF( ln_glo_trd )   CALL trd_glo( ptrdx, ptrdy, ktrd, 'TRA', kt, Kmm )
[4990]248
249      !                   ! Potential ENergy trends
[12377]250      IF( ln_PE_trd  )   CALL trd_pen( ptrdx, ptrdy, ktrd, kt, r2dt, Kmm )
[4990]251
252      !                   ! Mixed layer trends for active tracers
253      IF( ln_tra_mxl )   THEN   
254         !-----------------------------------------------------------------------------------------------
255         ! W.A.R.N.I.N.G :
256         ! jptra_ldf : called by traldf.F90
257         !                 at this stage we store:
258         !                  - the lateral geopotential diffusion (here, lateral = horizontal)
259         !                  - and the iso-neutral diffusion if activated
260         ! jptra_zdf : called by trazdf.F90
261         !                 * in case of iso-neutral diffusion we store the vertical diffusion component in the
262         !                   lateral trend including the K_z contrib, which will be removed later (see trd_mxl)
263         !-----------------------------------------------------------------------------------------------
264
265         SELECT CASE ( ktrd )
266         CASE ( jptra_xad )        ;   CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_xad, '3D' )   ! zonal    advection
267         CASE ( jptra_yad )        ;   CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_yad, '3D' )   ! merid.   advection
268         CASE ( jptra_zad )        ;   CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_zad, '3D' )   ! vertical advection
269         CASE ( jptra_ldf )        ;   CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_ldf, '3D' )   ! lateral  diffusion
270         CASE ( jptra_bbl )        ;   CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_bbl, '3D' )   ! bottom boundary layer
271         CASE ( jptra_zdf )
272            IF( ln_traldf_iso ) THEN ; CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_ldf, '3D' )   ! lateral  diffusion (K_z)
273            ELSE                   ;   CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_zdf, '3D' )   ! vertical diffusion (K_z)
274            ENDIF
275         CASE ( jptra_dmp )        ;   CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_dmp, '3D' )   ! internal 3D restoring (tradmp)
276         CASE ( jptra_qsr )        ;   CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_for, '3D' )   ! air-sea : penetrative sol radiat
277         CASE ( jptra_nsr )        ;   ptrdx(:,:,2:jpk) = 0._wp   ;   ptrdy(:,:,2:jpk) = 0._wp
278                                       CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_for, '2D' )   ! air-sea : non penetr sol radiation
279         CASE ( jptra_bbc )        ;   CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_bbc, '3D' )   ! bottom bound cond (geoth flux)
280         CASE ( jptra_npc )        ;   CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_npc, '3D' )   ! non penetr convect adjustment
281         CASE ( jptra_atf )        ;   CALL trd_mxl_zint( ptrdx, ptrdy, jpmxl_atf, '3D' )   ! asselin time filter (last trend)
282                                   !
283                                       CALL trd_mxl( kt, r2dt )                             ! trends: Mixed-layer (output)
284         END SELECT
285         !
286      ENDIF
287      !
288   END SUBROUTINE trd_tra_mng
289
290
[12377]291   SUBROUTINE trd_tra_iom( ptrdx, ptrdy, ktrd, kt, Kmm )
[4990]292      !!---------------------------------------------------------------------
293      !!                  ***  ROUTINE trd_tra_iom  ***
294      !!
295      !! ** Purpose :   output 3D tracer trends using IOM
296      !!----------------------------------------------------------------------
297      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptrdx   ! Temperature or U trend
298      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptrdy   ! Salinity    or V trend
299      INTEGER                   , INTENT(in   ) ::   ktrd    ! tracer trend index
300      INTEGER                   , INTENT(in   ) ::   kt      ! time step
[12377]301      INTEGER                   , INTENT(in   ) ::   Kmm     ! time level index
[4990]302      !!
303      INTEGER ::   ji, jj, jk   ! dummy loop indices
304      INTEGER ::   ikbu, ikbv   ! local integers
[9019]305      REAL(wp), ALLOCATABLE, DIMENSION(:,:)   ::   z2dx, z2dy   ! 2D workspace
[4990]306      !!----------------------------------------------------------------------
307      !
308!!gm Rq: mask the trends already masked in trd_tra, but lbc_lnk should probably be added
309      !
[8698]310      ! Trends evaluated every time step that could go to the standard T file and can be output every ts into a 1ts file if 1ts output is selected
[4990]311      SELECT CASE( ktrd )
[8698]312      ! This total trend is done every time step
313      CASE( jptra_tot  )   ;   CALL iom_put( "ttrd_tot" , ptrdx )           ! model total trend
[9019]314                               CALL iom_put( "strd_tot" , ptrdy )
[4990]315      END SELECT
[9019]316      !
[8698]317      ! These trends are done every second time step. When 1ts output is selected must go different (2ts) file from standard T-file
318      IF( MOD( kt, 2 ) == 0 ) THEN
319         SELECT CASE( ktrd )
[9019]320         CASE( jptra_xad  )   ;   CALL iom_put( "ttrd_xad"  , ptrdx )        ! x- horizontal advection
321                                  CALL iom_put( "strd_xad"  , ptrdy )
322         CASE( jptra_yad  )   ;   CALL iom_put( "ttrd_yad"  , ptrdx )        ! y- horizontal advection
323                                  CALL iom_put( "strd_yad"  , ptrdy )
324         CASE( jptra_zad  )   ;   CALL iom_put( "ttrd_zad"  , ptrdx )        ! z- vertical   advection
325                                  CALL iom_put( "strd_zad"  , ptrdy )
326                                  IF( ln_linssh ) THEN                   ! cst volume : adv flux through z=0 surface
327                                     ALLOCATE( z2dx(jpi,jpj), z2dy(jpi,jpj) )
[12377]328                                     z2dx(:,:) = ww(:,:,1) * ts(:,:,1,jp_tem,Kmm) / e3t(:,:,1,Kmm)
329                                     z2dy(:,:) = ww(:,:,1) * ts(:,:,1,jp_sal,Kmm) / e3t(:,:,1,Kmm)
[9019]330                                     CALL iom_put( "ttrd_sad", z2dx )
331                                     CALL iom_put( "strd_sad", z2dy )
332                                     DEALLOCATE( z2dx, z2dy )
333                                  ENDIF
334         CASE( jptra_totad  ) ;   CALL iom_put( "ttrd_totad", ptrdx )        ! total   advection
335                                  CALL iom_put( "strd_totad", ptrdy )
336         CASE( jptra_ldf  )   ;   CALL iom_put( "ttrd_ldf"  , ptrdx )        ! lateral diffusion
337                                  CALL iom_put( "strd_ldf"  , ptrdy )
338         CASE( jptra_zdf  )   ;   CALL iom_put( "ttrd_zdf"  , ptrdx )        ! vertical diffusion (including Kz contribution)
339                                  CALL iom_put( "strd_zdf"  , ptrdy )
340         CASE( jptra_zdfp )   ;   CALL iom_put( "ttrd_zdfp" , ptrdx )        ! PURE vertical diffusion (no isoneutral contribution)
341                                  CALL iom_put( "strd_zdfp" , ptrdy )
342         CASE( jptra_evd )    ;   CALL iom_put( "ttrd_evd"  , ptrdx )        ! EVD trend (convection)
343                                  CALL iom_put( "strd_evd"  , ptrdy )
344         CASE( jptra_dmp  )   ;   CALL iom_put( "ttrd_dmp"  , ptrdx )        ! internal restoring (damping)
345                                  CALL iom_put( "strd_dmp"  , ptrdy )
346         CASE( jptra_bbl  )   ;   CALL iom_put( "ttrd_bbl"  , ptrdx )        ! bottom boundary layer
347                                  CALL iom_put( "strd_bbl"  , ptrdy )
348         CASE( jptra_npc  )   ;   CALL iom_put( "ttrd_npc"  , ptrdx )        ! static instability mixing
349                                  CALL iom_put( "strd_npc"  , ptrdy )
350         CASE( jptra_bbc  )   ;   CALL iom_put( "ttrd_bbc"  , ptrdx )        ! geothermal heating   (only on temperature)
351         CASE( jptra_nsr  )   ;   CALL iom_put( "ttrd_qns"  , ptrdx(:,:,1) ) ! surface forcing + runoff (ln_rnf=T)
352                                  CALL iom_put( "strd_cdt"  , ptrdy(:,:,1) )        ! output as 2D surface fields
353         CASE( jptra_qsr  )   ;   CALL iom_put( "ttrd_qsr"  , ptrdx )        ! penetrative solar radiat. (only on temperature)
[8698]354         END SELECT
355         ! the Asselin filter trend  is also every other time step but needs to be lagged one time step
356         ! Even when 1ts output is selected can go to the same (2ts) file as the trends plotted every even time step.
357      ELSE IF( MOD( kt, 2 ) == 1 ) THEN
358         SELECT CASE( ktrd )
359         CASE( jptra_atf  )   ;   CALL iom_put( "ttrd_atf" , ptrdx )        ! asselin time Filter
[10036]360                                  CALL iom_put( "strd_atf" , ptrdy )
[8698]361         END SELECT
362      END IF
[4990]363      !
364   END SUBROUTINE trd_tra_iom
365
[2026]366   !!======================================================================
367END MODULE trdtra
Note: See TracBrowser for help on using the repository browser.