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 NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/TRD – NEMO

source: NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/TRD/trddyn.F90 @ 11480

Last change on this file since 11480 was 11480, checked in by davestorkey, 5 years ago

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : Merge in changes from branch of branch.
Main changes:

  1. "nxt" modules renamed as "atf" and now just do Asselin time filtering. The time level swapping is achieved by swapping indices.
  2. Some additional prognostic grid variables changed to use a time dimension.

Notes:

  1. This merged branch passes SETTE tests but does not identical results to the SETTE tests with the trunk@10721 unless minor bugs to do with Euler timestepping and the OFF timestepping are fixed in the trunk (NEMO tickets #2310 and #2311).
  2. The nn_dttrc > 1 option for TOP (TOP has a different timestep to OCE) doesn't work. But it doesn't work in the trunk or NEMO 4.0 release either.
  • Property svn:keywords set to Id
File size: 10.6 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 phycst         ! physical constants
18   USE sbc_oce        ! surface boundary condition: ocean
19   USE zdf_oce        ! ocean vertical physics: variables
20!!gm   USE zdfdrg         ! ocean vertical physics: bottom friction
21   USE trd_oce        ! trends: ocean variables
22   USE trdken         ! trends: Kinetic ENergy
23   USE trdglo         ! trends: global domain averaged
24   USE trdvor         ! trends: vertical averaged vorticity
25   USE trdmxl         ! trends: mixed layer averaged
26   !
27   USE in_out_manager ! I/O manager
28   USE lbclnk         ! lateral boundary condition
29   USE iom            ! I/O manager library
30   USE lib_mpp        ! MPP library
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC trd_dyn        ! called by all dynXXX modules
36
37   !! * Substitutions
38#  include "vectopt_loop_substitute.h90"
39   !!----------------------------------------------------------------------
40   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
41   !! $Id$
42   !! Software governed by the CeCILL license (see ./LICENSE)
43   !!----------------------------------------------------------------------
44CONTAINS
45
46   SUBROUTINE trd_dyn( putrd, pvtrd, ktrd, kt, Kmm )
47      !!---------------------------------------------------------------------
48      !!                  ***  ROUTINE trd_mod  ***
49      !!
50      !! ** Purpose :   Dispatch momentum trend computation, e.g. 3D output,
51      !!              integral constraints, barotropic vorticity, kinetic enrgy,
52      !!              and/or mixed layer budget.
53      !!----------------------------------------------------------------------
54      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   putrd, pvtrd   ! U and V trends
55      INTEGER                   , INTENT(in   ) ::   ktrd           ! trend index
56      INTEGER                   , INTENT(in   ) ::   kt             ! time step
57      INTEGER                   , INTENT(in   ) ::   Kmm            ! time level index
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, Kmm )
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, Kmm )
75
76      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
77      !  Kinetic Energy trends
78      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
79      IF( ln_KE_trd  )   CALL trd_ken( putrd, pvtrd, ktrd, kt, Kmm )
80
81      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
82      !  Vorticity trends
83      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
84      IF( ln_vor_trd )   CALL trd_vor( putrd, pvtrd, ktrd, kt, Kmm )
85
86      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
87      !  Mixed layer trends for active tracers
88      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
89!!gm      IF( ln_dyn_mxl )   CALL trd_mxl_dyn   
90      !
91   END SUBROUTINE trd_dyn
92
93
94   SUBROUTINE trd_dyn_iom( putrd, pvtrd, ktrd, kt, Kmm )
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      INTEGER                   , INTENT(in   ) ::   Kmm            ! time level index
104      !
105      INTEGER ::   ji, jj, jk   ! dummy loop indices
106      INTEGER ::   ikbu, ikbv   ! local integers
107      REAL(wp), ALLOCATABLE, DIMENSION(:,:)   ::   z2dx, z2dy   ! 2D workspace
108      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   z3dx, z3dy   ! 3D workspace
109      !!----------------------------------------------------------------------
110      !
111      SELECT CASE( ktrd )
112      CASE( jpdyn_hpg )   ;   CALL iom_put( "utrd_hpg", putrd )    ! hydrostatic pressure gradient
113                              CALL iom_put( "vtrd_hpg", pvtrd )
114      CASE( jpdyn_spg )   ;   CALL iom_put( "utrd_spg", putrd )    ! surface pressure gradient
115                              CALL iom_put( "vtrd_spg", pvtrd )
116      CASE( jpdyn_pvo )   ;   CALL iom_put( "utrd_pvo", putrd )    ! planetary vorticity
117                              CALL iom_put( "vtrd_pvo", pvtrd )
118      CASE( jpdyn_rvo )   ;   CALL iom_put( "utrd_rvo", putrd )    ! relative  vorticity     (or metric term)
119                              CALL iom_put( "vtrd_rvo", pvtrd )
120      CASE( jpdyn_keg )   ;   CALL iom_put( "utrd_keg", putrd )    ! Kinetic Energy gradient (or had)
121                              CALL iom_put( "vtrd_keg", pvtrd )
122                              ALLOCATE( z3dx(jpi,jpj,jpk) , z3dy(jpi,jpj,jpk) )
123                              z3dx(:,:,:) = 0._wp                  ! U.dxU & V.dyV (approximation)
124                              z3dy(:,:,:) = 0._wp
125                              DO jk = 1, jpkm1   ! no mask as uu, vv are masked
126                                 DO jj = 2, jpjm1
127                                    DO ji = 2, jpim1
128                                       z3dx(ji,jj,jk) = uu(ji,jj,jk,Kmm) * ( uu(ji+1,jj,jk,Kmm) - uu(ji-1,jj,jk,Kmm) ) / ( 2._wp * e1u(ji,jj) )
129                                       z3dy(ji,jj,jk) = vv(ji,jj,jk,Kmm) * ( vv(ji,jj+1,jk,Kmm) - vv(ji,jj-1,jk,Kmm) ) / ( 2._wp * e2v(ji,jj) )
130                                    END DO
131                                 END DO
132                              END DO
133                              CALL lbc_lnk_multi( 'trddyn', z3dx, 'U', -1., z3dy, 'V', -1. )
134                              CALL iom_put( "utrd_udx", z3dx  )
135                              CALL iom_put( "vtrd_vdy", z3dy  )
136                              DEALLOCATE( z3dx , z3dy )
137      CASE( jpdyn_zad )   ;   CALL iom_put( "utrd_zad", putrd )    ! vertical advection
138                              CALL iom_put( "vtrd_zad", pvtrd )
139      CASE( jpdyn_ldf )   ;   CALL iom_put( "utrd_ldf", putrd )    ! lateral  diffusion
140                              CALL iom_put( "vtrd_ldf", pvtrd )
141      CASE( jpdyn_zdf )   ;   CALL iom_put( "utrd_zdf", putrd )    ! vertical diffusion
142                              CALL iom_put( "vtrd_zdf", pvtrd )
143                              !
144                              !                                    ! wind stress trends
145                              ALLOCATE( z2dx(jpi,jpj) , z2dy(jpi,jpj) )
146                              z2dx(:,:) = ( utau_b(:,:) + utau(:,:) ) / ( e3u(:,:,1,Kmm) * rau0 )
147                              z2dy(:,:) = ( vtau_b(:,:) + vtau(:,:) ) / ( e3v(:,:,1,Kmm) * rau0 )
148                              CALL iom_put( "utrd_tau", z2dx )
149                              CALL iom_put( "vtrd_tau", z2dy )
150                              DEALLOCATE( z2dx , z2dy )
151!!gm  to be changed : computation should be done in dynzdf.F90
152!!gm                + missing the top friction
153!                              !                                    ! bottom stress tends (implicit case)
154!                              IF( ln_drgimp ) THEN
155!                                 ALLOCATE( z3dx(jpi,jpj,jpk) , z3dy(jpi,jpj,jpk) )
156!                             z3dx(:,:,:) = 0._wp   ;   z3dy(:,:,:) = 0._wp  ! after velocity known (now filed at this stage)
157!                            DO jk = 1, jpkm1
158!                                    DO jj = 2, jpjm1
159!                                       DO ji = 2, jpim1
160!                                      ikbu = mbku(ji,jj)          ! deepest ocean u- & v-levels
161!                                          ikbv = mbkv(ji,jj)
162!                                          z3dx(ji,jj,jk) = 0.5 * ( rCdU_bot(ji+1,jj) + rCdU_bot(ji,jj) ) &
163!                                               &         * uu(ji,jj,ikbu,Kmm) / e3u(ji,jj,ikbu,Kmm)
164!                                          z3dy(ji,jj,jk) = 0.5 * ( rCdU_bot(ji,jj+1) + rCdU_bot(ji,jj) ) &
165!                                               &         * vv(ji,jj,ikbv,Kmm) / e3v(ji,jj,ikbv,Kmm)
166!                                    END DO
167!                                 END DO
168!                              END DO
169!                              CALL lbc_lnk_multi( 'trddyn', z3dx, 'U', -1., z3dy, 'V', -1. )
170!                              CALL iom_put( "utrd_bfr", z3dx )
171!                              CALL iom_put( "vtrd_bfr", z3dy )
172!                                 DEALLOCATE( z3dx , z3dy )
173!                              ENDIF
174!!gm end
175      CASE( jpdyn_bfr )       ! called if ln_drgimp=F
176                              CALL iom_put( "utrd_bfr", putrd )    ! bottom friction (explicit case)
177                              CALL iom_put( "vtrd_bfr", pvtrd )
178      CASE( jpdyn_atf )   ;   CALL iom_put( "utrd_atf", putrd )        ! asselin filter trends
179                              CALL iom_put( "vtrd_atf", pvtrd )
180      END SELECT
181      !
182   END SUBROUTINE trd_dyn_iom
183
184   !!======================================================================
185END MODULE trddyn
Note: See TracBrowser for help on using the repository browser.