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.
lbclnk.F90 in branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/LBC – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/LBC/lbclnk.F90 @ 3432

Last change on this file since 3432 was 3432, checked in by trackstand2, 12 years ago

Merge branch 'ksection_partition'

  • Property svn:keywords set to Id
File size: 13.3 KB
Line 
1MODULE lbclnk
2   !!======================================================================
3   !!                       ***  MODULE  lbclnk  ***
4   !! Ocean        : lateral boundary conditions
5   !!=====================================================================
6   !! History :  OPA  ! 1997-06  (G. Madec)     Original code
7   !!   NEMO     1.0  ! 2002-09  (G. Madec)     F90: Free form and module
8   !!            3.2  ! 2009-03  (R. Benshila)  External north fold treatment 
9   !!----------------------------------------------------------------------
10#if   defined key_mpp_mpi
11   !!----------------------------------------------------------------------
12   !!   'key_mpp_mpi'             MPI massively parallel processing library
13   !!----------------------------------------------------------------------
14   !!   lbc_lnk      : generic interface for mpp_lnk_3d and mpp_lnk_2d routines defined in lib_mpp
15   !!   lbc_lnk_e    : generic interface for mpp_lnk_2d_e routine defined in lib_mpp
16   !!----------------------------------------------------------------------
17   USE lib_mpp          ! distributed memory computing library
18   USE exchmod          ! Comms for irregular domain decomposition
19
20   INTERFACE lbc_lnk
21#if  defined key_mpp_rkpart
22      MODULE PROCEDURE lbc_exch2, lbc_exch3 !, lbc_exch2i, lbc_exch3i
23#else
24      MODULE PROCEDURE mpp_lnk_3d_gather, mpp_lnk_3d, mpp_lnk_2d
25#endif
26   END INTERFACE
27
28   INTERFACE lbc_lnk_e
29      MODULE PROCEDURE mpp_lnk_2d_e
30   END INTERFACE
31
32   PUBLIC lbc_lnk       ! ocean lateral boundary conditions
33   PUBLIC lbc_lnk_e
34
35   !!----------------------------------------------------------------------
36   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
37   !! $Id$
38   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
39   !!----------------------------------------------------------------------
40
41#else
42   !!----------------------------------------------------------------------
43   !!   Default option                              shared memory computing
44   !!----------------------------------------------------------------------
45   !!   lbc_lnk      : generic interface for lbc_lnk_3d and lbc_lnk_2d
46   !!   lbc_lnk_3d   : set the lateral boundary condition on a 3D variable on ocean mesh
47   !!   lbc_lnk_2d   : set the lateral boundary condition on a 2D variable on ocean mesh
48   !!----------------------------------------------------------------------
49   USE oce             ! ocean dynamics and tracers   
50   USE dom_oce         ! ocean space and time domain
51   USE in_out_manager  ! I/O manager
52   USE lbcnfd          ! north fold
53
54   IMPLICIT NONE
55   PRIVATE
56
57   INTERFACE lbc_lnk
58      MODULE PROCEDURE lbc_lnk_3d_gather, lbc_lnk_3d, lbc_lnk_2d
59   END INTERFACE
60
61   INTERFACE lbc_lnk_e
62      MODULE PROCEDURE lbc_lnk_2d
63   END INTERFACE
64
65   PUBLIC   lbc_lnk       ! ocean/ice  lateral boundary conditions
66   PUBLIC   lbc_lnk_e 
67
68   !! * Control permutation of array indices
69#  include "oce_ftrans.h90"
70#  include "dom_oce_ftrans.h90"
71
72   !!----------------------------------------------------------------------
73   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
74   !! $Id$
75   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
76   !!----------------------------------------------------------------------
77CONTAINS
78
79   SUBROUTINE lbc_lnk_3d_gather( pt3d1, cd_type1, pt3d2, cd_type2, psgn )
80      !!---------------------------------------------------------------------
81      !!                  ***  ROUTINE lbc_lnk_3d_gather  ***
82      !!
83      !! ** Purpose :   set lateral boundary conditions on two 3D arrays (non mpp case)
84      !!
85      !! ** Method  :   psign = -1 :    change the sign across the north fold
86      !!                      =  1 : no change of the sign across the north fold
87      !!                      =  0 : no change of the sign across the north fold and
88      !!                             strict positivity preserved: use inner row/column
89      !!                             for closed boundaries.
90      !!----------------------------------------------------------------------
91      CHARACTER(len=1)                , INTENT(in   ) ::   cd_type1, cd_type2   ! nature of pt3d grid-points
92!FTRANS pt3d1 :I :I :z
93!FTRANS pt3d2 :I :I :z
94! DCSE_NEMO: work around a deficiency in ftrans
95!     REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pt3d1   , pt3d2      ! 3D array on which the lbc is applied
96      REAL(wp), INTENT(inout)   ::   pt3d1(jpi,jpj,jpk)   , pt3d2(jpi,jpj,jpk)
97      REAL(wp), INTENT(in   )   ::   psgn                 ! control of the sign
98      !!----------------------------------------------------------------------
99      !
100      CALL lbc_lnk_3d( pt3d1, cd_type1, psgn)
101      CALL lbc_lnk_3d( pt3d2, cd_type2, psgn)
102      !
103   END SUBROUTINE lbc_lnk_3d_gather
104
105
106   SUBROUTINE lbc_lnk_3d( pt3d, cd_type, psgn, cd_mpp, pval )
107      !!---------------------------------------------------------------------
108      !!                  ***  ROUTINE lbc_lnk_3d  ***
109      !!
110      !! ** Purpose :   set lateral boundary conditions on a 3D array (non mpp case)
111      !!
112      !! ** Method  :   psign = -1 :    change the sign across the north fold
113      !!                      =  1 : no change of the sign across the north fold
114      !!                      =  0 : no change of the sign across the north fold and
115      !!                             strict positivity preserved: use inner row/column
116      !!                             for closed boundaries.
117      !!----------------------------------------------------------------------
118      CHARACTER(len=1)                , INTENT(in   )           ::   cd_type   ! nature of pt3d grid-points
119!FTRANS pt3d :I :I :z
120!! DCSE_NEMO: work around a deficiency in ftrans
121!     REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout)           ::   pt3d      ! 3D array on which the lbc is applied
122      REAL(wp), INTENT(inout)                                   ::   pt3d(jpi,jpj,jpk)
123      REAL(wp)                        , INTENT(in   )           ::   psgn      ! control of the sign
124      CHARACTER(len=3)                , INTENT(in   ), OPTIONAL ::   cd_mpp    ! MPP only (here do nothing)
125      REAL(wp)                        , INTENT(in   ), OPTIONAL ::   pval      ! background value (for closed boundaries)
126      !!
127      REAL(wp) ::   zland
128      !!----------------------------------------------------------------------
129
130      IF( PRESENT( pval ) ) THEN   ;   zland = pval      ! set land value (zero by default)
131      ELSE                         ;   zland = 0.e0
132      ENDIF
133
134
135      IF( PRESENT( cd_mpp ) ) THEN
136         ! only fill the overlap area and extra allows
137         ! this is in mpp case. In this module, just do nothing
138      ELSE
139         !
140         !                                     !  East-West boundaries
141         !                                     ! ======================
142         SELECT CASE ( nperio )
143         !
144         CASE ( 1 , 4 , 6 )                       !**  cyclic east-west
145            pt3d( 1 ,:,:) = pt3d(jpim1,:,:)            ! all points
146            pt3d(jpi,:,:) = pt3d(  2  ,:,:)
147            !
148         CASE DEFAULT                             !**  East closed  --  West closed
149            SELECT CASE ( cd_type )
150            CASE ( 'T' , 'U' , 'V' , 'W' )             ! T-, U-, V-, W-points
151               pt3d( 1 ,:,:) = zland
152               pt3d(jpi,:,:) = zland
153            CASE ( 'F' )                               ! F-point
154               pt3d(jpi,:,:) = zland
155            END SELECT
156            !
157         END SELECT
158         !
159         !                                     ! North-South boundaries
160         !                                     ! ======================
161         SELECT CASE ( nperio )
162         !
163         CASE ( 2 )                               !**  South symmetric  --  North closed
164            SELECT CASE ( cd_type )
165            CASE ( 'T' , 'U' , 'W' )                   ! T-, U-, W-points
166               pt3d(:, 1 ,:) = pt3d(:,3,:)
167               pt3d(:,jpj,:) = zland
168            CASE ( 'V' , 'F' )                         ! V-, F-points
169               pt3d(:, 1 ,:) = psgn * pt3d(:,2,:)
170               pt3d(:,jpj,:) = zland
171            END SELECT
172            !
173         CASE ( 3 , 4 , 5 , 6 )                   !**  North fold  T or F-point pivot  --  South closed
174            SELECT CASE ( cd_type )                    ! South : closed
175            CASE ( 'T' , 'U' , 'V' , 'W' , 'I' )             ! all points except F-point
176               pt3d(:, 1 ,:) = zland
177            END SELECT
178            !                                          ! North fold
179            pt3d( 1 ,jpj,:) = zland
180            pt3d(jpi,jpj,:) = zland
181            CALL lbc_nfd( pt3d(:,:,:), cd_type, psgn )
182            !
183         CASE DEFAULT                             !**  North closed  --  South closed
184            SELECT CASE ( cd_type )
185            CASE ( 'T' , 'U' , 'V' , 'W' )             ! T-, U-, V-, W-points
186               pt3d(:, 1 ,:) = zland
187               pt3d(:,jpj,:) = zland
188            CASE ( 'F' )                               ! F-point
189               pt3d(:,jpj,:) = zland
190            END SELECT
191            !
192         END SELECT
193         !
194      ENDIF
195      !
196   END SUBROUTINE lbc_lnk_3d
197
198
199   SUBROUTINE lbc_lnk_2d( pt2d, cd_type, psgn, cd_mpp, pval )
200      !!---------------------------------------------------------------------
201      !!                 ***  ROUTINE lbc_lnk_2d  ***
202      !!
203      !! ** Purpose :   set lateral boundary conditions on a 2D array (non mpp case)
204      !!
205      !! ** Method  :   psign = -1 :    change the sign across the north fold
206      !!                      =  1 : no change of the sign across the north fold
207      !!                      =  0 : no change of the sign across the north fold and
208      !!                             strict positivity preserved: use inner row/column
209      !!                             for closed boundaries.
210      !!----------------------------------------------------------------------
211      CHARACTER(len=1)            , INTENT(in   )           ::   cd_type   ! nature of pt3d grid-points
212      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout)           ::   pt2d      ! 2D array on which the lbc is applied
213      REAL(wp)                    , INTENT(in   )           ::   psgn      ! control of the sign
214      CHARACTER(len=3)            , INTENT(in   ), OPTIONAL ::   cd_mpp    ! MPP only (here do nothing)
215      REAL(wp)                    , INTENT(in   ), OPTIONAL ::   pval      ! background value (for closed boundaries)
216      !!
217      REAL(wp) ::   zland
218      !!----------------------------------------------------------------------
219
220      IF( PRESENT( pval ) ) THEN   ;   zland = pval      ! set land value (zero by default)
221      ELSE                         ;   zland = 0.e0
222      ENDIF
223
224      IF (PRESENT(cd_mpp)) THEN
225         ! only fill the overlap area and extra allows
226         ! this is in mpp case. In this module, just do nothing
227      ELSE     
228         !
229         !                                     ! East-West boundaries
230         !                                     ! ====================
231         SELECT CASE ( nperio )
232         !
233         CASE ( 1 , 4 , 6 )                       !** cyclic east-west
234            pt2d( 1 ,:) = pt2d(jpim1,:)               ! all points
235            pt2d(jpi,:) = pt2d(  2  ,:)
236            !
237         CASE DEFAULT                             !** East closed  --  West closed
238            SELECT CASE ( cd_type )
239            CASE ( 'T' , 'U' , 'V' , 'W' )            ! T-, U-, V-, W-points
240               pt2d( 1 ,:) = zland
241               pt2d(jpi,:) = zland
242            CASE ( 'F' )                              ! F-point
243               pt2d(jpi,:) = zland
244            END SELECT
245            !
246         END SELECT
247         !
248         !                                     ! North-South boundaries
249         !                                     ! ======================
250         SELECT CASE ( nperio )
251         !
252         CASE ( 2 )                               !**  South symmetric  --  North closed
253            SELECT CASE ( cd_type )
254            CASE ( 'T' , 'U' , 'W' )                   ! T-, U-, W-points
255               pt2d(:, 1 ) = pt2d(:,3)
256               pt2d(:,jpj) = zland
257            CASE ( 'V' , 'F' )                         ! V-, F-points
258               pt2d(:, 1 ) = psgn * pt2d(:,2)
259               pt2d(:,jpj) = zland
260            END SELECT
261            !
262         CASE ( 3 , 4 , 5 , 6 )                   !**  North fold  T or F-point pivot  --  South closed
263            SELECT CASE ( cd_type )                    ! South : closed
264            CASE ( 'T' , 'U' , 'V' , 'W' , 'I' )             ! all points except F-point
265               pt2d(:, 1 ) = zland
266            END SELECT
267            !                                          ! North fold
268            pt2d( 1 ,1  ) = zland 
269            pt2d( 1 ,jpj) = zland 
270            pt2d(jpi,jpj) = zland
271            CALL lbc_nfd( pt2d(:,:), cd_type, psgn )
272            !
273         CASE DEFAULT                             !**  North closed  --  South closed
274            SELECT CASE ( cd_type )
275            CASE ( 'T' , 'U' , 'V' , 'W' )             ! T-, U-, V-, W-points
276               pt2d(:, 1 ) = zland
277               pt2d(:,jpj) = zland
278            CASE ( 'F' )                               ! F-point
279               pt2d(:,jpj) = zland
280            END SELECT
281            !
282         END SELECT
283         !
284      ENDIF
285      !   
286   END SUBROUTINE lbc_lnk_2d
287
288#endif
289
290   !!======================================================================
291END MODULE lbclnk
Note: See TracBrowser for help on using the repository browser.