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_tam.F90 in branches/TAM_V3_2_2/NEMOTAM/OPATAM_SRC – NEMO

source: branches/TAM_V3_2_2/NEMOTAM/OPATAM_SRC/lbclnk_tam.F90 @ 3317

Last change on this file since 3317 was 2578, checked in by rblod, 13 years ago

first import of NEMOTAM 3.2.2

File size: 12.1 KB
Line 
1MODULE lbclnk_tam
2   !!======================================================================
3   !!                       ***  MODULE  lbclnk_tam  ***
4   !! Ocean        : adjoint of lateral boundary conditions
5   !!=====================================================================
6#if   defined key_mpp_mpi   ||   defined key_mpp_shmem
7   !!----------------------------------------------------------------------
8   !!   'key_mpp_mpi'     OR      MPI massively parallel processing library
9   !!   'key_mpp_shmem'         SHMEM massively parallel processing library
10   !!----------------------------------------------------------------------
11   !!----------------------------------------------------------------------
12   !!   lbc_lnk_adj     : generic interface for mpp_lnk_3d_adj and
13   !!                     mpp_lnkadj_2d routines defined in lib_mpp_tam
14   !!   lbc_lnk_adj_e   : generic interface for mpp_lnk_2d_e_adj
15   !!                     routine defined in lib_mpp_tam
16   !!----------------------------------------------------------------------
17   !! * Modules used
18   USE lib_mpp_tam          ! distributed memory computing library
19
20   INTERFACE lbc_lnk_adj
21      MODULE PROCEDURE mpp_lnk_3d_gather_adj, mpp_lnk_3d_adj, mpp_lnk_2d_adj
22   END INTERFACE
23
24   INTERFACE lbc_lnk_e_adj
25      MODULE PROCEDURE mpp_lnk_2d_e_adj
26   END INTERFACE
27
28   PUBLIC lbc_lnk_adj       ! ocean lateral boundary conditions
29   PUBLIC lbc_lnk_e_adj     ! ocean lateral boundary conditions
30   !!----------------------------------------------------------------------
31
32#else
33   !!----------------------------------------------------------------------
34   !!   Default option                              shared memory computing
35   !!----------------------------------------------------------------------
36   !!   lbc_lnk_adj     : generic interface for lbc_lnkadj_3d and lbc_lnkadj_2d
37   !!   lbc_lnk_3d_adj  : set the lateral boundary condition on a 3D variable
38   !!                  on OPA ocean mesh
39   !!   lbc_lnk_2d_adj  : set the lateral boundary condition on a 2D variable
40   !!                  on OPA ocean mesh
41   !!----------------------------------------------------------------------
42   !! * Modules used
43   USE oce             ! ocean dynamics and tracers   
44   USE dom_oce         ! ocean space and time domain
45   USE in_out_manager  ! I/O manager
46   USE lbcnfd_tam      ! TAM of north fold
47
48   IMPLICIT NONE
49   PRIVATE
50
51   INTERFACE lbc_lnk_adj
52      MODULE PROCEDURE lbc_lnk_3d_gather_adj, lbc_lnk_3d_adj, lbc_lnk_2d_adj
53   END INTERFACE
54
55   INTERFACE lbc_lnk_e_adj
56      MODULE PROCEDURE lbc_lnk_2d_adj
57   END INTERFACE
58
59   PUBLIC lbc_lnk_adj       ! ocean/ice  lateral boundary conditions
60   PUBLIC lbc_lnk_e_adj     ! ocean/ice  lateral boundary conditions
61   !!----------------------------------------------------------------------
62
63CONTAINS
64
65   SUBROUTINE lbc_lnk_3d_gather_adj( pt3d1, cd_type1, pt3d2, cd_type2, psgn )
66      !!---------------------------------------------------------------------
67      !!                  ***  ROUTINE lbc_lnkadj_3d_gather  ***
68      !!
69      !! ** Purpose : Adjoint of set lateral boundary conditions (non mpp case)
70      !!
71      !! ** Method  :
72      !!
73      !! History of TAM:
74      !!                  ! 2007-08  (K. Mogensen) Original code
75      !!         NEMO 3.2 ! 2010-04 (F. Vigilant)  External north fold treatment
76      !!----------------------------------------------------------------------
77      !! * Arguments
78      CHARACTER(len=1), INTENT( in ) ::   &
79         cd_type1, cd_type2       ! nature of pt3d grid-points
80         !             !   = T ,  U , V , F or W  gridpoints
81      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   &
82         pt3d1, pt3d2          ! 3D array on which the boundary condition is applied
83      REAL(wp), INTENT( in ) ::   &
84         psgn          ! control of the sign change
85         !             !   =-1 , the sign is changed if north fold boundary
86         !             !   = 1 , no sign change
87         !             !   = 0 , no sign change and > 0 required (use the inner
88         !             !         row/column if closed boundary)
89
90      CALL lbc_lnk_3d_adj( pt3d2, cd_type2, psgn)
91      CALL lbc_lnk_3d_adj( pt3d1, cd_type1, psgn)
92
93   END SUBROUTINE lbc_lnk_3d_gather_adj
94
95   SUBROUTINE lbc_lnk_3d_adj( pt3d, cd_type, psgn, cd_mpp )
96      !!---------------------------------------------------------------------
97      !!                  ***  ROUTINE lbc_lnkadj_3d  ***
98      !!
99      !! ** Purpose : Adjoint of set lateral boundary conditions (non mpp case)
100      !!
101      !! ** Method  :
102      !!
103      !! History :
104      !!                  ! 2007-08  (K. Mogensen) Original code
105      !!         NEMO 3.2 ! 2010-04 (F. Vigilant)  External north fold treatment
106      !!----------------------------------------------------------------------
107      !! * Arguments
108      CHARACTER(len=1), INTENT( in ) ::   &
109         cd_type       ! nature of pt3d grid-points
110         !             !   = T ,  U , V , F or W  gridpoints
111      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   &
112         pt3d          ! 3D array on which the boundary condition is applied
113      REAL(wp), INTENT( in ) ::   &
114         psgn          ! control of the sign change
115         !             !   =-1 , the sign is changed if north fold boundary
116         !             !   = 1 , no sign change
117         !             !   = 0 , no sign change and > 0 required (use the inner
118         !             !         row/column if closed boundary)
119      CHARACTER(len=3), INTENT( in ), OPTIONAL ::    &
120         cd_mpp        ! fill the overlap area only (here do nothing)
121
122      IF (PRESENT(cd_mpp)) THEN
123         ! only fill the overlap area and extra allows
124         ! this is in mpp case. In this module, just do nothing
125      ELSE
126
127         !                                     ! North-South boundaries
128         !                                     ! ======================
129         SELECT CASE ( nperio )
130
131         CASE ( 2 )                            !**  South symmetric  --  North closed
132
133            SELECT CASE ( cd_type )
134            CASE ( 'T' , 'U' , 'W' )                   ! T-, U-, W-points
135               pt3d(:,jpj,:) = 0.0_wp
136               pt3d(:, 3 ,:) = pt3d(:,3,:) + pt3d(:,1,:)
137               pt3d(:, 1 ,:) = 0.0_wp
138            CASE ( 'V' , 'F' )                         ! V-, F-points
139               pt3d(:,jpj,:) = 0.0_wp
140               pt3d(:, 2 ,:) = pt3d(:,2,:) + psgn * pt3d(:,1,:)
141               pt3d(:, 1 ,:) = 0.0_wp
142            END SELECT
143
144         CASE ( 3 , 4 , 5, 6 )                 !**  North fold  T or F-point pivot  --  South closed
145            CALL lbc_nfd_adj( pt3d(:,:,:), cd_type, psgn  )  ! North fold
146            pt3d(jpi,jpj,:) = 0.0_wp
147            pt3d( 1 ,jpj,:) = 0.0_wp
148            !
149            SELECT CASE ( cd_type )
150            CASE ( 'T' , 'U' , 'V' , 'W' , 'I' )             ! all points except F-point
151               pt3d(:, 1 ,:) = 0.0_wp
152            END SELECT
153
154         CASE DEFAULT                          !**  North closed  --  South closed
155            SELECT CASE ( cd_type )
156            CASE ( 'T' , 'U' , 'V' , 'W' )             ! T-, U-, V-, W-points
157               pt3d(:,jpj,:) = 0.0_wp
158               pt3d(:, 1 ,:) = 0.0_wp
159            CASE ( 'F' )                               ! F-point
160               pt3d(:,jpj,:) = 0.0_wp
161            END SELECT
162
163         END SELECT
164
165         !                                     !  East-West boundaries
166         !                                     ! ======================
167         SELECT CASE ( nperio )
168         !
169         CASE ( 1 , 4 , 6 )                       !**  cyclic east-west
170            pt3d(  2  ,:,:) = pt3d(  2  ,:,:) + pt3d(jpi,:,:)
171            pt3d(jpi,:,:) = 0.0_wp
172            pt3d(jpim1,:,:) = pt3d(jpim1,:,:) + pt3d( 1 ,:,:)
173            pt3d( 1 ,:,:) = 0.0_wp
174            !
175         CASE DEFAULT                             !**  East closed  --  West closed
176            SELECT CASE ( cd_type )
177            CASE ( 'T' , 'U' , 'V' , 'W' )             ! T-, U-, V-, W-points
178               pt3d( 1 ,:,:) = 0.0_wp
179               pt3d(jpi,:,:) = 0.0_wp
180            CASE ( 'F' )                               ! F-point
181               pt3d(jpi,:,:) = 0.0_wp
182            END SELECT
183            !
184         END SELECT
185
186      ENDIF
187
188   END SUBROUTINE lbc_lnk_3d_adj
189
190   SUBROUTINE lbc_lnk_2d_adj( pt2d, cd_type, psgn, cd_mpp )
191      !!---------------------------------------------------------------------
192      !!                 ***  ROUTINE lbc_lnkadj_2d  ***
193      !!
194      !! ** Purpose : Adjoint of set lateral boundary conditions (non mpp case)
195      !!
196      !! ** Method  :
197      !!
198      !! History of TAM:
199      !!                  ! 2007-08  (K. Mogensen) Original code
200      !!         NEMO 3.2 ! 2010-04 (F. Vigilant)  External north fold treatment
201      !!----------------------------------------------------------------------
202      !! * Arguments
203      CHARACTER(len=1), INTENT( in ) ::   &
204         cd_type       ! nature of pt2d grid-point
205         !             !   = T , U , V , F or W  gridpoints
206         !             !   = I sea-ice U-V gridpoint (= F ocean grid point with indice shift)
207      REAL(wp), INTENT( in ) ::   &
208         psgn          ! control of the sign change
209         !             !   =-1 , the sign is modified following the type of b.c. used
210         !             !   = 1 , no sign change
211      REAL(wp), DIMENSION(jpi,jpj), INTENT( inout ) ::   &
212         pt2d          ! 2D array on which the boundary condition is applied
213      CHARACTER(len=3), INTENT( in ), OPTIONAL ::    &
214         cd_mpp        ! fill the overlap area only (here do nothing)
215     
216      IF (PRESENT(cd_mpp)) THEN
217         ! only fill the overlap area and extra allows
218         ! this is in mpp case. In this module, just do nothing
219      ELSE
220
221         !                                     ! North-South boundaries
222         !                                     ! ======================
223         SELECT CASE ( nperio )
224         !
225         CASE ( 2 )                            ! *  south symmetric
226         SELECT CASE ( cd_type )
227         CASE ( 'T' , 'U' , 'W' )                   ! T-, U-, W-points
228            pt2d(:,jpj) = 0.0_wp
229            pt2d(:, 3 ) = pt2d(:,3) + pt2d(:,1)
230            pt2d(:, 1 ) = 0.0_wp
231         CASE ( 'V' , 'F' )                         ! V-, F-points
232            pt2d(:,jpj) = 0.e0
233            pt2d(:, 2 ) = pt2d(:,2) + psgn * pt2d(:,1)
234            pt2d(:, 1 ) = 0.e0
235         END SELECT
236         
237         CASE ( 3 , 4, 5, 6 )                   !**  North fold  T or F-point pivot  --  South closed
238            CALL lbc_nfd_adj( pt2d(:,:), cd_type, psgn )
239            pt2d(jpi,jpj) = 0.0_wp
240            pt2d( 1 ,jpj) = 0.0_wp
241            pt2d( 1 , 1 ) = 0.0_wp       
242            SELECT CASE ( cd_type )
243            CASE ( 'T' , 'U' , 'V' , 'W' ,  'I')             ! all points except F-point
244               pt2d(:, 1 ) = 0.0_wp
245            END SELECT
246         
247         CASE DEFAULT                          ! *  closed
248            SELECT CASE ( cd_type )
249            CASE ( 'T' , 'U' , 'V' , 'W' )             ! T-, U-, V-, W-points
250               pt2d(:,jpj) = 0.0_wp
251               pt2d(:, 1 ) = 0.0_wp
252            CASE ( 'F' )                               ! F-point
253               pt2d(:,jpj) = 0.0_wp
254            END SELECT
255            !
256         END SELECT
257
258         !                                     ! East-West boundaries
259         !                                     ! ====================
260         SELECT CASE ( nperio )
261         !
262         CASE ( 1 , 4 , 6 )                    ! * cyclic east-west
263            pt2d(  2  ,:) = pt2d(  2  ,:) + pt2d( jpi ,:)
264            pt2d( jpi ,:) = 0.0_wp
265            pt2d(jpim1,:) = pt2d(jpim1,:) + pt2d( 1 ,:)
266            pt2d(  1  ,:) = 0.0_wp 
267            !
268      CASE DEFAULT                             !** East closed  --  West closed
269         SELECT CASE ( cd_type )
270         CASE ( 'T' , 'U' , 'V' , 'W' )             ! T-, U-, V-, W-points
271            pt2d(jpi,:) = 0.0_wp
272            pt2d( 1 ,:) = 0.0_wp
273         CASE ( 'F' )                               ! F-point
274            pt2d(jpi,:) = 0.0_wp
275         END SELECT
276         
277      END SELECT
278     
279      ENDIF
280     
281   END SUBROUTINE lbc_lnk_2d_adj
282
283#endif
284
285END MODULE lbclnk_tam
Note: See TracBrowser for help on using the repository browser.