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.
dynbfr.F90 in branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/DYN – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/DYN/dynbfr.F90 @ 4460

Last change on this file since 4460 was 3211, checked in by spickles2, 12 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

  • Property svn:keywords set to Id
File size: 4.1 KB
Line 
1MODULE dynbfr
2   !!==============================================================================
3   !!                 ***  MODULE  dynbfr  ***
4   !! Ocean dynamics :  bottom friction component of the momentum mixing trend
5   !!==============================================================================
6   !! History :  3.2  ! 2008-11  (A. C. Coward)  Original code
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   dyn_bfr      : Update the momentum trend with the bottom friction contribution
11   !!----------------------------------------------------------------------
12   USE oce             ! ocean dynamics and tracers variables
13   USE dom_oce         ! ocean space and time domain variables
14   USE zdf_oce         ! ocean vertical physics variables
15   USE trdmod          ! ocean active dynamics and tracers trends
16   USE trdmod_oce      ! ocean variables trends
17   USE in_out_manager  ! I/O manager
18   USE prtctl          ! Print control
19
20   IMPLICIT NONE
21   PRIVATE
22
23   PUBLIC   dyn_bfr    !  routine called by step.F90
24
25   !! * Control permutation of array indices
26#  include "oce_ftrans.h90"
27#  include "dom_oce_ftrans.h90"
28#  include "zdf_oce_ftrans.h90"
29
30   !! * Substitutions
31#  include "domzgr_substitute.h90"
32#  include "zdfddm_substitute.h90"
33#  include "vectopt_loop_substitute.h90"
34   !!----------------------------------------------------------------------
35   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
36   !! $Id$
37   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
38   !!----------------------------------------------------------------------
39CONTAINS
40   
41   SUBROUTINE dyn_bfr( kt )
42      !!----------------------------------------------------------------------
43      !!                  ***  ROUTINE dyn_bfr  ***
44      !!
45      !! ** Purpose :   compute the bottom friction ocean dynamics physics.
46      !!
47      !! ** Action  :   (ua,va)   momentum trend increased by bottom friction trend
48      !!---------------------------------------------------------------------
49      USE oce, ONLY:   ztrduv => tsa   ! tsa used as 4D workspace
50      !! DCSE_NEMO: module variable renamed, need additional directives
51!FTRANS ztrduv :I :I :z :I
52
53      !!
54      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
55      !!
56      INTEGER  ::   ji, jj       ! dummy loop indexes
57      INTEGER  ::   ikbu, ikbv   ! local integers
58      REAL(wp) ::   zm1_2dt      ! local scalar
59      !!---------------------------------------------------------------------
60      !
61      zm1_2dt = - 1._wp / ( 2._wp * rdt )
62
63      IF( l_trddyn )   THEN                      ! temporary save of ua and va trends
64         ztrduv(:,:,:,1) = ua(:,:,:)
65         ztrduv(:,:,:,2) = va(:,:,:)
66      ENDIF
67
68# if defined key_vectopt_loop
69      DO jj = 1, 1
70         DO ji = jpi+2, jpij-jpi-1   ! vector opt. (forced unrolling)
71# else
72      DO jj = 2, jpjm1
73         DO ji = 2, jpim1
74# endif
75            ikbu = mbku(ji,jj)          ! deepest ocean u- & v-levels
76            ikbv = mbkv(ji,jj)
77            !
78            ! Apply stability criteria on absolute value  : abs(bfr/e3) < 1/(2dt) => bfr/e3 > -1/(2dt)
79            ua(ji,jj,ikbu) = ua(ji,jj,ikbu) + MAX(  bfrua(ji,jj) / fse3u(ji,jj,ikbu) , zm1_2dt  ) * ub(ji,jj,ikbu)
80            va(ji,jj,ikbv) = va(ji,jj,ikbv) + MAX(  bfrva(ji,jj) / fse3v(ji,jj,ikbv) , zm1_2dt  ) * vb(ji,jj,ikbv)
81         END DO
82      END DO
83
84      !
85      IF( l_trddyn )   THEN                      ! save the vertical diffusive trends for further diagnostics
86         ztrduv(:,:,:,1) = ua(:,:,:) - ztrduv(:,:,:,1)
87         ztrduv(:,:,:,2) = va(:,:,:) - ztrduv(:,:,:,2)
88         CALL trd_mod( ztrduv(:,:,:,1), ztrduv(:,:,:,2), jpdyn_trd_bfr, 'DYN', kt )
89      ENDIF
90      !                                          ! print mean trends (used for debugging)
91      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ua, clinfo1=' bfr  - Ua: ', mask1=umask,               &
92         &                       tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
93      !
94   END SUBROUTINE dyn_bfr
95
96   !!==============================================================================
97END MODULE dynbfr
Note: See TracBrowser for help on using the repository browser.