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/UKMO/dev_r5518_GO6_package_FOAMv14/NEMOGCM/NEMO/OPA_SRC/TRD – NEMO

source: branches/UKMO/dev_r5518_GO6_package_FOAMv14/NEMOGCM/NEMO/OPA_SRC/TRD/trddyn.F90 @ 11442

Last change on this file since 11442 was 11442, checked in by mattmartin, 5 years ago

Introduction of stochastic physics in NEMO, based on Andrea Storto's code.
For details, see ticket https://code.metoffice.gov.uk/trac/utils/ticket/251.

File size: 10.5 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 sbc_oce        ! surface boundary condition: ocean
21   USE phycst         ! physical constants
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   USE in_out_manager ! I/O manager
27   USE lbclnk         ! lateral boundary condition
28   USE iom            ! I/O manager library
29   USE lib_mpp        ! MPP library
30   USE wrk_nemo       ! Memory allocation
31   USE stopack     
32
33   IMPLICIT NONE
34   PRIVATE
35
36   PUBLIC trd_dyn        ! called by all dynXX modules
37
38   !! * Substitutions
39#  include "domzgr_substitute.h90"
40#  include "vectopt_loop_substitute.h90"
41   !!----------------------------------------------------------------------
42   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
43   !! $Id$
44   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
45   !!----------------------------------------------------------------------
46CONTAINS
47
48   SUBROUTINE trd_dyn( putrd, pvtrd, ktrd, kt )
49      !!---------------------------------------------------------------------
50      !!                  ***  ROUTINE trd_mod  ***
51      !!
52      !! ** Purpose :   Dispatch momentum trend computation, e.g. 3D output,
53      !!              integral constraints, barotropic vorticity, kinetic enrgy,
54      !!              and/or mixed layer budget.
55      !!----------------------------------------------------------------------
56      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   putrd, pvtrd   ! U and V trends
57      INTEGER                   , INTENT(in   ) ::   ktrd           ! trend index
58      INTEGER                   , INTENT(in   ) ::   kt             ! time step
59      !!----------------------------------------------------------------------
60      !
61      putrd(:,:,:) = putrd(:,:,:) * umask(:,:,:)                       ! mask the trends
62      pvtrd(:,:,:) = pvtrd(:,:,:) * vmask(:,:,:)
63      !
64
65!!gm NB : here a lbc_lnk should probably be added
66
67      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
68      !   3D output of momentum and/or tracers trends using IOM interface
69      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
70      IF( ln_dyn_trd )   CALL trd_dyn_iom( putrd, pvtrd, ktrd, kt )
71      IF( ln_dyn_trd .AND. ln_stopack .AND. ln_sppt_dyn ) &
72         & CALL dyn_sppt_collect( putrd, pvtrd, ktrd, kt )
73         
74      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
75      !  Integral Constraints Properties for momentum and/or tracers trends
76      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
77      IF( ln_glo_trd )   CALL trd_glo( putrd, pvtrd, ktrd, 'DYN', kt )
78
79      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
80      !  Kinetic Energy trends
81      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
82      IF( ln_KE_trd  )   CALL trd_ken( putrd, pvtrd, ktrd, kt )
83
84      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
85      !  Vorticity trends
86      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
87      IF( ln_vor_trd )   CALL trd_vor( putrd, pvtrd, ktrd, kt )
88
89      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
90      !  Mixed layer trends for active tracers
91      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
92!!gm      IF( ln_dyn_mxl )   CALL trd_mxl_dyn   
93      !
94   END SUBROUTINE trd_dyn
95
96
97   SUBROUTINE trd_dyn_iom( putrd, pvtrd, ktrd, kt )
98      !!---------------------------------------------------------------------
99      !!                  ***  ROUTINE trd_dyn_iom  ***
100      !!
101      !! ** Purpose :   output 3D trends using IOM
102      !!----------------------------------------------------------------------
103      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   putrd, pvtrd   ! U and V trends
104      INTEGER                   , INTENT(in   ) ::   ktrd           ! trend index
105      INTEGER                   , INTENT(in   ) ::   kt             ! time step
106      !
107      INTEGER ::   ji, jj, jk   ! dummy loop indices
108      INTEGER ::   ikbu, ikbv   ! local integers
109      REAL(wp), POINTER, DIMENSION(:,:)   ::   z2dx, z2dy   ! 2D workspace
110      REAL(wp), POINTER, DIMENSION(:,:,:) ::   z3dx, z3dy   ! 3D workspace
111      !!----------------------------------------------------------------------
112      !
113      SELECT CASE( ktrd )
114      CASE( jpdyn_hpg )   ;   CALL iom_put( "utrd_hpg", putrd )    ! hydrostatic pressure gradient
115                              CALL iom_put( "vtrd_hpg", pvtrd )
116      CASE( jpdyn_spg )   ;   CALL iom_put( "utrd_spg", putrd )    ! surface pressure gradient
117                              CALL iom_put( "vtrd_spg", pvtrd )
118      CASE( jpdyn_spgexp );   CALL iom_put( "utrd_spgexp", putrd ) ! surface pressure gradient (explicit)
119                              CALL iom_put( "vtrd_spgexp", pvtrd )
120      CASE( jpdyn_spgflt );   CALL iom_put( "utrd_spgflt", putrd ) ! surface pressure gradient (filtered)
121                              CALL iom_put( "vtrd_spgflt", pvtrd )
122      CASE( jpdyn_pvo )   ;   CALL iom_put( "utrd_pvo", putrd )    ! planetary vorticity
123                              CALL iom_put( "vtrd_pvo", pvtrd )
124      CASE( jpdyn_rvo )   ;   CALL iom_put( "utrd_rvo", putrd )    ! relative  vorticity     (or metric term)
125                              CALL iom_put( "vtrd_rvo", pvtrd )
126      CASE( jpdyn_keg )   ;   CALL iom_put( "utrd_keg", putrd )    ! Kinetic Energy gradient (or had)
127                              CALL iom_put( "vtrd_keg", pvtrd )
128                              CALL wrk_alloc( jpi, jpj, jpk, z3dx, z3dy )
129                              z3dx(:,:,:) = 0._wp                  ! U.dxU & V.dyV (approximation)
130                              z3dy(:,:,:) = 0._wp
131                              DO jk = 1, jpkm1                 ! no mask as un,vn are masked
132                                 DO jj = 2, jpjm1
133                                    DO ji = 2, jpim1
134                                       z3dx(ji,jj,jk) = un(ji,jj,jk) * ( un(ji+1,jj,jk) - un(ji-1,jj,jk) ) / ( 2._wp * e1u(ji,jj) )
135                                       z3dy(ji,jj,jk) = vn(ji,jj,jk) * ( vn(ji,jj+1,jk) - vn(ji,jj-1,jk) ) / ( 2._wp * e2v(ji,jj) )
136                                    END DO
137                                 END DO
138                              END DO
139                              CALL lbc_lnk( z3dx, 'U', -1. )
140                              CALL lbc_lnk( z3dy, 'V', -1. )
141                              CALL iom_put( "utrd_udx", z3dx  )
142                              CALL iom_put( "vtrd_vdy", z3dy  )
143                              CALL wrk_dealloc( jpi, jpj, jpk, z3dx, z3dy )
144      CASE( jpdyn_zad )   ;   CALL iom_put( "utrd_zad", putrd )    ! vertical   advection
145                              CALL iom_put( "vtrd_zad", pvtrd )
146      CASE( jpdyn_ldf )   ;   CALL iom_put( "utrd_ldf", putrd )    ! lateral diffusion
147                              CALL iom_put( "vtrd_ldf", pvtrd )
148      CASE( jpdyn_zdf )   ;   CALL iom_put( "utrd_zdf", putrd )    ! vertical diffusion
149                              CALL iom_put( "vtrd_zdf", pvtrd )
150                              !                                    ! wind stress trends
151                              CALL wrk_alloc( jpi, jpj, z2dx, z2dy )
152                              z2dx(:,:) = ( utau_b(:,:) + utau(:,:) ) / ( fse3u(:,:,1) * rau0 )
153                              z2dy(:,:) = ( vtau_b(:,:) + vtau(:,:) ) / ( fse3v(:,:,1) * rau0 )
154                              CALL iom_put( "utrd_tau", z2dx )
155                              CALL iom_put( "vtrd_tau", z2dy )
156                              CALL wrk_dealloc( jpi, jpj, z2dx, z2dy )
157      CASE( jpdyn_bfr )       ! called if ln_bfrimp=T
158                              CALL iom_put( "utrd_bfr", putrd )    ! bottom friction (explicit case)
159                              CALL iom_put( "vtrd_bfr", pvtrd )
160      CASE( jpdyn_atf )   ;   CALL iom_put( "utrd_atf", putrd )        ! asselin filter trends
161                              CALL iom_put( "vtrd_atf", pvtrd )
162      CASE( jpdyn_bfri )  ;   IF( ln_bfrimp ) THEN                     ! bottom friction (implicit case)
163                                 CALL wrk_alloc( jpi, jpj, jpk, z3dx, z3dy )
164                                 z3dx(:,:,:) = 0._wp   ;   z3dy(:,:,:) = 0._wp  ! after velocity known (now filed at this stage)
165                                 DO jk = 1, jpkm1
166                                    DO jj = 2, jpjm1
167                                       DO ji = 2, jpim1
168                                          ikbu = mbku(ji,jj)          ! deepest ocean u- & v-levels
169                                          ikbv = mbkv(ji,jj)
170                                          z3dx(ji,jj,jk) = bfrua(ji,jj) * un(ji,jj,ikbu) / fse3u(ji,jj,ikbu)
171                                          z3dy(ji,jj,jk) = bfrva(ji,jj) * vn(ji,jj,ikbv) / fse3v(ji,jj,ikbv)
172                                       END DO
173                                    END DO
174                                 END DO
175                                 CALL lbc_lnk( z3dx, 'U', -1. ) ; CALL lbc_lnk( z3dy, 'V', -1. )
176                                 CALL iom_put( "utrd_bfri", z3dx )
177                                 CALL iom_put( "vtrd_bfri", z3dy )
178                                 CALL wrk_dealloc( jpi, jpj, jpk, z3dx, z3dy )
179                              ENDIF
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.