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 branches/2011/UKMO_MERCATOR_obc_bdy_merge/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: branches/2011/UKMO_MERCATOR_obc_bdy_merge/NEMOGCM/NEMO/OPA_SRC/BDY/bdytra.F90 @ 2888

Last change on this file since 2888 was 2888, checked in by davestorkey, 13 years ago

Move changes into updated BDY module and restore old OBC code.
(Full merge to take place next year).

File size: 4.5 KB
Line 
1MODULE bdytra
2   !!======================================================================
3   !!                       ***  MODULE  bdytra  ***
4   !! Ocean tracers:   Flow Relaxation Scheme of tracers on each open boundary
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   !!----------------------------------------------------------------------
9#if defined key_bdy
10   !!----------------------------------------------------------------------
11   !!   'key_bdy'                     Unstructured Open Boundary Conditions
12   !!----------------------------------------------------------------------
13   !!   bdy_tra            : Apply open boundary conditions to T and S
14   !!   bdy_tra_frs        : Apply Flow Relaxation Scheme
15   !!----------------------------------------------------------------------
16   USE oce             ! ocean dynamics and tracers variables
17   USE dom_oce         ! ocean space and time domain variables
18   USE bdy_oce         ! ocean open boundary conditions
19   USE bdydta, ONLY:   bf
20   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
21   USE in_out_manager  ! I/O manager
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC bdy_tra      ! routine called in tranxt.F90
27
28   !!----------------------------------------------------------------------
29   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
30   !! $Id: bdytra.F90 2528 2010-12-27 17:33:53Z rblod $
31   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
32   !!----------------------------------------------------------------------
33CONTAINS
34
35   SUBROUTINE bdy_tra( kt )
36      !!----------------------------------------------------------------------
37      !!                  ***  SUBROUTINE bdy_dyn3d  ***
38      !!
39      !! ** Purpose : - Apply open boundary conditions for baroclinic velocities
40      !!
41      !!----------------------------------------------------------------------
42      INTEGER, INTENT( in ) :: kt     ! Main time step counter
43      !!
44      INTEGER               :: ib_bdy ! Loop index
45
46      DO ib_bdy=1, nb_bdy
47
48         SELECT CASE( nn_tra(ib_bdy) )
49         CASE(jp_none)
50            CYCLE
51         CASE(jp_frs)
52            CALL bdy_tra_frs( idx_bdy(ib_bdy), dta_bdy(ib_bdy), kt )
53         CASE DEFAULT
54            CALL ctl_stop( 'bdy_tra : unrecognised option for open boundaries for T and S' )
55         END SELECT
56      ENDDO
57
58   END SUBROUTINE bdy_tra
59
60   SUBROUTINE bdy_tra_frs( idx, dta, kt )
61      !!----------------------------------------------------------------------
62      !!                 ***  SUBROUTINE bdy_tra_frs  ***
63      !!                   
64      !! ** Purpose : Apply the Flow Relaxation Scheme for tracers at open boundaries.
65      !!
66      !! Reference : Engedahl H., 1995, Tellus, 365-382.
67      !!----------------------------------------------------------------------
68      INTEGER,         INTENT(in) ::   kt
69      TYPE(OBC_INDEX), INTENT(in) ::   idx  ! OBC indices
70      TYPE(OBC_DATA),  INTENT(in) ::   dta  ! OBC external data
71      !!
72      REAL(wp) ::   zwgt           ! boundary weight
73      INTEGER  ::   ib, ik, igrd   ! dummy loop indices
74      INTEGER  ::   ii, ij         ! 2D addresses
75      !!----------------------------------------------------------------------
76      !
77      !
78      igrd = 1                       ! Everything is at T-points here
79      DO ib = 1, idx%nblen(igrd)
80         DO ik = 1, jpkm1
81            ii = idx%nbi(ib,igrd)
82            ij = idx%nbj(ib,igrd)
83            zwgt = idx%nbw(ib,igrd)
84            ta(ii,ij,ik) = ( ta(ii,ij,ik) + zwgt * ( dta%tem(ib,ik) - ta(ii,ij,ik) ) ) * tmask(ii,ij,ik)         
85            sa(ii,ij,ik) = ( sa(ii,ij,ik) + zwgt * ( dta%sal(ib,ik) - sa(ii,ij,ik) ) ) * tmask(ii,ij,ik)
86         END DO
87      END DO 
88      !
89      CALL lbc_lnk( ta, 'T', 1. )   ; CALL lbc_lnk( sa, 'T', 1. )    ! Boundary points should be updated
90      !
91      IF( kt .eq. nit000 ) CLOSE( unit = 102 )
92   !
93   END SUBROUTINE bdy_tra_frs
94   
95#else
96   !!----------------------------------------------------------------------
97   !!   Dummy module                   NO Unstruct Open Boundary Conditions
98   !!----------------------------------------------------------------------
99CONTAINS
100   SUBROUTINE bdy_tra(kt)      ! Empty routine
101      WRITE(*,*) 'bdy_tra: You should not have seen this print! error?', kt
102   END SUBROUTINE bdy_tra
103#endif
104
105   !!======================================================================
106END MODULE bdytra
Note: See TracBrowser for help on using the repository browser.