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.
obccli.F90 in trunk/NEMO/OPA_SRC/OBC – NEMO

source: trunk/NEMO/OPA_SRC/OBC/obccli.F90 @ 719

Last change on this file since 719 was 719, checked in by ctlod, 17 years ago

get back to the nemo_v2_3 version for trunk

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 9.3 KB
Line 
1MODULE obccli
2   !!======================================================================
3   !!                       ***  MODULE  obccli  ***
4   !! Ocean dynamics:   Baroclinic velocities on each open boundary
5   !!======================================================================
6   !! History :
7   !!   8.5  !  02-10 (C. Talandier, A-M. Treguier) Free surface, F90
8   !!   9.0  !  06-04 (R.Benshila, G. Madec)  zco, zps, sco coordinate
9   !!----------------------------------------------------------------------
10#if defined key_obc && defined key_dynspg_rl
11   !!----------------------------------------------------------------------
12   !!   'key_obc' and 'key_dynspg_rl' open boundary condition and rigid-lid
13   !!----------------------------------------------------------------------
14   !!   obc_cli_dyn : baroclinic componant after the radiation phase
15   !!   obc_cli_dta : baroclinic componant for the climatological velocities
16   !!----------------------------------------------------------------------
17   !! * Modules used
18   USE oce             ! ocean dynamics and tracers   
19   USE dom_oce         ! ocean space and time domain
20   USE phycst          ! physical constants
21   USE obc_oce         ! ocean open boundary conditions
22
23   IMPLICIT NONE
24   PRIVATE
25
26   !! * Accessibility
27   PUBLIC obc_cli    ! routine called in obcdyn.F90 and obcdta.F90 (rigid lid case)
28
29   INTERFACE obc_cli
30     MODULE PROCEDURE obc_cli_dyn, obc_cli_dta
31   END INTERFACE
32
33   !! * Substitutions
34#  include "domzgr_substitute.h90"
35   !!----------------------------------------------------------------------
36   !!   OPA 9.0 , LOCEAN-IPSL (2005)
37   !! $Header$
38   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
39   !!----------------------------------------------------------------------
40
41CONTAINS
42
43   SUBROUTINE obc_cli_dyn( obvel, velcli, obd, obf, obtyp, obl)
44      !!----------------------------------------------------------------------
45      !!                 ***  SUBROUTINE obc_cli_dyn  ***
46      !!                   
47      !! ** Purpose :   Compute the baroclinic velocities at the open boundaries.
48      !!
49      !! ** Method  :
50      !!      - Compute de barotropic velocity along the considered Open Boundary
51      !!        and substract it to the total velocity to have baroclinic velotity.
52      !!      - obtyp must be set to | 0 when traiting an East or West OB
53      !!                             | 1 when traiting a North or South OB.
54      !!      - obl is the lenght of the OB (jpi or jpj)
55      !!
56      !!-----------------------------------------------------------------------
57      !! * Arguments
58      INTEGER, INTENT( in ) ::   & ! OB localization:jpieob or jpiwob for East or West
59         obd, obf,               & !                 jpjnob or jpjsob for North or South
60         obl,                    & ! Lenght of the Open Boundary
61         obtyp                     ! Type of Open Boundary: zonal or Meridional
62      REAL(wp), DIMENSION(:,:), INTENT( out) ::   &
63         velcli                    ! Baroclinic velocity calculated
64      REAL(wp), DIMENSION(:,:,:), INTENT( in ) ::   &
65         obvel                     ! ua or va velocities from obcdyn.F90 routine
66
67      !! * Local declarations
68      INTEGER ::   &   
69         ji, jj, jk, jle, jol         ! loop indices 
70      REAL(wp) ::   zcbl              ! Temporary Baroclinic velocity
71      REAL(wp), DIMENSION(obl) ::   & 
72         zvelbtpe,                  & ! Barotropic velocity
73         zhinv                        ! Invert of the local depth 1/H
74      REAL(wp), DIMENSION(obl,jpk) ::   &
75         zmskob,                    & ! Velocity mask
76         zvel                         ! 2D Local velocity on OB
77      REAL(wp), DIMENSION(obl,jpk) ::   &
78         ze3ob                        ! Vertical scale factor
79      !!--------------------------------------------------------------------------------
80
81      ! 0. Array initialization
82      ! -----------------------
83
84      zhinv (:)   = 0.e0
85      zmskob(:,:) = 0.e0
86      zvel  (:,:) = 0.e0
87      ze3ob (:,:) = 0.e0
88
89      IF( obtyp == 0 ) THEN            ! Meridional Open Boundary ( East or West OB )
90         DO ji = obd, obf
91            zhinv (:)   = hur  (ji,:)
92            zmskob(:,:) = umask(ji,:,:)
93            zvel  (:,:) = obvel(ji,:,:)
94            ze3ob (:,:) = fse3u(ji,:,:)
95         END DO
96      ELSE                             ! Zonal Open Boundary ( North or South OB )
97         DO jj = obd, obf
98            zhinv (:)   = hvr  (:,jj)
99            zmskob(:,:) = vmask(:,jj,:)
100            zvel  (:,:) = obvel(:,jj,:)
101            ze3ob (:,:) = fse3v(:,jj,:)
102         END DO
103      END IF
104
105
106      ! 1. vertical sum
107      ! ----------------
108      zvelbtpe(1) = 0.e0
109!CDIR NOLOOPCHG
110      DO jk = 1, jpkm1
111         DO jle = 1, obl
112            zvelbtpe(jle) = zvelbtpe(jle) + zvel(jle,jk) * zmskob(jle,jk) * ze3ob(jle,jk)
113         END DO
114      END DO
115
116      ! 2. divide by the depth
117      ! -----------------------
118      zvelbtpe(:) = zvelbtpe(:) * zhinv(:) * zmskob(:,1) 
119
120      ! 3. substract zvelbtpe to the total velocity
121      !    and save the baroclinic velocity in velcli()
122      ! ------------------------------------------------
123      DO jk = 1, jpkm1
124         velcli(:,jk) = ( zvel(:,jk) - zvelbtpe(:) ) * zmskob(:,jk)
125      END DO
126
127   END SUBROUTINE obc_cli_dyn
128
129
130   SUBROUTINE obc_cli_dta( obvel, velcli, obd, obf, obtyp, obl, mpp )
131      !!--------------------------------------------------------------------------------
132      !!                 ***  SUBROUTINE obc_cli_dta  ***
133      !!                   
134      !! ** Purpose :
135      !!      Compute the baroclinic velocities for the climatological velocities.
136      !!
137      !! ** Method  :
138      !!      - Compute de barotropic velocity along the considered Open Boundary
139      !!        and substract it to the total velocity to have baroclinic velotity.
140      !!      - obtyp must be set to | 0 when traiting an East or West OB
141      !!                             | 1 when traiting a North or South OB.
142      !!      - obl is the lenght of the OB (jpi or jpj)
143      !!
144      !!--------------------------------------------------------------------------------
145      !! * Arguments
146      INTEGER, INTENT( in ) ::   & ! OB localization: jpieob or jpiwob for East or West
147         obd, obf,               & !                  jpjnob or jpjsob for North or South
148         obl,                    & ! Lenght of the Open Boundary
149         mpp,                    & ! MPP index
150         obtyp                     ! Type of Open Boundary: zonal or Meridional
151      REAL(wp), INTENT( out), DIMENSION(:,:) ::   &
152         velcli                    ! Baroclinic velocity calculated
153      REAL(wp), INTENT( inout ), DIMENSION(:,:,:) ::   &
154         obvel                     ! uXdta or vXdta climatological velocities from
155                                   ! obcdta.F90 routine
156
157      !! * Local declarations
158      INTEGER ::   &
159         ji, jj, jk, jle, jol, ij     ! loop indices 
160      REAL(wp), DIMENSION(obl) ::   & 
161         zvelbtpe,                  & ! Barotropic velocity
162         zhinv                        ! Invert of the local depth 1/H
163      REAL(wp), DIMENSION(obl,jpk) ::   &
164         zmskob                       ! Velocity mask
165      REAL(wp), DIMENSION(obl,jpk) ::   &
166         ze3ob                        ! Vertical scale factor
167      !!--------------------------------------------------------------------------------
168
169      ! 0. Array initialization
170      ! -----------------------
171
172      zhinv (:)   = 0.e0
173      zmskob(:,:) = 0.e0
174      ze3ob (:,:) = 0.e0
175
176      IF( obtyp == 0 ) THEN            ! Meridional Open Boundary ( East or West OB )
177         DO ji = obd, obf
178            zhinv (:)   = hur  (ji,:)
179            zmskob(:,:) = umask(ji,:,:)
180            ze3ob (:,:) = fse3u(ji,:,:)
181         END DO
182      ELSE                             ! Zonal Open Boundary ( North or South OB )
183         DO jj = obd, obf
184            zhinv (:)   = hvr  (:,jj)
185            zmskob(:,:) = vmask(:,jj,:)
186            ze3ob (:,:) = fse3v(:,jj,:)
187         END DO
188      END IF
189
190      ! 1. vertical sum
191      ! ----------------
192      zvelbtpe(1) = 0.e0
193!CDIR NOLOOPCHG
194      DO jk = 1, jpkm1
195         DO jle = 1, obl
196            ij = jle -1 + mpp
197            zvelbtpe(jle) = zvelbtpe(jle) + obvel(ij,jk,1)*zmskob(jle,jk) * ze3ob(jle,jk)
198         END DO
199      END DO
200
201      ! 2. divide by the depth
202      ! -----------------------
203         zvelbtpe(:) = zvelbtpe(:) * zhinv(:) * zmskob(:,1) 
204
205      ! 3. substract zvelbtpe to the total velocity
206      !    and save the baroclinic velocity in velcli()
207      ! ------------------------------------------------
208      DO jk = 1, jpkm1
209         DO jle = 1, obl
210            ij = jle -1 + mpp
211            obvel(ij,jk,1) = obvel(ij,jk,1) - zvelbtpe(jle)*zmskob(jle,jk)
212            velcli(jle,jk) = obvel(ij,jk,1) * zmskob(jle,jk)
213         END DO
214      END DO
215
216   END SUBROUTINE obc_cli_dta
217
218#else
219   !!----------------------------------------------------------------------------------
220   !!   Default options :                                                  Empty module
221   !!----------------------------------------------------------------------------------
222CONTAINS
223   SUBROUTINE obc_cli_dyn       ! Empty routine
224   END SUBROUTINE obc_cli_dyn
225   SUBROUTINE obc_cli_dta       ! Empty routine
226   END SUBROUTINE obc_cli_dta
227#endif
228
229   !!==================================================================================
230END MODULE obccli
Note: See TracBrowser for help on using the repository browser.