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/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/TOP – NEMO

source: NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/TOP/trcbdy.F90 @ 11067

Last change on this file since 11067 was 11067, checked in by girrmann, 5 years ago

dev_r10984_HPC-13 : new implementation of lbc_bdy_lnk in prevision of step 2, regroup communications, see #2285

  • Property svn:keywords set to Id
File size: 7.3 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, only: idx_bdy       ! 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 )
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      !!
48      INTEGER                           :: ib_bdy ,jn ,igrd ! Loop indeces
49      REAL(wp), POINTER, DIMENSION(:,:) ::  ztrc
50      REAL(wp), POINTER                 ::  zfac
51      LOGICAL, DIMENSION(4)             :: lsend1, lrecv1     ! indicate how communications are to be carried out
52      !!----------------------------------------------------------------------
53      !
54      IF( ln_timing )   CALL timing_start('trc_bdy')
55      !
56      igrd = 1 
57      !
58      DO ib_bdy=1, nb_bdy
59         DO jn = 1, jptra
60            !
61            ztrc => trcdta_bdy(jn,ib_bdy)%trc 
62            zfac => trcdta_bdy(jn,ib_bdy)%rn_fac
63            !
64            SELECT CASE( TRIM(trcdta_bdy(jn,ib_bdy)%cn_obc) )
65            CASE('none'        )   ;   CYCLE
66            CASE('frs'         )   ;   CALL bdy_frs( idx_bdy(ib_bdy),                tra(:,:,:,jn), ztrc*zfac )
67            CASE('specified'   )   ;   CALL bdy_spe( idx_bdy(ib_bdy),                tra(:,:,:,jn), ztrc*zfac )
68            CASE('neumann'     )   ;   CALL bdy_nmn( idx_bdy(ib_bdy), igrd         , tra(:,:,:,jn) )
69            CASE('orlanski'    )   ;   CALL bdy_orl( idx_bdy(ib_bdy), trb(:,:,:,jn), tra(:,:,:,jn), ztrc*zfac, ll_npo=.false. )
70            CASE('orlanski_npo')   ;   CALL bdy_orl( idx_bdy(ib_bdy), trb(:,:,:,jn), tra(:,:,:,jn), ztrc*zfac, ll_npo=.true. )
71            CASE DEFAULT           ;   CALL ctl_stop( 'trc_bdy : unrecognised option for open boundaries for passive tracers' )
72            END SELECT
73            !
74         END DO
75      END DO
76      !
77      lsend1(:) = .false.
78      lrecv1(:) = .false.
79      DO ib_bdy=1, nb_bdy
80         SELECT CASE( TRIM(cn_tra(ib_bdy)) )
81         CASE('neumann')
82            lsend1(:) = lsend1(:) .OR. lsend_bdy(ib_bdy,1,:)   ! to   every bdy neighbour, T points
83            lrecv1(:) = lrecv1(:) .OR. lrecv_bdy(ib_bdy,1,:)   ! from every bdy neighbour, T points
84         CASE('orlanski')
85            lsend1(:) = lsend1(:) .OR. lsend_bdy(ib_bdy,1,:)   ! to   every bdy neighbour, T points
86            lrecv1(:) = lrecv1(:) .OR. lrecv_bdy(ib_bdy,1,:)   ! from every bdy neighbour, T points
87         CASE('orlanski_npo')
88            lsend1(:) = lsend1(:) .OR. lsend_bdy(ib_bdy,1,:)   ! to   every bdy neighbour, T points
89            lrecv1(:) = lrecv1(:) .OR. lrecv_bdy(ib_bdy,1,:)   ! from every bdy neighbour, T points
90         END SELECT
91      END DO
92      IF( ANY(lsend1) .OR. ANY(lrecv1) ) THEN   ! if need to send/recv in at least one direction
93         CALL lbc_bdy_lnk( 'bdytra', lsend1, lrecv1, tsa, 'T',  1. )
94      END IF
95      !
96      IF( ln_timing )   CALL timing_stop('trc_bdy')
97      !
98   END SUBROUTINE trc_bdy
99
100
101   SUBROUTINE trc_bdy_dmp( kt )
102      !!----------------------------------------------------------------------
103      !!                 ***  SUBROUTINE trc_bdy_dmp  ***
104      !!                   
105      !! ** Purpose : Apply damping for tracers at open boundaries.
106      !!             It currently applies the damping to all tracers!!!
107      !!
108      !!----------------------------------------------------------------------
109      INTEGER,         INTENT(in) ::   kt
110      !!
111      INTEGER  ::   jn             ! Tracer index
112      REAL(wp) ::   zwgt           ! boundary weight
113      REAL(wp) ::   zta, zsa, ztime
114      INTEGER  ::   ib, ik, igrd   ! dummy loop indices
115      INTEGER  ::   ii, ij         ! 2D addresses
116      INTEGER  ::   ib_bdy         ! Loop index
117      !!----------------------------------------------------------------------
118      !
119      IF( ln_timing )   CALL timing_start('trc_bdy_dmp')
120      !
121      DO jn = 1, jptra
122         DO ib_bdy=1, nb_bdy
123            IF( trcdta_bdy(jn, ib_bdy)%dmp ) THEN
124               igrd = 1                       ! Everything is at T-points here
125               DO ib = 1, idx_bdy(ib_bdy)%nblen(igrd)
126                  ii = idx_bdy(ib_bdy)%nbi(ib,igrd)
127                  ij = idx_bdy(ib_bdy)%nbj(ib,igrd)
128                  zwgt = idx_bdy(ib_bdy)%nbd(ib,igrd)
129                  DO ik = 1, jpkm1
130                     zta = zwgt * ( trcdta_bdy(jn, ib_bdy)%trc(ib,ik) - trb(ii,ij,ik,jn) ) * tmask(ii,ij,ik)
131                     tra(ii,ij,ik,jn) = tra(ii,ij,ik,jn) + zta
132                  END DO
133               END DO
134            ENDIF
135         END DO
136      END DO
137      !
138      IF( ln_timing )   CALL timing_stop('trc_bdy_dmp')
139      !
140   END SUBROUTINE trc_bdy_dmp
141 
142#else
143   !!----------------------------------------------------------------------
144   !!   Dummy module                   NO Unstruct Open Boundary Conditions
145   !!----------------------------------------------------------------------
146CONTAINS
147   SUBROUTINE trc_bdy(kt)      ! Empty routine
148      WRITE(*,*) 'trc_bdy: You should not have seen this print! error?', kt
149   END SUBROUTINE trc_bdy
150
151   SUBROUTINE trc_bdy_dmp(kt)      ! Empty routine
152      WRITE(*,*) 'trc_bdy_dmp: You should not have seen this print! error?', kt
153   END SUBROUTINE trc_bdy_dmp
154
155#endif
156
157   !!======================================================================
158END MODULE trcbdy
Note: See TracBrowser for help on using the repository browser.