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 trunk/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: trunk/NEMOGCM/NEMO/OPA_SRC/BDY/bdytra.F90 @ 3294

Last change on this file since 3294 was 3294, checked in by rblod, 12 years ago

Merge of 3.4beta into the trunk

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