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

source: branches/2011/dev_NEMO_MERGE_2011/NEMOGCM/NEMO/OPA_SRC/BDY/bdytra.F90 @ 3186

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

Change dynamic allocation and add timing to BDY module.

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