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.
trddyn.F90 in branches/2012/dev_r3309_LOCEAN12_Ediag/NEMOGCM/NEMO/OPA_SRC/TRD – NEMO

source: branches/2012/dev_r3309_LOCEAN12_Ediag/NEMOGCM/NEMO/OPA_SRC/TRD/trddyn.F90 @ 3325

Last change on this file since 3325 was 3325, checked in by gm, 12 years ago

Ediag branche: #927 add Kinetic Energy trend diagnostics (trdken.F90)

  • Property svn:keywords set to Id
File size: 9.4 KB
Line 
1MODULE trddyn
2   !!======================================================================
3   !!                       ***  MODULE  trddyn  ***
4   !! Ocean diagnostics:  ocean dynamic trends
5   !!=====================================================================
6   !! History :  3.5  !  2012-02  (G. Madec) creation from trdmod: split DYN and TRA trends
7   !!                                        and manage  3D trends output for U, V, and KE
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   trd_dyn       : manage the type of momentum trend diagnostics (3D I/O, domain averaged, KE)
12   !!   trd_dyn_iom   : output 3D momentum and/or tracer trends using IOM
13   !!   trd_dyn_init  : initialization step
14   !!----------------------------------------------------------------------
15   USE oce            ! ocean dynamics and tracers variables
16   USE dom_oce        ! ocean space and time domain variables
17   USE zdf_oce        ! ocean vertical physics variables
18   USE trd_oce        ! trends: ocean variables
19   USE zdfbfr         ! bottom friction
20   USE ldftra_oce     ! ocean active tracers lateral physics
21   USE sbc_oce        ! surface boundary condition: ocean
22   USE phycst         ! physical constants
23   USE trdken         ! trends: Kinetic ENergy
24   USE trdglo         ! trends: global domain averaged
25   USE trdvor         ! trends: vertical averaged vorticity
26   USE trdmld         ! trends: mixed layer averaged
27   USE in_out_manager ! I/O manager
28   USE iom            ! I/O manager library
29   USE lib_mpp        ! MPP library
30   USE wrk_nemo       ! Memory allocation
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC trd_dyn        ! called by all dynXX modules
36
37   !! * Substitutions
38#  include "domzgr_substitute.h90"
39#  include "vectopt_loop_substitute.h90"
40   !!----------------------------------------------------------------------
41   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
42   !! $Id$
43   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
44   !!----------------------------------------------------------------------
45CONTAINS
46
47   SUBROUTINE trd_dyn( putrd, pvtrd, ktrd, kt )
48      !!---------------------------------------------------------------------
49      !!                  ***  ROUTINE trd_mod  ***
50      !!
51      !! ** Purpose :   Dispatch momentum trend computation, e.g. 3D output,
52      !!              integral constraints, barotropic vorticity, kinetic enrgy,
53      !!              and/or mixed layer budget.
54      !!----------------------------------------------------------------------
55      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   putrd, pvtrd   ! U and V trends
56      INTEGER                   , INTENT(in   ) ::   ktrd           ! trend index
57      INTEGER                   , INTENT(in   ) ::   kt             ! time step
58      !!----------------------------------------------------------------------
59      !
60      putrd(:,:,:) = putrd(:,:,:) * umask(:,:,:)                       ! mask the trends
61      pvtrd(:,:,:) = pvtrd(:,:,:) * vmask(:,:,:)
62      !
63
64!!gm NB : here a lbc_lnk should probably be added
65
66      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
67      !   3D output of momentum and/or tracers trends using IOM interface
68      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
69      IF( ln_dyn_trd )   CALL trd_dyn_iom( putrd, pvtrd, ktrd, kt )
70         
71      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
72      !  Integral Constraints Properties for momentum and/or tracers trends
73      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
74      IF( ln_glo_trd  )   CALL trd_glo( putrd, pvtrd, ktrd, 'DYN', kt )
75
76      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
77      !  Kinetic Energy trends
78      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
79      IF( ln_KE_trd  )   CALL trd_ken( putrd, pvtrd, ktrd, kt )
80
81      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
82      !  Vorticity trends
83      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
84      IF( ln_vor_trd  )   CALL trd_vor( putrd, pvtrd, ktrd, kt )
85
86      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
87      !  Mixed layer trends for active tracers
88      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
89!!gm      IF( ln_dyn_mld )   CALL trd_mld_dyn   
90      !
91   END SUBROUTINE trd_dyn
92
93
94   SUBROUTINE trd_dyn_iom( putrd, pvtrd, ktrd, kt )
95      !!---------------------------------------------------------------------
96      !!                  ***  ROUTINE trd_dyn_iom  ***
97      !!
98      !! ** Purpose :   output 3D trends using IOM
99      !!----------------------------------------------------------------------
100      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   putrd, pvtrd   ! U and V trends
101      INTEGER                   , INTENT(in   ) ::   ktrd           ! trend index
102      INTEGER                   , INTENT(in   ) ::   kt             ! time step
103      !
104      INTEGER ::   ji, jj, jk   ! dummy loop indices
105      INTEGER ::   ikbu, ikbv   ! local integers
106      REAL(wp), POINTER, DIMENSION(:,:)   ::   z2dx, z2dy, ztswu, ztswv   ! 2D workspace
107      REAL(wp), POINTER, DIMENSION(:,:,:) ::   z3dx, z3dy                 ! 3D workspace
108      !!----------------------------------------------------------------------
109      !
110      SELECT CASE( ktrd )
111      CASE( jpdyn_hpg )   ;   CALL iom_put( "utrd_hpg", putrd )    ! hydrostatic pressure gradient
112                              CALL iom_put( "vtrd_hpg", pvtrd )
113      CASE( jpdyn_spg )   ;   CALL iom_put( "utrd_spg", putrd )    ! surface pressure gradient
114                              CALL iom_put( "vtrd_spg", pvtrd )
115      CASE( jpdyn_pvo )   ;   CALL iom_put( "utrd_pvo", putrd )    ! planetary vorticity
116                              CALL iom_put( "vtrd_pvo", pvtrd )
117      CASE( jpdyn_rvo )   ;   CALL iom_put( "utrd_rvo", putrd )    ! relative  vorticity     (or metric term)
118                              CALL iom_put( "vtrd_rvo", pvtrd )
119      CASE( jpdyn_keg )   ;   CALL iom_put( "utrd_keg", putrd )    ! Kinetic Energy gradient (or had)
120                              CALL iom_put( "vtrd_keg", pvtrd )
121         z3dx(:,:,:) = 0._wp                                           ! U.dxU & V.dyV (approximation)
122         z3dy(:,:,:) = 0._wp
123         DO jk = 1, jpkm1                                                  ! no mask as un,vn are masked
124            DO jj = 2, jpjm1
125                DO ji = 2, jpim1
126                  z3dx(ji,jj,jk) = un(ji,jj,jk) * ( un(ji+1,jj,jk) - un(ji-1,jj,jk) ) / ( 2._wp * e1u(ji,jj) )
127                  z3dy(ji,jj,jk) = vn(ji,jj,jk) * ( vn(ji,jj+1,jk) - vn(ji,jj-1,jk) ) / ( 2._wp * e2v(ji,jj) )
128               END DO
129            END DO
130         END DO
131         CALL lbc_lnk( z3dx, 'U', -1. )   ;    CALL lbc_lnk( z3dy, 'V', -1. )
132                              CALL iom_put( "utrd_udx", z3dx  ) 
133                              CALL iom_put( "vtrd_vdy", z3dy  )
134      CASE( jpdyn_zad )   ;   CALL iom_put( "utrd_zad", putrd )    ! vertical   advection
135                              CALL iom_put( "vtrd_zad", pvtrd )
136      CASE( jpdyn_ldf )   ;   CALL iom_put( "utrd_ldf", putrd )    ! lateral diffusion
137                              CALL iom_put( "vtrd_ldf", pvtrd )
138      CASE( jpdyn_zdf )   ;   CALL iom_put( "utrd_zdf", putrd )    ! vertical diffusion
139                              CALL iom_put( "vtrd_zdf", pvtrd )
140                              !                                    ! wind stress trends
141                              z2dx(:,:) = ( utau_b(:,:) + utau(:,:) ) / ( fse3u(:,:,1) * rau0 )
142                              z2dy(:,:) = ( vtau_b(:,:) + vtau(:,:) ) / ( fse3v(:,:,1) * rau0 )
143                              CALL iom_put( "utrd_tau", z2dx )
144                              CALL iom_put( "vtrd_tau", z2dy )
145      CASE( jpdyn_bfr )
146         IF( .NOT.ln_bfrimp )     CALL iom_put( "utrd_bfr", putrd )    ! bottom friction (explicit case)
147         IF( .NOT.ln_bfrimp )     CALL iom_put( "vtrd_bfr", pvtrd )
148!!gm only valid if ln_bfrimp=T otherwise the bottom stress as to be recomputed at the end of the compuation....
149
150      CASE( jpdyn_atf )   ;   CALL iom_put( "utrd_atf", putrd )    ! asselin filter trends
151                              CALL iom_put( "vtrd_atf", pvtrd )
152         IF( ln_bfrimp ) THEN                                          ! bottom friction (implicit case)
153            z3dx(:,:,:) = 0._wp   ;   z3dy(:,:,:) = 0._wp                 ! after velocity known (now filed at this stage)
154            DO jk = 1, jpkm1
155               DO jj = 2, jpjm1
156                  DO ji = 2, jpim1
157                     ikbu = mbku(ji,jj)          ! deepest ocean u- & v-levels
158                     ikbv = mbkv(ji,jj)
159                     z3dx(ji,jj,jk) = bfrua(ji,jj) * un(ji,jj,ikbu) / fse3u(ji,jj,ikbu)
160                     z3dy(ji,jj,jk) = bfrva(ji,jj) * vn(ji,jj,ikbv) / fse3v(ji,jj,ikbv)
161                  END DO
162               END DO
163            END DO
164                              CALL iom_put( "utrd_bfr", z3dx )    ! bottom friction (implicit)
165                              CALL iom_put( "vtrd_bfr", z3dy )
166         ENDIF
167         !
168      END SELECT
169      !
170      CALL wrk_dealloc( jpi, jpj     , z2dx, z2dy, ztswu, ztswv )
171      CALL wrk_dealloc( jpi, jpj, jpk, z3dx, z3dy )
172      !
173   END SUBROUTINE trd_dyn_iom
174
175   !!======================================================================
176END MODULE trddyn
Note: See TracBrowser for help on using the repository browser.