ROMS
Loading...
Searching...
No Matches
ad_bc_bry2d.F
Go to the documentation of this file.
1#include "cppdefs.h"
3#ifdef ADJOINT
4!
5!git $Id$
6!================================================== Hernan G. Arango ===
7! Copyright (c) 2002-2025 The ROMS Group !
8! Licensed under a MIT/X style license !
9! See License_ROMS.md !
10!=======================================================================
11! !
12! This package applies adjoint gradient conditions for generic 2D !
13! boundary fields. !
14! !
15! Routines: !
16! !
17! ad_bc_r2d_bry_tile Boundary conditions for field at RHO-points !
18! ad_bc_u2d_bry_tile Boundary conditions for field at U-points !
19! ad_bc_v2d_bry_tile Boundary conditions for field at V-points !
20! !
21!=======================================================================
22!
23 implicit none
24
25 CONTAINS
26!
27!***********************************************************************
28 SUBROUTINE ad_bc_r2d_bry_tile (ng, tile, boundary, &
29 & LBij, UBij, &
30 & ad_A)
31!***********************************************************************
32!
33 USE mod_param
34 USE mod_scalars
35!
36! Imported variable declarations.
37!
38 integer, intent(in) :: ng, tile, boundary
39 integer, intent(in) :: LBij, UBij
40
41# ifdef ASSUMED_SHAPE
42 real(r8), intent(inout) :: ad_A(LBij:)
43# else
44 real(r8), intent(inout) :: ad_A(LBij:UBij)
45# endif
46
47# include "set_bounds.h"
48!
49!-----------------------------------------------------------------------
50! Adjoint Southern and Northern edges: gradient boundary conditions.
51!-----------------------------------------------------------------------
52!
53 IF (boundary.eq.inorth) THEN
54 IF (domain(ng)%NorthEast_Corner(tile)) THEN
55!^ tl_A(Iend+1)=tl_A(Iend)
56!^
57 ad_a(iend)=ad_a(iend)+ad_a(iend+1)
58 ad_a(iend+1)=0.0_r8
59 END IF
60 IF (domain(ng)%NorthWest_Corner(tile)) THEN
61!^ tl_A(Istr-1)=tl_A(Istr)
62!^
63 ad_a(istr)=ad_a(istr)+ad_a(istr-1)
64 ad_a(istr-1)=0.0_r8
65 END IF
66 END IF
67
68 IF (boundary.eq.isouth) THEN
69 IF (domain(ng)%SouthEast_Corner(tile)) THEN
70!^ tl_A(Iend+1)=tl_A(Iend)
71!^
72 ad_a(iend)=ad_a(iend)+ad_a(iend+1)
73 ad_a(iend+1)=0.0_r8
74 END IF
75 IF (domain(ng)%SouthWest_Corner(tile)) THEN
76!^ tl_A(Istr-1)=tl_A(Istr)
77!^
78 ad_a(istr)=ad_a(istr)+ad_a(istr-1)
79 ad_a(istr-1)=0.0_r8
80 END IF
81 END IF
82!
83!-----------------------------------------------------------------------
84! Adjoint Western and Eastern edges: gradient boundary conditions.
85!-----------------------------------------------------------------------
86!
87 IF (boundary.eq.ieast) THEN
88 IF (domain(ng)%NorthEast_Corner(tile)) THEN
89!^ tl_A(Jend+1)=tl_A(Jend)
90!^
91 ad_a(jend)=ad_a(jend)+ad_a(jend+1)
92 ad_a(jend+1)=0.0_r8
93 END IF
94 IF (domain(ng)%SouthEast_Corner(tile)) THEN
95!^ tl_A(Jstr-1)=tl_A(Jstr)
96!^
97 ad_a(jstr)=ad_a(jstr)+ad_a(jstr-1)
98 ad_a(jstr-1)=0.0_r8
99 END IF
100 END IF
101
102 IF (boundary.eq.iwest) THEN
103 IF (domain(ng)%NorthWest_Corner(tile)) THEN
104!^ tl_A(Jend+1)=tl_A(Jend)
105!^
106 ad_a(jend)=ad_a(jend)+ad_a(jend+1)
107 ad_a(jend+1)=0.0_r8
108 END IF
109 IF (domain(ng)%SouthWest_Corner(tile)) THEN
110!^ tl_A(Jstr-1)=tl_A(Jstr)
111!^
112 ad_a(jstr)=ad_a(jstr)+ad_a(jstr-1)
113 ad_a(jstr-1)=0.0_r8
114 END IF
115 END IF
116
117 RETURN
118 END SUBROUTINE ad_bc_r2d_bry_tile
119
120!
121!***********************************************************************
122 SUBROUTINE ad_bc_u2d_bry_tile (ng, tile, boundary, &
123 & LBij, UBij, &
124 & ad_A)
125!***********************************************************************
126!
127 USE mod_param
128 USE mod_scalars
129!
130! Imported variable declarations.
131!
132 integer, intent(in) :: ng, tile, boundary
133 integer, intent(in) :: LBij, UBij
134
135# ifdef ASSUMED_SHAPE
136 real(r8), intent(inout) :: ad_A(LBij:)
137# else
138 real(r8), intent(inout) :: ad_A(LBij:UBij)
139# endif
140
141# include "set_bounds.h"
142!
143!-----------------------------------------------------------------------
144! Adjoint Southern and Northern edges: gradient boundary conditions.
145!-----------------------------------------------------------------------
146!
147 IF (boundary.eq.inorth) THEN
148 IF (domain(ng)%NorthEast_Corner(tile)) THEN
149!^ tl_A(Iend+1)=tl_A(Iend)
150!^
151 ad_a(iend)=ad_a(iend)+ad_a(iend+1)
152 ad_a(iend+1)=0.0_r8
153 END IF
154 IF (domain(ng)%NorthWest_Corner(tile)) THEN
155!^ tl_A(IstrU-1)=tl_A(IstrU)
156!^
157 ad_a(istru)=ad_a(istru)+ad_a(istru-1)
158 ad_a(istru-1)=0.0_r8
159 END IF
160 END IF
161
162 IF (boundary.eq.isouth) THEN
163 IF (domain(ng)%SouthEast_Corner(tile)) THEN
164!^ tl_A(Iend+1)=tl_A(Iend)
165!^
166 ad_a(iend)=ad_a(iend)+ad_a(iend+1)
167 ad_a(iend+1)=0.0_r8
168 END IF
169 IF (domain(ng)%SouthWest_Corner(tile)) THEN
170!^ tl_A(IstrU-1)=tl_A(IstrU)
171!^
172 ad_a(istru)=ad_a(istru)+ad_a(istru-1)
173 ad_a(istru-1)=0.0_r8
174 END IF
175 END IF
176!
177!-----------------------------------------------------------------------
178! Adjoint Western and Eastern edges: gradient boundary conditions.
179!-----------------------------------------------------------------------
180!
181 IF (boundary.eq.ieast) THEN
182 IF (domain(ng)%NorthEast_Corner(tile)) THEN
183!^ tl_A(Jend+1)=tl_A(Jend)
184!^
185 ad_a(jend)=ad_a(jend)+ad_a(jend+1)
186 ad_a(jend+1)=0.0_r8
187 END IF
188 IF (domain(ng)%SouthEast_Corner(tile)) THEN
189!^ tl_A(Jstr-1)=tl_A(Jstr)
190!^
191 ad_a(jstr)=ad_a(jstr)+ad_a(jstr-1)
192 ad_a(jstr-1)=0.0_r8
193 END IF
194 END IF
195
196 IF (boundary.eq.iwest) THEN
197 IF (domain(ng)%NorthWest_Corner(tile)) THEN
198!^ tl_A(Jend+1)=tl_A(Jend)
199!^
200 ad_a(jend)=ad_a(jend)+ad_a(jend+1)
201 ad_a(jend+1)=0.0_r8
202 END IF
203 IF (domain(ng)%SouthWest_Corner(tile)) THEN
204!^ tl_A(Jstr-1)=tl_A(Jstr)
205!^
206 ad_a(jstr)=ad_a(jstr)+ad_a(jstr-1)
207 ad_a(jstr-1)=0.0_r8
208 END IF
209 END IF
210
211 RETURN
212 END SUBROUTINE ad_bc_u2d_bry_tile
213
214!
215!***********************************************************************
216 SUBROUTINE ad_bc_v2d_bry_tile (ng, tile, boundary, &
217 & LBij, UBij, &
218 & ad_A)
219!***********************************************************************
220!
221 USE mod_param
222 USE mod_scalars
223!
224! Imported variable declarations.
225!
226 integer, intent(in) :: ng, tile, boundary
227 integer, intent(in) :: LBij, UBij
228
229# ifdef ASSUMED_SHAPE
230 real(r8), intent(inout) :: ad_A(LBij:)
231# else
232 real(r8), intent(inout) :: ad_A(LBij:UBij)
233# endif
234
235# include "set_bounds.h"
236!
237!-----------------------------------------------------------------------
238! Adjoint Southern and Northern edges: gradient boundary conditions.
239!-----------------------------------------------------------------------
240!
241 IF (boundary.eq.inorth) THEN
242 IF (domain(ng)%NorthEast_Corner(tile)) THEN
243!^ tl_A(Iend+1)=tl_A(Iend)
244!^
245 ad_a(iend)=ad_a(iend)+ad_a(iend+1)
246 ad_a(iend+1)=0.0_r8
247 END IF
248 IF (domain(ng)%NorthWest_Corner(tile)) THEN
249!^ tl_A(Istr-1)=tl_A(Istr)
250!^
251 ad_a(istr)=ad_a(istr)+ad_a(istr-1)
252 ad_a(istr-1)=0.0_r8
253 END IF
254 END IF
255
256 IF (boundary.eq.isouth) THEN
257 IF (domain(ng)%SouthEast_Corner(tile)) THEN
258!^ tl_A(Iend+1)=tl_A(Iend)
259!^
260 ad_a(iend)=ad_a(iend)+ad_a(iend+1)
261 ad_a(iend+1)=0.0_r8
262 END IF
263 IF (domain(ng)%SouthWest_Corner(tile)) THEN
264!^ tl_A(Istr-1)=tl_A(Istr)
265!^
266 ad_a(istr)=ad_a(istr)+ad_a(istr-1)
267 ad_a(istr-1)=0.0_r8
268 END IF
269 END IF
270!
271!-----------------------------------------------------------------------
272! Adjoint Western and Eastern edges: gradient boundary conditions.
273!-----------------------------------------------------------------------
274!
275 IF (boundary.eq.ieast) THEN
276 IF (domain(ng)%NorthEast_Corner(tile)) THEN
277!^ tl_A(Jend+1)=tl_A(Jend)
278!^
279 ad_a(jend)=ad_a(jend)+ad_a(jend+1)
280 ad_a(jend+1)=0.0_r8
281 END IF
282 IF (domain(ng)%SouthEast_Corner(tile)) THEN
283!^ tl_A(JstrV-1)=tl_A(JstrV)
284!^
285 ad_a(jstrv)=ad_a(jstrv)+ad_a(jstrv-1)
286 ad_a(jstrv-1)=0.0_r8
287 END IF
288 END IF
289
290 IF (boundary.eq.iwest) THEN
291 IF (domain(ng)%NorthWest_Corner(tile)) THEN
292!^ tl_A(Jend+1)=tl_A(Jend)
293!^
294 ad_a(jend)=ad_a(jend)+ad_a(jend+1)
295 ad_a(jend+1)=0.0_r8
296 END IF
297 IF (domain(ng)%SouthWest_Corner(tile)) THEN
298!^ tl_A(JstrV-1)=tl_A(JstrV)
299!^
300 ad_a(jstrv)=ad_a(jstrv)+ad_a(jstrv-1)
301 ad_a(jstrv-1)=0.0_r8
302 END IF
303 END IF
304
305 RETURN
306 END SUBROUTINE ad_bc_v2d_bry_tile
307#endif
308 END MODULE ad_bc_bry2d_mod
subroutine ad_bc_u2d_bry_tile(ng, tile, boundary, lbij, ubij, ad_a)
subroutine ad_bc_v2d_bry_tile(ng, tile, boundary, lbij, ubij, ad_a)
subroutine ad_bc_r2d_bry_tile(ng, tile, boundary, lbij, ubij, ad_a)
Definition ad_bc_bry2d.F:31
type(t_domain), dimension(:), allocatable domain
Definition mod_param.F:329
integer, parameter iwest
integer, parameter isouth
integer, parameter ieast
integer, parameter inorth