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.
bdytra.F90 in NEMO/trunk/src/OCE/BDY – NEMO

source: NEMO/trunk/src/OCE/BDY/bdytra.F90 @ 12560

Last change on this file since 12560 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: 9.2 KB
RevLine 
[911]1MODULE bdytra
[1125]2   !!======================================================================
[911]3   !!                       ***  MODULE  bdytra  ***
[3294]4   !! Ocean tracers:   Apply boundary conditions for tracers
[1125]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
[3294]8   !!            3.4  !  2011     (D. Storkey) rewrite in preparation for OBC-BDY merge
[3680]9   !!            3.5  !  2012     (S. Mocavero, I. Epicoco) Optimization of BDY communications
[7646]10   !!            4.0  !  2016     (T. Lovato) Generalize OBC structure
[1125]11   !!----------------------------------------------------------------------
[7646]12   !!   bdy_tra       : Apply open boundary conditions & damping to T and S
[1125]13   !!----------------------------------------------------------------------
[6140]14   USE oce            ! ocean dynamics and tracers variables
15   USE dom_oce        ! ocean space and time domain variables
16   USE bdy_oce        ! ocean open boundary conditions
17   USE bdylib         ! for orlanski library routines
18   !
19   USE in_out_manager ! I/O manager
20   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
[10529]21   USE lib_mpp, ONLY: ctl_stop
[6140]22   USE timing         ! Timing
[911]23
24   IMPLICIT NONE
25   PRIVATE
26
[7646]27   ! Local structure to rearrange tracers data
28   TYPE, PUBLIC ::   ztrabdy
29      REAL(wp), POINTER, DIMENSION(:,:) ::  tra
30   END TYPE
31
[6140]32   PUBLIC   bdy_tra      ! called in tranxt.F90
33   PUBLIC   bdy_tra_dmp  ! called in step.F90
[911]34
[1125]35   !!----------------------------------------------------------------------
[9598]36   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[1146]37   !! $Id$
[10068]38   !! Software governed by the CeCILL license (see ./LICENSE)
[1125]39   !!----------------------------------------------------------------------
[911]40CONTAINS
41
[12377]42   SUBROUTINE bdy_tra( kt, Kbb, pts, Kaa )
[1125]43      !!----------------------------------------------------------------------
[3294]44      !!                  ***  SUBROUTINE bdy_tra  ***
45      !!
46      !! ** Purpose : - Apply open boundary conditions for temperature and salinity
47      !!
48      !!----------------------------------------------------------------------
[12377]49      INTEGER                                  , INTENT(in)    :: kt        ! Main time step counter
50      INTEGER                                  , INTENT(in)    :: Kbb, Kaa  ! time level indices
51      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts,jpt), INTENT(inout) :: pts       ! tracer fields
[6140]52      !
[11536]53      INTEGER                        :: ib_bdy, jn, igrd, ir   ! Loop indeces
54      TYPE(ztrabdy), DIMENSION(jpts) :: zdta                   ! Temporary data structure
55      LOGICAL                        :: llrim0                 ! indicate if rim 0 is treated
56      LOGICAL, DIMENSION(4)          :: llsend1, llrecv1       ! indicate how communications are to be carried out
[6140]57      !!----------------------------------------------------------------------
[7646]58      igrd = 1 
[11536]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            !
66            zdta(1)%tra => dta_bdy(ib_bdy)%tem
67            zdta(2)%tra => dta_bdy(ib_bdy)%sal
68            !
69            DO jn = 1, jpts
70               !
71               SELECT CASE( TRIM(cn_tra(ib_bdy)) )
72               CASE('none'        )   ;   CYCLE
73               CASE('frs'         )   ! treat the whole boundary at once
[12377]74                  IF( ir == 0 ) CALL bdy_frs ( idx_bdy(ib_bdy),                pts(:,:,:,jn,Kaa), zdta(jn)%tra )
[11536]75               CASE('specified'   )   ! treat the whole rim      at once
[12377]76                  IF( ir == 0 ) CALL bdy_spe ( idx_bdy(ib_bdy),                pts(:,:,:,jn,Kaa), zdta(jn)%tra )
77               CASE('neumann'     )   ;   CALL bdy_nmn ( idx_bdy(ib_bdy), igrd         , pts(:,:,:,jn,Kaa), llrim0 )   ! tsa masked
78               CASE('orlanski'    )   ;   CALL bdy_orl ( idx_bdy(ib_bdy), pts(:,:,:,jn,Kbb), pts(:,:,:,jn,Kaa), &
[11536]79                    & zdta(jn)%tra, llrim0, ll_npo=.false. )
[12377]80               CASE('orlanski_npo')   ;   CALL bdy_orl ( idx_bdy(ib_bdy), pts(:,:,:,jn,Kbb), pts(:,:,:,jn,Kaa), &
[11536]81                    & zdta(jn)%tra, llrim0, ll_npo=.true.  )
[12377]82               CASE('runoff'      )   ;   CALL bdy_rnf ( idx_bdy(ib_bdy),                pts(:,:,:,jn,Kaa), jn, llrim0 )
[11536]83               CASE DEFAULT           ;   CALL ctl_stop( 'bdy_tra : unrecognised option for open boundaries for T and S' )
84               END SELECT
85               !
86            END DO
87         END DO
[6140]88         !
[11536]89         IF( nn_hls > 1 .AND. ir == 1 ) CYCLE   ! at least 2 halos will be corrected -> no need to correct rim 1 before rim 0
90         IF( nn_hls == 1 ) THEN   ;   llsend1(:) = .false.   ;   llrecv1(:) = .false.   ;   END IF
91         DO ib_bdy=1, nb_bdy
[7646]92            SELECT CASE( TRIM(cn_tra(ib_bdy)) )
[11536]93            CASE('neumann','runoff')
94               llsend1(:) = llsend1(:) .OR. lsend_bdyint(ib_bdy,1,:,ir)   ! possibly every direction, T points
95               llrecv1(:) = llrecv1(:) .OR. lrecv_bdyint(ib_bdy,1,:,ir)   ! possibly every direction, T points
96            CASE('orlanski', 'orlanski_npo')
97               llsend1(:) = llsend1(:) .OR. lsend_bdy(ib_bdy,1,:,ir)   ! possibly every direction, T points
98               llrecv1(:) = llrecv1(:) .OR. lrecv_bdy(ib_bdy,1,:,ir)   ! possibly every direction, T points
[7646]99            END SELECT
100         END DO
[11536]101         IF( ANY(llsend1) .OR. ANY(llrecv1) ) THEN   ! if need to send/recv in at least one direction
[12377]102            CALL lbc_lnk( 'bdytra', pts(:,:,:,jn,Kaa), 'T',  1., kfillmode=jpfillnothing ,lsend=llsend1, lrecv=llrecv1 )
[11536]103         END IF
104         !
105      END DO   ! ir
[3651]106      !
[3294]107   END SUBROUTINE bdy_tra
108
[9124]109
[12377]110   SUBROUTINE bdy_rnf( idx, pt, jpa, llrim0 )
[3294]111      !!----------------------------------------------------------------------
[7646]112      !!                 ***  SUBROUTINE bdy_rnf  ***
[911]113      !!                   
[7646]114      !! ** Purpose : Specialized routine to apply TRA runoff values at OBs:
115      !!                  - duplicate the neighbour value for the temperature
[3651]116      !!                  - specified to 0.1 PSU for the salinity
117      !!
118      !!----------------------------------------------------------------------
[11536]119      TYPE(OBC_INDEX),                     INTENT(in) ::   idx      ! OBC indices
[12377]120      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pt       ! tracer trend
[11536]121      INTEGER,                             INTENT(in) ::   jpa      ! TRA index
122      LOGICAL,                             INTENT(in) ::   llrim0   ! indicate if rim 0 is treated
[6140]123      !
[11536]124      INTEGER  ::   ib, ii, ij, igrd   ! dummy loop indices
[3651]125      !!----------------------------------------------------------------------
126      !
127      igrd = 1                       ! Everything is at T-points here
[11536]128      IF(      jpa == jp_tem ) THEN
[12377]129         CALL bdy_nmn( idx, igrd, pt, llrim0 )
[11536]130      ELSE IF( jpa == jp_sal ) THEN
131         IF( .NOT. llrim0 )   RETURN
132         DO ib = 1, idx%nblenrim(igrd)   ! if llrim0 then treat the whole rim
133            ii = idx%nbi(ib,igrd)
134            ij = idx%nbj(ib,igrd)
[12377]135            pt(ii,ij,1:jpkm1) = 0.1 * tmask(ii,ij,1:jpkm1)
[3651]136         END DO
[11536]137      END IF
[3651]138      !
[7646]139   END SUBROUTINE bdy_rnf
[3651]140
[9124]141
[12377]142   SUBROUTINE bdy_tra_dmp( kt, Kbb, pts, Krhs )
[3651]143      !!----------------------------------------------------------------------
144      !!                 ***  SUBROUTINE bdy_tra_dmp  ***
145      !!                   
146      !! ** Purpose : Apply damping for tracers at open boundaries.
147      !!
148      !!----------------------------------------------------------------------
[12377]149      INTEGER                                  , INTENT(in)    :: kt        ! time step
150      INTEGER                                  , INTENT(in)    :: Kbb, Krhs ! time level indices
151      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts,jpt), INTENT(inout) :: pts       ! active tracers and RHS of tracer equation
[6140]152      !
[3651]153      REAL(wp) ::   zwgt           ! boundary weight
154      REAL(wp) ::   zta, zsa, ztime
155      INTEGER  ::   ib, ik, igrd   ! dummy loop indices
156      INTEGER  ::   ii, ij         ! 2D addresses
157      INTEGER  ::   ib_bdy         ! Loop index
158      !!----------------------------------------------------------------------
159      !
[9124]160      IF( ln_timing )   CALL timing_start('bdy_tra_dmp')
[3651]161      !
[6140]162      DO ib_bdy = 1, nb_bdy
163         IF( ln_tra_dmp(ib_bdy) ) THEN
[3651]164            igrd = 1                       ! Everything is at T-points here
165            DO ib = 1, idx_bdy(ib_bdy)%nblen(igrd)
166               ii = idx_bdy(ib_bdy)%nbi(ib,igrd)
167               ij = idx_bdy(ib_bdy)%nbj(ib,igrd)
168               zwgt = idx_bdy(ib_bdy)%nbd(ib,igrd)
169               DO ik = 1, jpkm1
[12377]170                  zta = zwgt * ( dta_bdy(ib_bdy)%tem(ib,ik) - pts(ii,ij,ik,jp_tem,Kbb) ) * tmask(ii,ij,ik)
171                  zsa = zwgt * ( dta_bdy(ib_bdy)%sal(ib,ik) - pts(ii,ij,ik,jp_sal,Kbb) ) * tmask(ii,ij,ik)
172                  pts(ii,ij,ik,jp_tem,Krhs) = pts(ii,ij,ik,jp_tem,Krhs) + zta
173                  pts(ii,ij,ik,jp_sal,Krhs) = pts(ii,ij,ik,jp_sal,Krhs) + zsa
[3651]174               END DO
175            END DO
176         ENDIF
[6140]177      END DO
[3651]178      !
[9124]179      IF( ln_timing )   CALL timing_stop('bdy_tra_dmp')
[3651]180      !
181   END SUBROUTINE bdy_tra_dmp
182 
[1125]183   !!======================================================================
[911]184END MODULE bdytra
Note: See TracBrowser for help on using the repository browser.