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.
trcbdy.F90 in NEMO/trunk/src/TOP – NEMO

source: NEMO/trunk/src/TOP/trcbdy.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: 8.1 KB
Line 
1MODULE trcbdy
2   !!======================================================================
3   !!                       ***  MODULE  bdytrc  ***
4   !! Ocean tracers:   Apply boundary conditions for tracers in TOP component
5   !!======================================================================
6   !! History :  1.0  !  2005-01  (J. Chanut, A. Sellar)  Original code
7   !!            3.0  !  2008-04  (NEMO team)  add in the reference version
8   !!            3.4  !  2011     (D. Storkey) rewrite in preparation for OBC-BDY merge
9   !!            3.5  !  2012     (S. Mocavero, I. Epicoco) Optimization of BDY communications
10   !!            3.6  !  2015     (T. Lovato) Adapt BDY for tracers in TOP component
11   !!            4.0  !  2016     (T. Lovato) Generalize OBC structure
12   !!----------------------------------------------------------------------
13#if defined key_top
14   !!----------------------------------------------------------------------
15   !!   trc_bdy       : Apply open boundary conditions & damping to tracers
16   !!----------------------------------------------------------------------
17   USE timing                       ! Timing
18   USE oce_trc                      ! ocean dynamics and tracers variables
19   USE par_trc
20   USE trc                          ! ocean space and time domain variables
21   USE bdylib                       ! for orlanski library routines
22   USE lbclnk                       ! ocean lateral boundary conditions (or mpp link)
23   USE in_out_manager               ! I/O manager
24   USE bdy_oce                      ! ocean open boundary conditions
25
26   IMPLICIT NONE
27   PRIVATE
28
29   PUBLIC trc_bdy      ! routine called in trcnxt.F90
30   PUBLIC trc_bdy_dmp  ! routine called in trcstp.F90
31
32   !!----------------------------------------------------------------------
33   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
34   !! $Id$
35   !! Software governed by the CeCILL license (see ./LICENSE)
36   !!----------------------------------------------------------------------
37CONTAINS
38
39   SUBROUTINE trc_bdy( kt, Kbb, Kmm, Krhs )
40      !!----------------------------------------------------------------------
41      !!                  ***  SUBROUTINE trc_bdy  ***
42      !!
43      !! ** Purpose : - Apply open boundary conditions for TOP tracers
44      !!
45      !!----------------------------------------------------------------------
46      INTEGER, INTENT( in ) :: kt              ! Main time step counter
47      INTEGER, INTENT( in ) :: Kbb, Kmm, Krhs  ! time level indices
48      !!
49      INTEGER                           :: ib_bdy ,ir, jn ,igrd ! Loop indices
50      REAL(wp), POINTER, DIMENSION(:,:) ::  ztrc
51      REAL(wp), POINTER                 ::  zfac
52      LOGICAL                           :: llrim0               ! indicate if rim 0 is treated
53      LOGICAL, DIMENSION(4)             :: llsend1, llrecv1     ! indicate how communications are to be carried out
54      !!----------------------------------------------------------------------
55      !
56      IF( ln_timing )   CALL timing_start('trc_bdy')
57      !
58      igrd = 1 
59      llsend1(:) = .false.  ;   llrecv1(:) = .false.
60      DO ir = 1, 0, -1   ! treat rim 1 before rim 0
61         IF( ir == 0 ) THEN   ;   llrim0 = .TRUE.
62         ELSE                 ;   llrim0 = .FALSE.
63         END IF
64         DO ib_bdy=1, nb_bdy
65            DO jn = 1, jptra
66               !
67               ztrc => trcdta_bdy(jn,ib_bdy)%trc 
68               zfac => trcdta_bdy(jn,ib_bdy)%rn_fac
69               !
70               SELECT CASE( TRIM(trcdta_bdy(jn,ib_bdy)%cn_obc) )
71               CASE('none'        )   ;   CYCLE
72               CASE('frs'         )   ! treat the whole boundary at once
73                  IF( ir == 0 ) CALL bdy_frs( idx_bdy(ib_bdy),                tr(:,:,:,jn,Krhs), ztrc*zfac )
74               CASE('specified'   )   ! treat the whole rim      at once
75                  IF( ir == 0 ) CALL bdy_spe( idx_bdy(ib_bdy),                tr(:,:,:,jn,Krhs), ztrc*zfac )
76               CASE('neumann'     )   ;   CALL bdy_nmn( idx_bdy(ib_bdy), igrd         , tr(:,:,:,jn,Krhs) )   ! tra masked
77               CASE('orlanski'    )   ;   CALL bdy_orl( idx_bdy(ib_bdy), tr(:,:,:,jn,Kbb), tr(:,:,:,jn,Krhs), ztrc*zfac, ll_npo=.false. )
78               CASE('orlanski_npo')   ;   CALL bdy_orl( idx_bdy(ib_bdy), tr(:,:,:,jn,Kbb), tr(:,:,:,jn,Krhs), ztrc*zfac, ll_npo=.true. )
79               CASE DEFAULT           ;   CALL ctl_stop( 'trc_bdy : unrecognised option for open boundaries for passive tracers' )
80               END SELECT
81               !
82            END DO
83         END DO
84         !
85         IF( nn_hls > 1 .AND. ir == 1 ) CYCLE   ! at least 2 halos will be corrected -> no need to correct rim 1 before rim 0
86         IF( nn_hls == 1 ) THEN   ;   llsend1(:) = .false.   ;   llrecv1(:) = .false.   ;   END IF
87         DO ib_bdy=1, nb_bdy
88            SELECT CASE( TRIM(cn_tra(ib_bdy)) )
89            CASE('neumann')
90               llsend1(:) = llsend1(:) .OR. lsend_bdyint(ib_bdy,1,:,ir)   ! possibly every direction, T points
91               llrecv1(:) = llrecv1(:) .OR. lrecv_bdyint(ib_bdy,1,:,ir)   ! possibly every direction, T points
92            CASE('orlanski','orlanski_npo')
93               llsend1(:) = llsend1(:) .OR. lsend_bdy(ib_bdy,1,:,ir)   ! possibly every direction, T points
94               llrecv1(:) = llrecv1(:) .OR. lrecv_bdy(ib_bdy,1,:,ir)   ! possibly every direction, T points
95            END SELECT
96         END DO
97         IF( ANY(llsend1) .OR. ANY(llrecv1) ) THEN   ! if need to send/recv in at least one direction
98            CALL lbc_lnk( 'trcbdy', tr(:,:,:,:,Krhs), 'T',  1., kfillmode=jpfillnothing ,lsend=llsend1, lrecv=llrecv1 )
99         END IF
100         !
101      END DO   ! ir
102      !
103      IF( ln_timing )   CALL timing_stop('trc_bdy')
104      !
105   END SUBROUTINE trc_bdy
106
107
108   SUBROUTINE trc_bdy_dmp( kt, Kbb, Krhs )
109      !!----------------------------------------------------------------------
110      !!                 ***  SUBROUTINE trc_bdy_dmp  ***
111      !!                   
112      !! ** Purpose : Apply damping for tracers at open boundaries.
113      !!             It currently applies the damping to all tracers!!!
114      !!
115      !!----------------------------------------------------------------------
116      INTEGER,         INTENT(in) ::   kt
117      INTEGER,         INTENT(in) ::   Kbb, Krhs  ! time level indices
118      !!
119      INTEGER  ::   jn             ! Tracer index
120      REAL(wp) ::   zwgt           ! boundary weight
121      REAL(wp) ::   zta, zsa, ztime
122      INTEGER  ::   ib, ik, igrd   ! dummy loop indices
123      INTEGER  ::   ii, ij         ! 2D addresses
124      INTEGER  ::   ib_bdy         ! Loop index
125      !!----------------------------------------------------------------------
126      !
127      IF( ln_timing )   CALL timing_start('trc_bdy_dmp')
128      !
129      DO jn = 1, jptra
130         DO ib_bdy=1, nb_bdy
131            IF( trcdta_bdy(jn, ib_bdy)%dmp ) THEN
132               igrd = 1                       ! Everything is at T-points here
133               DO ib = 1, idx_bdy(ib_bdy)%nblen(igrd)
134                  ii = idx_bdy(ib_bdy)%nbi(ib,igrd)
135                  ij = idx_bdy(ib_bdy)%nbj(ib,igrd)
136                  zwgt = idx_bdy(ib_bdy)%nbd(ib,igrd)
137                  DO ik = 1, jpkm1
138                     zta = zwgt * ( trcdta_bdy(jn, ib_bdy)%trc(ib,ik) - tr(ii,ij,ik,jn,Kbb) ) * tmask(ii,ij,ik)
139                     tr(ii,ij,ik,jn,Krhs) = tr(ii,ij,ik,jn,Krhs) + zta
140                  END DO
141               END DO
142            ENDIF
143         END DO
144      END DO
145      !
146      IF( ln_timing )   CALL timing_stop('trc_bdy_dmp')
147      !
148   END SUBROUTINE trc_bdy_dmp
149 
150#else
151   !!----------------------------------------------------------------------
152   !!   Dummy module                   NO Unstruct Open Boundary Conditions
153   !!----------------------------------------------------------------------
154CONTAINS
155   SUBROUTINE trc_bdy(kt)      ! Empty routine
156      WRITE(*,*) 'trc_bdy: You should not have seen this print! error?', kt
157   END SUBROUTINE trc_bdy
158
159   SUBROUTINE trc_bdy_dmp(kt)      ! Empty routine
160      WRITE(*,*) 'trc_bdy_dmp: You should not have seen this print! error?', kt
161   END SUBROUTINE trc_bdy_dmp
162
163#endif
164
165   !!======================================================================
166END MODULE trcbdy
Note: See TracBrowser for help on using the repository browser.