FV3DYCORE  Version 2.0.0
tp_core.F90
Go to the documentation of this file.
1 !***********************************************************************
2 !* GNU Lesser General Public License
3 !*
4 !* This file is part of the FV3 dynamical core.
5 !*
6 !* The FV3 dynamical core is free software: you can redistribute it
7 !* and/or modify it under the terms of the
8 !* GNU Lesser General Public License as published by the
9 !* Free Software Foundation, either version 3 of the License, or
10 !* (at your option) any later version.
11 !*
12 !* The FV3 dynamical core is distributed in the hope that it will be
13 !* useful, but WITHOUT ANYWARRANTY; without even the implied warranty
14 !* of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
15 !* See the GNU General Public License for more details.
16 !*
17 !* You should have received a copy of the GNU Lesser General Public
18 !* License along with the FV3 dynamical core.
19 !* If not, see <http://www.gnu.org/licenses/>.
20 !***********************************************************************
21 
25 
26 ! Modules Included:
27 !
28 ! <table>
29 ! <tr>
30 ! <th>Module Name</th>
31 ! <th>Functions Included</th>
32 ! </tr>
33 ! <tr>
34 ! <td>fv_mp_mod</td>
35 ! <td>ng</td>
36 ! </tr>
37 ! <tr>
38 ! <td>fv_grid_utils_mod</td>
39 ! <td>big_number</td>
40 ! </tr>
41 ! <tr>
42 ! <td>fv_arrays_mod</td>
43 ! <td>fv_grid_type, fv_grid_bounds_type</td>
44 ! </tr>
45 ! <tr>
46 ! <td>field_manager_mod</td>
47 ! <td>fm_path_name_len, fm_string_len, fm_exists, fm_get_index, fm_new_list, fm_get_current_list,
48 ! fm_change_list, fm_field_name_len, fm_type_name_len, fm_dump_list, fm_loop_over_list</td>
49 ! </tr>
50 ! </table>
51 
52  use fv_grid_utils_mod, only: big_number
54 
55  implicit none
56 
57  private
59 
60  real, parameter:: ppm_fac = 1.5
61  real, parameter:: r3 = 1./3.
62  real, parameter:: near_zero = 1.e-25
63  real, parameter:: ppm_limiter = 2.0
64 
65 #ifdef WAVE_FORM
66 ! Suresh & Huynh scheme 2.2 (purtabation form)
67 ! The wave-form is more diffusive than scheme 2.1
68  real, parameter:: b1 = 0.0375
69  real, parameter:: b2 = -7./30.
70  real, parameter:: b3 = -23./120.
71  real, parameter:: b4 = 13./30.
72  real, parameter:: b5 = -11./240.
73 #else
74 ! scheme 2.1: perturbation form
75  real, parameter:: b1 = 1./30.
76  real, parameter:: b2 = -13./60.
77  real, parameter:: b3 = -13./60.
78  real, parameter:: b4 = 0.45
79  real, parameter:: b5 = -0.05
80 #endif
81  real, parameter:: t11 = 27./28., t12 = -13./28., t13=3./7.
82  real, parameter:: s11 = 11./14., s14 = 4./7., s15=3./14.
83 !----------------------------------------------------
84 ! volume-conserving cubic with 2nd drv=0 at end point:
85 !----------------------------------------------------
86 ! Non-monotonic
87  real, parameter:: c1 = -2./14.
88  real, parameter:: c2 = 11./14.
89  real, parameter:: c3 = 5./14.
90 !----------------------
91 ! PPM volume mean form:
92 !----------------------
93  real, parameter:: p1 = 7./12. ! 0.58333333
94  real, parameter:: p2 = -1./12.
95 ! q(i+0.5) = p1*(q(i-1)+q(i)) + p2*(q(i-2)+q(i+1))
96 ! integer:: is, ie, js, je, isd, ied, jsd, jed
97 
98 !
99 !EOP
100 !-----------------------------------------------------------------------
101 
102 contains
103 
107  subroutine fv_tp_2d(q, crx, cry, npx, npy, hord, fx, fy, xfx, yfx, &
108  gridstruct, bd, ra_x, ra_y, lim_fac, mfx, mfy, mass, nord, damp_c)
109  type(fv_grid_bounds_type), intent(IN) :: bd
110  integer, intent(in):: npx, npy
111  integer, intent(in)::hord
112 
113  real, intent(in):: crx(bd%is:bd%ie+1,bd%jsd:bd%jed)
114  real, intent(in):: xfx(bd%is:bd%ie+1,bd%jsd:bd%jed)
115  real, intent(in):: cry(bd%isd:bd%ied,bd%js:bd%je+1 )
116  real, intent(in):: yfx(bd%isd:bd%ied,bd%js:bd%je+1 )
117  real, intent(in):: ra_x(bd%is:bd%ie,bd%jsd:bd%jed)
118  real, intent(in):: ra_y(bd%isd:bd%ied,bd%js:bd%je)
119  real, intent(inout):: q(bd%isd:bd%ied,bd%jsd:bd%jed)
120  real, intent(out)::fx(bd%is:bd%ie+1 ,bd%js:bd%je)
121  real, intent(out)::fy(bd%is:bd%ie, bd%js:bd%je+1 )
122 
123  type(fv_grid_type), intent(IN), target :: gridstruct
124 
125  real, intent(in):: lim_fac
126 ! optional Arguments:
127  real, OPTIONAL, intent(in):: mfx(bd%is:bd%ie+1,bd%js:bd%je )
128  real, OPTIONAL, intent(in):: mfy(bd%is:bd%ie ,bd%js:bd%je+1)
129  real, OPTIONAL, intent(in):: mass(bd%isd:bd%ied,bd%jsd:bd%jed)
130  real, OPTIONAL, intent(in):: damp_c
131  integer, OPTIONAL, intent(in):: nord
132 ! Local:
133  integer ord_ou, ord_in
134  real q_i(bd%isd:bd%ied,bd%js:bd%je)
135  real q_j(bd%is:bd%ie,bd%jsd:bd%jed)
136  real fx2(bd%is:bd%ie+1,bd%jsd:bd%jed)
137  real fy2(bd%isd:bd%ied,bd%js:bd%je+1)
138  real fyy(bd%isd:bd%ied,bd%js:bd%je+1)
139  real fx1(bd%is:bd%ie+1)
140  real damp
141  integer i, j
142 
143  integer:: is, ie, js, je, isd, ied, jsd, jed
144 
145  is = bd%is
146  ie = bd%ie
147  js = bd%js
148  je = bd%je
149  isd = bd%isd
150  ied = bd%ied
151  jsd = bd%jsd
152  jed = bd%jed
153 
154  if ( hord == 10 ) then
155  ord_in = 8
156  else
157  ord_in = hord
158  endif
159  ord_ou = hord
160 
161  if (.not. gridstruct%bounded_domain) &
162  call copy_corners(q, npx, npy, 2, gridstruct%bounded_domain, bd, &
163  gridstruct%sw_corner, gridstruct%se_corner, gridstruct%nw_corner, gridstruct%ne_corner)
164 
165  call yppm(fy2, q, cry, ord_in, isd,ied,isd,ied, js,je,jsd,jed, npx,npy, gridstruct%dya, gridstruct%bounded_domain, gridstruct%grid_type, lim_fac)
166 
167  do j=js,je+1
168  do i=isd,ied
169  fyy(i,j) = yfx(i,j) * fy2(i,j)
170  enddo
171  enddo
172  do j=js,je
173  do i=isd,ied
174  q_i(i,j) = (q(i,j)*gridstruct%area(i,j) + fyy(i,j)-fyy(i,j+1))/ra_y(i,j)
175  enddo
176  enddo
177 
178  call xppm(fx, q_i, crx(is,js), ord_ou, is,ie,isd,ied, js,je,jsd,jed, npx,npy, gridstruct%dxa, gridstruct%bounded_domain, gridstruct%grid_type, lim_fac)
179 
180  if (.not. gridstruct%bounded_domain) &
181  call copy_corners(q, npx, npy, 1, gridstruct%bounded_domain, bd, &
182  gridstruct%sw_corner, gridstruct%se_corner, gridstruct%nw_corner, gridstruct%ne_corner)
183 
184  call xppm(fx2, q, crx, ord_in, is,ie,isd,ied, jsd,jed,jsd,jed, npx,npy, gridstruct%dxa, gridstruct%bounded_domain, gridstruct%grid_type, lim_fac)
185 
186  do j=jsd,jed
187  do i=is,ie+1
188  fx1(i) = xfx(i,j) * fx2(i,j)
189  enddo
190  do i=is,ie
191  q_j(i,j) = (q(i,j)*gridstruct%area(i,j) + fx1(i)-fx1(i+1))/ra_x(i,j)
192  enddo
193  enddo
194 
195  call yppm(fy, q_j, cry, ord_ou, is,ie,isd,ied, js,je,jsd,jed, npx, npy, gridstruct%dya, gridstruct%bounded_domain, gridstruct%grid_type, lim_fac)
196 
197 !----------------
198 ! Flux averaging:
199 !----------------
200 
201  if ( present(mfx) .and. present(mfy) ) then
202 !---------------------------------
203 ! For transport of pt and tracers
204 !---------------------------------
205  do j=js,je
206  do i=is,ie+1
207  fx(i,j) = 0.5*(fx(i,j) + fx2(i,j)) * mfx(i,j)
208  enddo
209  enddo
210  do j=js,je+1
211  do i=is,ie
212  fy(i,j) = 0.5*(fy(i,j) + fy2(i,j)) * mfy(i,j)
213  enddo
214  enddo
215  if ( present(nord) .and. present(damp_c) .and. present(mass) ) then
216  if ( damp_c > 1.e-4 ) then
217  damp = (damp_c * gridstruct%da_min)**(nord+1)
218  call deln_flux(nord, is,ie,js,je, npx, npy, damp, q, fx, fy, gridstruct, bd, mass )
219  endif
220  endif
221  else
222 !---------------------------------
223 ! For transport of delp, vorticity
224 !---------------------------------
225  do j=js,je
226  do i=is,ie+1
227  fx(i,j) = 0.5*(fx(i,j) + fx2(i,j)) * xfx(i,j)
228  enddo
229  enddo
230  do j=js,je+1
231  do i=is,ie
232  fy(i,j) = 0.5*(fy(i,j) + fy2(i,j)) * yfx(i,j)
233  enddo
234  enddo
235  if ( present(nord) .and. present(damp_c) ) then
236  if ( damp_c > 1.e-4 ) then
237  damp = (damp_c * gridstruct%da_min)**(nord+1)
238  call deln_flux(nord, is,ie,js,je, npx, npy, damp, q, fx, fy, gridstruct, bd)
239  endif
240  endif
241  endif
242  end subroutine fv_tp_2d
243 
244  !Weird arguments are because this routine is called in a lot of
245  !places outside of tp_core, sometimes very deeply nested in the call tree.
246  subroutine copy_corners(q, npx, npy, dir, bounded_domain, bd, &
247  sw_corner, se_corner, nw_corner, ne_corner)
248  type(fv_grid_bounds_type), intent(IN) :: bd
249  integer, intent(in):: npx, npy, dir
250  real, intent(inout):: q(bd%isd:bd%ied,bd%jsd:bd%jed)
251  logical, intent(IN) :: bounded_domain, sw_corner, se_corner, nw_corner, ne_corner
252  integer i,j, ng
253 
254  ng = bd%ng
255 
256  if (bounded_domain) return
257 
258  if ( dir == 1 ) then
259 ! XDir:
260  if ( sw_corner ) then
261  do j=1-ng,0
262  do i=1-ng,0
263  q(i,j) = q(j,1-i)
264  enddo
265  enddo
266  endif
267  if ( se_corner ) then
268  do j=1-ng,0
269  do i=npx,npx+ng-1
270  q(i,j) = q(npy-j,i-npx+1)
271  enddo
272  enddo
273  endif
274  if ( ne_corner ) then
275  do j=npy,npy+ng-1
276  do i=npx,npx+ng-1
277  q(i,j) = q(j,2*npx-1-i)
278  enddo
279  enddo
280  endif
281  if ( nw_corner ) then
282  do j=npy,npy+ng-1
283  do i=1-ng,0
284  q(i,j) = q(npy-j,i-1+npx)
285  enddo
286  enddo
287  endif
288 
289  elseif ( dir == 2 ) then
290 ! YDir:
291 
292  if ( sw_corner ) then
293  do j=1-ng,0
294  do i=1-ng,0
295  q(i,j) = q(1-j,i)
296  enddo
297  enddo
298  endif
299  if ( se_corner ) then
300  do j=1-ng,0
301  do i=npx,npx+ng-1
302  q(i,j) = q(npy+j-1,npx-i)
303  enddo
304  enddo
305  endif
306  if ( ne_corner ) then
307  do j=npy,npy+ng-1
308  do i=npx,npx+ng-1
309  q(i,j) = q(2*npy-1-j,i)
310  enddo
311  enddo
312  endif
313  if ( nw_corner ) then
314  do j=npy,npy+ng-1
315  do i=1-ng,0
316  q(i,j) = q(j+1-npx,npy-i)
317  enddo
318  enddo
319  endif
320 
321  endif
322 
323  end subroutine copy_corners
324 
325  subroutine xppm(flux, q, c, iord, is,ie,isd,ied, jfirst,jlast,jsd,jed, npx, npy, dxa, bounded_domain, grid_type, lim_fac)
326  integer, INTENT(IN) :: is, ie, isd, ied, jsd, jed
327  integer, INTENT(IN) :: jfirst, jlast
328  integer, INTENT(IN) :: iord
329  integer, INTENT(IN) :: npx, npy
330  real , INTENT(IN) :: q(isd:ied,jfirst:jlast)
331  real , INTENT(IN) :: c(is:ie+1,jfirst:jlast)
332  real , intent(IN) :: dxa(isd:ied,jsd:jed)
333  logical, intent(IN) :: bounded_domain
334  integer, intent(IN) :: grid_type
335  real , intent(IN) :: lim_fac
336 !OUTPUT PARAMETERS:
337  real , INTENT(OUT) :: flux(is:ie+1,jfirst:jlast)
338 ! Local
339  real, dimension(is-1:ie+1):: bl, br, b0
340  real:: q1(isd:ied)
341  real, dimension(is:ie+1):: fx0, fx1, xt1
342  logical, dimension(is-1:ie+1):: smt5, smt6
343  logical, dimension(is:ie+1):: hi5, hi6
344  real al(is-1:ie+2)
345  real dm(is-2:ie+2)
346  real dq(is-3:ie+2)
347  integer:: i, j, ie3, is1, ie1, mord
348  real:: x0, x1, xt, qtmp, pmp_1, lac_1, pmp_2, lac_2
349 
350  if ( .not. bounded_domain .and. grid_type<3 ) then
351  is1 = max(3,is-1); ie3 = min(npx-2,ie+2)
352  ie1 = min(npx-3,ie+1)
353  else
354  is1 = is-1; ie3 = ie+2
355  ie1 = ie+1
356  end if
357  mord = abs(iord)
358 
359  do 666 j=jfirst,jlast
360 
361  do i=isd, ied
362  q1(i) = q(i,j)
363  enddo
364 
365  if ( iord < 8 ) then
366 ! ord = 2: perfectly linear ppm scheme
367 ! Diffusivity: ord2 < ord5 < ord3 < ord4 < ord6
368 
369  do i=is1, ie3
370  al(i) = p1*(q1(i-1)+q1(i)) + p2*(q1(i-2)+q1(i+1))
371  enddo
372 
373  if ( .not. bounded_domain .and. grid_type<3 ) then
374  if ( is==1 ) then
375  al(0) = c1*q1(-2) + c2*q1(-1) + c3*q1(0)
376  al(1) = 0.5*(((2.*dxa(0,j)+dxa(-1,j))*q1(0)-dxa(0,j)*q1(-1))/(dxa(-1,j)+dxa(0,j)) &
377  + ((2.*dxa(1,j)+dxa( 2,j))*q1(1)-dxa(1,j)*q1( 2))/(dxa(1, j)+dxa(2,j)))
378  al(2) = c3*q1(1) + c2*q1(2) +c1*q1(3)
379  endif
380  if ( (ie+1)==npx ) then
381  al(npx-1) = c1*q1(npx-3) + c2*q1(npx-2) + c3*q1(npx-1)
382  al(npx) = 0.5*(((2.*dxa(npx-1,j)+dxa(npx-2,j))*q1(npx-1)-dxa(npx-1,j)*q1(npx-2))/(dxa(npx-2,j)+dxa(npx-1,j)) &
383  + ((2.*dxa(npx, j)+dxa(npx+1,j))*q1(npx )-dxa(npx, j)*q1(npx+1))/(dxa(npx, j)+dxa(npx+1,j)))
384  al(npx+1) = c3*q1(npx) + c2*q1(npx+1) + c1*q1(npx+2)
385  endif
386  endif
387 
388  if ( iord<0 ) then
389  do i=is-1, ie+2
390  al(i) = max(0., al(i))
391  enddo
392  endif
393 
394  if ( mord==1 ) then ! perfectly linear scheme
395  do i=is-1,ie+1
396  bl(i) = al(i) - q1(i)
397  br(i) = al(i+1) - q1(i)
398  b0(i) = bl(i) + br(i)
399  smt5(i) = abs(lim_fac*b0(i)) < abs(bl(i)-br(i))
400  enddo
401 !DEC$ VECTOR ALWAYS
402  do i=is,ie+1
403  if ( c(i,j) > 0. ) then
404  fx1(i) = (1.-c(i,j))*(br(i-1) - c(i,j)*b0(i-1))
405  flux(i,j) = q1(i-1)
406  else
407  fx1(i) = (1.+c(i,j))*(bl(i) + c(i,j)*b0(i))
408  flux(i,j) = q1(i)
409  endif
410  if (smt5(i-1).or.smt5(i)) flux(i,j) = flux(i,j) + fx1(i)
411  enddo
412 
413  elseif ( mord==2 ) then ! perfectly linear scheme
414 
415 !DEC$ VECTOR ALWAYS
416  do i=is,ie+1
417  xt = c(i,j)
418  if ( xt > 0. ) then
419  qtmp = q1(i-1)
420  flux(i,j) = qtmp + (1.-xt)*(al(i)-qtmp-xt*(al(i-1)+al(i)-(qtmp+qtmp)))
421  else
422  qtmp = q1(i)
423  flux(i,j) = qtmp + (1.+xt)*(al(i)-qtmp+xt*(al(i)+al(i+1)-(qtmp+qtmp)))
424  endif
425 ! x0 = sign(dim(xt, 0.), 1.)
426 ! x1 = sign(dim(0., xt), 1.)
427 ! flux(i,j) = x0*(q1(i-1)+(1.-xt)*(al(i)-qtmp-xt*(al(i-1)+al(i)-(qtmp+qtmp)))) &
428 ! + x1*(q1(i) +(1.+xt)*(al(i)-qtmp+xt*(al(i)+al(i+1)-(qtmp+qtmp))))
429  enddo
430 
431  elseif ( mord==3 ) then
432 
433  do i=is-1,ie+1
434  bl(i) = al(i) - q1(i)
435  br(i) = al(i+1) - q1(i)
436  b0(i) = bl(i) + br(i)
437  x0 = abs(b0(i))
438  xt = abs(bl(i)-br(i))
439  smt5(i) = x0 < xt
440  smt6(i) = 3.*x0 < xt
441  enddo
442  do i=is,ie+1
443  fx1(i) = 0.
444  xt1(i) = c(i,j)
445  hi5(i) = smt5(i-1) .and. smt5(i) ! more diffusive
446  hi6(i) = smt6(i-1) .or. smt6(i)
447  enddo
448  do i=is,ie+1
449  if ( xt1(i) > 0. ) then
450  if ( hi6(i) ) then
451  fx1(i) = br(i-1) - xt1(i)*b0(i-1)
452  elseif ( hi5(i) ) then ! 2nd order, piece-wise linear
453  fx1(i) = sign(min(abs(bl(i-1)),abs(br(i-1))), br(i-1))
454  endif
455  flux(i,j) = q1(i-1) + (1.-xt1(i))*fx1(i)
456  else
457  if ( hi6(i) ) then
458  fx1(i) = bl(i) + xt1(i)*b0(i)
459  elseif ( hi5(i) ) then ! 2nd order, piece-wise linear
460  fx1(i) = sign(min(abs(bl(i)), abs(br(i))), bl(i))
461  endif
462  flux(i,j) = q1(i) + (1.+xt1(i))*fx1(i)
463  endif
464  enddo
465 
466  elseif ( mord==4 ) then
467 
468  do i=is-1,ie+1
469  bl(i) = al(i) - q1(i)
470  br(i) = al(i+1) - q1(i)
471  b0(i) = bl(i) + br(i)
472  x0 = abs(b0(i))
473  xt = abs(bl(i)-br(i))
474  smt5(i) = x0 < xt
475  smt6(i) = 3.*x0 < xt
476  enddo
477  do i=is,ie+1
478  xt1(i) = c(i,j)
479  hi5(i) = smt5(i-1) .and. smt5(i) ! more diffusive
480  hi6(i) = smt6(i-1) .or. smt6(i)
481  hi5(i) = hi5(i) .or. hi6(i)
482  enddo
483 !DEC$ VECTOR ALWAYS
484  do i=is,ie+1
485  if ( xt1(i) > 0. ) then
486  fx1(i) = (1.-xt1(i))*(br(i-1) - xt1(i)*b0(i-1))
487  flux(i,j) = q1(i-1)
488  else
489  fx1(i) = (1.+xt1(i))*(bl(i) + xt1(i)*b0(i))
490  flux(i,j) = q1(i)
491  endif
492  if ( hi5(i) ) flux(i,j) = flux(i,j) + fx1(i)
493  enddo
494 
495  else
496 
497  if ( mord==5 ) then
498  do i=is-1,ie+1
499  bl(i) = al(i) - q1(i)
500  br(i) = al(i+1) - q1(i)
501  b0(i) = bl(i) + br(i)
502  smt5(i) = bl(i)*br(i) < 0.
503  enddo
504  else
505  do i=is-1,ie+1
506  bl(i) = al(i) - q1(i)
507  br(i) = al(i+1) - q1(i)
508  b0(i) = bl(i) + br(i)
509  smt5(i) = 3.*abs(b0(i)) < abs(bl(i)-br(i))
510  enddo
511  endif
512 
513 !DEC$ VECTOR ALWAYS
514  do i=is,ie+1
515  if ( c(i,j) > 0. ) then
516  fx1(i) = (1.-c(i,j))*(br(i-1) - c(i,j)*b0(i-1))
517  flux(i,j) = q1(i-1)
518  else
519  fx1(i) = (1.+c(i,j))*(bl(i) + c(i,j)*b0(i))
520  flux(i,j) = q1(i)
521  endif
522  if (smt5(i-1).or.smt5(i)) flux(i,j) = flux(i,j) + fx1(i)
523  enddo
524 
525  endif
526  goto 666
527 
528  else
529 
530 ! Monotonic constraints:
531 ! ord = 8: PPM with Lin's PPM fast monotone constraint
532 ! ord = 10: PPM with Lin's modification of Huynh 2nd constraint
533 ! ord = 13: 10 plus positive definite constraint
534 
535  do i=is-2,ie+2
536  xt = 0.25*(q1(i+1) - q1(i-1))
537  dm(i) = sign(min(abs(xt), max(q1(i-1), q1(i), q1(i+1)) - q1(i), &
538  q1(i) - min(q1(i-1), q1(i), q1(i+1))), xt)
539  enddo
540  do i=is1,ie1+1
541  al(i) = 0.5*(q1(i-1)+q1(i)) + r3*(dm(i-1)-dm(i))
542  enddo
543 
544  if ( iord==8 ) then
545  do i=is1, ie1
546  xt = 2.*dm(i)
547  bl(i) = -sign(min(abs(xt), abs(al(i )-q1(i))), xt)
548  br(i) = sign(min(abs(xt), abs(al(i+1)-q1(i))), xt)
549  enddo
550  elseif ( iord==11 ) then
551 ! This is emulation of 2nd van Leer scheme using PPM codes
552  do i=is1, ie1
553  xt = ppm_fac*dm(i)
554  bl(i) = -sign(min(abs(xt), abs(al(i )-q1(i))), xt)
555  br(i) = sign(min(abs(xt), abs(al(i+1)-q1(i))), xt)
556  enddo
557  else
558  do i=is1-2, ie1+1
559  dq(i) = 2.*(q1(i+1) - q1(i))
560  enddo
561  do i=is1, ie1
562  bl(i) = al(i ) - q1(i)
563  br(i) = al(i+1) - q1(i)
564  if ( abs(dm(i-1))+abs(dm(i))+abs(dm(i+1)) < near_zero ) then
565  bl(i) = 0.
566  br(i) = 0.
567  elseif( abs(3.*(bl(i)+br(i))) > abs(bl(i)-br(i)) ) then
568  pmp_2 = dq(i-1)
569  lac_2 = pmp_2 - 0.75*dq(i-2)
570  br(i) = min( max(0., pmp_2, lac_2), max(br(i), min(0., pmp_2, lac_2)) )
571  pmp_1 = -dq(i)
572  lac_1 = pmp_1 + 0.75*dq(i+1)
573  bl(i) = min( max(0., pmp_1, lac_1), max(bl(i), min(0., pmp_1, lac_1)) )
574  endif
575  enddo
576  endif
577 ! Positive definite constraint:
578  if(iord==9 .or. iord==13) call pert_ppm(ie1-is1+1, q1(is1), bl(is1), br(is1), 0)
579 
580  if (.not. bounded_domain .and. grid_type<3) then
581  if ( is==1 ) then
582  bl(0) = s14*dm(-1) + s11*(q1(-1)-q1(0))
583 
584  xt = 0.5*(((2.*dxa(0,j)+dxa(-1,j))*q1(0)-dxa(0,j)*q1(-1))/(dxa(-1,j)+dxa(0,j)) &
585  + ((2.*dxa(1,j)+dxa( 2,j))*q1(1)-dxa(1,j)*q1( 2))/(dxa(1, j)+dxa(2,j)))
586 ! if ( iord==8 .or. iord==10 ) then
587  xt = max(xt, min(q1(-1),q1(0),q1(1),q1(2)))
588  xt = min(xt, max(q1(-1),q1(0),q1(1),q1(2)))
589 ! endif
590  br(0) = xt - q1(0)
591  bl(1) = xt - q1(1)
592  xt = s15*q1(1) + s11*q1(2) - s14*dm(2)
593  br(1) = xt - q1(1)
594  bl(2) = xt - q1(2)
595 
596  br(2) = al(3) - q1(2)
597  call pert_ppm(3, q1(0), bl(0), br(0), 1)
598  endif
599  if ( (ie+1)==npx ) then
600  bl(npx-2) = al(npx-2) - q1(npx-2)
601 
602  xt = s15*q1(npx-1) + s11*q1(npx-2) + s14*dm(npx-2)
603  br(npx-2) = xt - q1(npx-2)
604  bl(npx-1) = xt - q1(npx-1)
605 
606  xt = 0.5*(((2.*dxa(npx-1,j)+dxa(npx-2,j))*q1(npx-1)-dxa(npx-1,j)*q1(npx-2))/(dxa(npx-2,j)+dxa(npx-1,j)) &
607  + ((2.*dxa(npx, j)+dxa(npx+1,j))*q1(npx )-dxa(npx, j)*q1(npx+1))/(dxa(npx, j)+dxa(npx+1,j)))
608 ! if ( iord==8 .or. iord==10 ) then
609  xt = max(xt, min(q1(npx-2),q1(npx-1),q1(npx),q1(npx+1)))
610  xt = min(xt, max(q1(npx-2),q1(npx-1),q1(npx),q1(npx+1)))
611 ! endif
612  br(npx-1) = xt - q1(npx-1)
613  bl(npx ) = xt - q1(npx )
614 
615  br(npx) = s11*(q1(npx+1)-q1(npx)) - s14*dm(npx+1)
616  call pert_ppm(3, q1(npx-2), bl(npx-2), br(npx-2), 1)
617  endif
618  endif
619 
620  endif
621 
622  do i=is,ie+1
623  if( c(i,j)>0. ) then
624  flux(i,j) = q1(i-1) + (1.-c(i,j))*(br(i-1)-c(i,j)*(bl(i-1)+br(i-1)))
625  else
626  flux(i,j) = q1(i ) + (1.+c(i,j))*(bl(i )+c(i,j)*(bl(i)+br(i)))
627  endif
628  enddo
629 
630 666 continue
631  end subroutine xppm
632 
633 
634  subroutine yppm(flux, q, c, jord, ifirst,ilast, isd,ied, js,je,jsd,jed, npx, npy, dya, bounded_domain, grid_type, lim_fac)
635  integer, INTENT(IN) :: ifirst,ilast
636  integer, INTENT(IN) :: isd,ied, js,je,jsd,jed
637  integer, INTENT(IN) :: jord
638  integer, INTENT(IN) :: npx, npy
639  real , INTENT(IN) :: q(ifirst:ilast,jsd:jed)
640  real , intent(in) :: c(isd:ied,js:je+1 )
641  real , INTENT(OUT):: flux(ifirst:ilast,js:je+1)
642  real , intent(IN) :: dya(isd:ied,jsd:jed)
643  logical, intent(IN) :: bounded_domain
644  integer, intent(IN) :: grid_type
645  real , intent(IN) :: lim_fac
646 ! Local:
647  real:: dm(ifirst:ilast,js-2:je+2)
648  real:: al(ifirst:ilast,js-1:je+2)
649  real, dimension(ifirst:ilast,js-1:je+1):: bl, br, b0
650  real:: dq(ifirst:ilast,js-3:je+2)
651  real, dimension(ifirst:ilast):: fx0, fx1, xt1
652  logical, dimension(ifirst:ilast,js-1:je+1):: smt5, smt6
653  logical, dimension(ifirst:ilast):: hi5, hi6
654  real:: x0, xt, qtmp, pmp_1, lac_1, pmp_2, lac_2, r1
655  integer:: i, j, js1, je3, je1, mord
656 
657  if ( .not.bounded_domain .and. grid_type < 3 ) then
658 ! Cubed-sphere:
659  js1 = max(3,js-1); je3 = min(npy-2,je+2)
660  je1 = min(npy-3,je+1)
661  else
662 ! Bounded_domain grid OR Doubly periodic domain:
663  js1 = js-1; je3 = je+2
664  je1 = je+1
665  endif
666 
667  mord = abs(jord)
668 
669 if ( jord < 8 ) then
670 
671  do j=js1, je3
672  do i=ifirst,ilast
673  al(i,j) = p1*(q(i,j-1)+q(i,j)) + p2*(q(i,j-2)+q(i,j+1))
674  enddo
675  enddo
676 
677  if ( .not. bounded_domain .and. grid_type<3 ) then
678  if( js==1 ) then
679  do i=ifirst,ilast
680  al(i,0) = c1*q(i,-2) + c2*q(i,-1) + c3*q(i,0)
681  al(i,1) = 0.5*(((2.*dya(i,0)+dya(i,-1))*q(i,0)-dya(i,0)*q(i,-1))/(dya(i,-1)+dya(i,0)) &
682  + ((2.*dya(i,1)+dya(i,2))*q(i,1)-dya(i,1)*q(i,2))/(dya(i,1)+dya(i,2)))
683  al(i,2) = c3*q(i,1) + c2*q(i,2) + c1*q(i,3)
684  enddo
685  endif
686  if( (je+1)==npy ) then
687  do i=ifirst,ilast
688  al(i,npy-1) = c1*q(i,npy-3) + c2*q(i,npy-2) + c3*q(i,npy-1)
689  al(i,npy) = 0.5*(((2.*dya(i,npy-1)+dya(i,npy-2))*q(i,npy-1)-dya(i,npy-1)*q(i,npy-2))/(dya(i,npy-2)+dya(i,npy-1)) &
690  + ((2.*dya(i,npy)+dya(i,npy+1))*q(i,npy)-dya(i,npy)*q(i,npy+1))/(dya(i,npy)+dya(i,npy+1)))
691  al(i,npy+1) = c3*q(i,npy) + c2*q(i,npy+1) + c1*q(i,npy+2)
692  enddo
693  endif
694  endif
695 
696  if ( jord<0 ) then
697  do j=js-1, je+2
698  do i=ifirst,ilast
699  al(i,j) = max(0., al(i,j))
700  enddo
701  enddo
702  endif
703 
704  if ( mord==1 ) then
705  do j=js-1,je+1
706  do i=ifirst,ilast
707  bl(i,j) = al(i,j ) - q(i,j)
708  br(i,j) = al(i,j+1) - q(i,j)
709  b0(i,j) = bl(i,j) + br(i,j)
710  smt5(i,j) = abs(lim_fac*b0(i,j)) < abs(bl(i,j)-br(i,j))
711  enddo
712  enddo
713  do j=js,je+1
714 !DEC$ VECTOR ALWAYS
715  do i=ifirst,ilast
716  if ( c(i,j) > 0. ) then
717  fx1(i) = (1.-c(i,j))*(br(i,j-1) - c(i,j)*b0(i,j-1))
718  flux(i,j) = q(i,j-1)
719  else
720  fx1(i) = (1.+c(i,j))*(bl(i,j) + c(i,j)*b0(i,j))
721  flux(i,j) = q(i,j)
722  endif
723  if (smt5(i,j-1).or.smt5(i,j)) flux(i,j) = flux(i,j) + fx1(i)
724  enddo
725  enddo
726 
727  elseif ( mord==2 ) then ! Perfectly linear scheme
728 ! Diffusivity: ord2 < ord5 < ord3 < ord4 < ord6 < ord7
729 
730  do j=js,je+1
731 !DEC$ VECTOR ALWAYS
732  do i=ifirst,ilast
733  xt = c(i,j)
734  if ( xt > 0. ) then
735  qtmp = q(i,j-1)
736  flux(i,j) = qtmp + (1.-xt)*(al(i,j)-qtmp-xt*(al(i,j-1)+al(i,j)-(qtmp+qtmp)))
737  else
738  qtmp = q(i,j)
739  flux(i,j) = qtmp + (1.+xt)*(al(i,j)-qtmp+xt*(al(i,j)+al(i,j+1)-(qtmp+qtmp)))
740  endif
741  enddo
742  enddo
743 
744  elseif ( mord==3 ) then
745 
746  do j=js-1,je+1
747  do i=ifirst,ilast
748  bl(i,j) = al(i,j ) - q(i,j)
749  br(i,j) = al(i,j+1) - q(i,j)
750  b0(i,j) = bl(i,j) + br(i,j)
751  x0 = abs(b0(i,j))
752  xt = abs(bl(i,j)-br(i,j))
753  smt5(i,j) = x0 < xt
754  smt6(i,j) = 3.*x0 < xt
755  enddo
756  enddo
757  do j=js,je+1
758  do i=ifirst,ilast
759  fx1(i) = 0.
760  xt1(i) = c(i,j)
761  hi5(i) = smt5(i,j-1) .and. smt5(i,j)
762  hi6(i) = smt6(i,j-1) .or. smt6(i,j)
763  enddo
764  do i=ifirst,ilast
765  if ( xt1(i) > 0. ) then
766  if( hi6(i) ) then
767  fx1(i) = br(i,j-1) - xt1(i)*b0(i,j-1)
768  elseif ( hi5(i) ) then ! both up-downwind sides are noisy; 2nd order, piece-wise linear
769  fx1(i) = sign(min(abs(bl(i,j-1)),abs(br(i,j-1))),br(i,j-1))
770  endif
771  flux(i,j) = q(i,j-1) + (1.-xt1(i))*fx1(i)
772  else
773  if( hi6(i) ) then
774  fx1(i) = bl(i,j) + xt1(i)*b0(i,j)
775  elseif ( hi5(i) ) then ! both up-downwind sides are noisy; 2nd order, piece-wise linear
776  fx1(i) = sign(min(abs(bl(i,j)),abs(br(i,j))), bl(i,j))
777  endif
778  flux(i,j) = q(i,j) + (1.+xt1(i))*fx1(i)
779  endif
780  enddo
781  enddo
782 
783  elseif ( mord==4 ) then
784 
785  do j=js-1,je+1
786  do i=ifirst,ilast
787  bl(i,j) = al(i,j ) - q(i,j)
788  br(i,j) = al(i,j+1) - q(i,j)
789  b0(i,j) = bl(i,j) + br(i,j)
790  x0 = abs(b0(i,j))
791  xt = abs(bl(i,j)-br(i,j))
792  smt5(i,j) = x0 < xt
793  smt6(i,j) = 3.*x0 < xt
794  enddo
795  enddo
796  do j=js,je+1
797  do i=ifirst,ilast
798  xt1(i) = c(i,j)
799  hi5(i) = smt5(i,j-1) .and. smt5(i,j)
800  hi6(i) = smt6(i,j-1) .or. smt6(i,j)
801  hi5(i) = hi5(i) .or. hi6(i)
802  enddo
803 !DEC$ VECTOR ALWAYS
804  do i=ifirst,ilast
805  if ( xt1(i) > 0. ) then
806  fx1(i) = (1.-xt1(i))*(br(i,j-1) - xt1(i)*b0(i,j-1))
807  flux(i,j) = q(i,j-1)
808  else
809  fx1(i) = (1.+xt1(i))*(bl(i,j) + xt1(i)*b0(i,j))
810  flux(i,j) = q(i,j)
811  endif
812  if ( hi5(i) ) flux(i,j) = flux(i,j) + fx1(i)
813  enddo
814  enddo
815 
816  else ! mord=5,6,7
817  if ( mord==5 ) then
818  do j=js-1,je+1
819  do i=ifirst,ilast
820  bl(i,j) = al(i,j ) - q(i,j)
821  br(i,j) = al(i,j+1) - q(i,j)
822  b0(i,j) = bl(i,j) + br(i,j)
823  smt5(i,j) = bl(i,j)*br(i,j) < 0.
824  enddo
825  enddo
826  else
827  do j=js-1,je+1
828  do i=ifirst,ilast
829  bl(i,j) = al(i,j ) - q(i,j)
830  br(i,j) = al(i,j+1) - q(i,j)
831  b0(i,j) = bl(i,j) + br(i,j)
832  smt5(i,j) = 3.*abs(b0(i,j)) < abs(bl(i,j)-br(i,j))
833  enddo
834  enddo
835  endif
836 
837  do j=js,je+1
838 !DEC$ VECTOR ALWAYS
839  do i=ifirst,ilast
840  if ( c(i,j) > 0. ) then
841  fx1(i) = (1.-c(i,j))*(br(i,j-1) - c(i,j)*b0(i,j-1))
842  flux(i,j) = q(i,j-1)
843  else
844  fx1(i) = (1.+c(i,j))*(bl(i,j) + c(i,j)*b0(i,j))
845  flux(i,j) = q(i,j)
846  endif
847  if (smt5(i,j-1).or.smt5(i,j)) flux(i,j) = flux(i,j) + fx1(i)
848  enddo
849  enddo
850 
851  endif
852  return
853 
854 else
855 ! Monotonic constraints:
856 ! ord = 8: PPM with Lin's PPM fast monotone constraint
857 ! ord > 8: PPM with Lin's modification of Huynh 2nd constraint
858 
859  do j=js-2,je+2
860  do i=ifirst,ilast
861  xt = 0.25*(q(i,j+1) - q(i,j-1))
862  dm(i,j) = sign(min(abs(xt), max(q(i,j-1), q(i,j), q(i,j+1)) - q(i,j), &
863  q(i,j) - min(q(i,j-1), q(i,j), q(i,j+1))), xt)
864  enddo
865  enddo
866  do j=js1,je1+1
867  do i=ifirst,ilast
868  al(i,j) = 0.5*(q(i,j-1)+q(i,j)) + r3*(dm(i,j-1) - dm(i,j))
869  enddo
870  enddo
871 
872  if ( jord==8 ) then
873  do j=js1,je1
874  do i=ifirst,ilast
875  xt = 2.*dm(i,j)
876  bl(i,j) = -sign(min(abs(xt), abs(al(i,j)-q(i,j))), xt)
877  br(i,j) = sign(min(abs(xt), abs(al(i,j+1)-q(i,j))), xt)
878  enddo
879  enddo
880  elseif ( jord==11 ) then
881  do j=js1,je1
882  do i=ifirst,ilast
883  xt = ppm_fac*dm(i,j)
884  bl(i,j) = -sign(min(abs(xt), abs(al(i,j)-q(i,j))), xt)
885  br(i,j) = sign(min(abs(xt), abs(al(i,j+1)-q(i,j))), xt)
886  enddo
887  enddo
888  else
889  do j=js1-2,je1+1
890  do i=ifirst,ilast
891  dq(i,j) = 2.*(q(i,j+1) - q(i,j))
892  enddo
893  enddo
894  do j=js1,je1
895  do i=ifirst,ilast
896  bl(i,j) = al(i,j ) - q(i,j)
897  br(i,j) = al(i,j+1) - q(i,j)
898  if ( abs(dm(i,j-1))+abs(dm(i,j))+abs(dm(i,j+1)) < near_zero ) then
899  bl(i,j) = 0.
900  br(i,j) = 0.
901  elseif( abs(3.*(bl(i,j)+br(i,j))) > abs(bl(i,j)-br(i,j)) ) then
902  pmp_2 = dq(i,j-1)
903  lac_2 = pmp_2 - 0.75*dq(i,j-2)
904  br(i,j) = min(max(0.,pmp_2,lac_2), max(br(i,j), min(0.,pmp_2,lac_2)))
905  pmp_1 = -dq(i,j)
906  lac_1 = pmp_1 + 0.75*dq(i,j+1)
907  bl(i,j) = min(max(0.,pmp_1,lac_1), max(bl(i,j), min(0.,pmp_1,lac_1)))
908  endif
909  enddo
910  enddo
911  endif
912  if ( jord==9 .or. jord==13 ) then
913 ! Positive definite constraint:
914  do j=js1,je1
915  call pert_ppm(ilast-ifirst+1, q(ifirst,j), bl(ifirst,j), br(ifirst,j), 0)
916  enddo
917  endif
918 
919  if (.not. bounded_domain .and. grid_type<3) then
920  if( js==1 ) then
921  do i=ifirst,ilast
922  bl(i,0) = s14*dm(i,-1) + s11*(q(i,-1)-q(i,0))
923 
924  xt = 0.5*(((2.*dya(i,0)+dya(i,-1))*q(i,0)-dya(i,0)*q(i,-1))/(dya(i,-1)+dya(i,0)) &
925  + ((2.*dya(i,1)+dya(i,2))*q(i,1)-dya(i,1)*q(i,2))/(dya(i,1)+dya(i,2)))
926 ! if ( jord==8 .or. jord==10 ) then
927  xt = max(xt, min(q(i,-1),q(i,0),q(i,1),q(i,2)))
928  xt = min(xt, max(q(i,-1),q(i,0),q(i,1),q(i,2)))
929 ! endif
930  br(i,0) = xt - q(i,0)
931  bl(i,1) = xt - q(i,1)
932 
933  xt = s15*q(i,1) + s11*q(i,2) - s14*dm(i,2)
934  br(i,1) = xt - q(i,1)
935  bl(i,2) = xt - q(i,2)
936 
937  br(i,2) = al(i,3) - q(i,2)
938  enddo
939  call pert_ppm(3*(ilast-ifirst+1), q(ifirst,0), bl(ifirst,0), br(ifirst,0), 1)
940  endif
941  if( (je+1)==npy ) then
942  do i=ifirst,ilast
943  bl(i,npy-2) = al(i,npy-2) - q(i,npy-2)
944 
945  xt = s15*q(i,npy-1) + s11*q(i,npy-2) + s14*dm(i,npy-2)
946  br(i,npy-2) = xt - q(i,npy-2)
947  bl(i,npy-1) = xt - q(i,npy-1)
948 
949  xt = 0.5*(((2.*dya(i,npy-1)+dya(i,npy-2))*q(i,npy-1)-dya(i,npy-1)*q(i,npy-2))/(dya(i,npy-2)+dya(i,npy-1)) &
950  + ((2.*dya(i,npy)+dya(i,npy+1))*q(i,npy)-dya(i,npy)*q(i,npy+1))/(dya(i,npy)+dya(i,npy+1)))
951 ! if ( jord==8 .or. jord==10 ) then
952  xt = max(xt, min(q(i,npy-2),q(i,npy-1),q(i,npy),q(i,npy+1)))
953  xt = min(xt, max(q(i,npy-2),q(i,npy-1),q(i,npy),q(i,npy+1)))
954 ! endif
955  br(i,npy-1) = xt - q(i,npy-1)
956  bl(i,npy ) = xt - q(i,npy)
957 
958  br(i,npy) = s11*(q(i,npy+1)-q(i,npy)) - s14*dm(i,npy+1)
959  enddo
960  call pert_ppm(3*(ilast-ifirst+1), q(ifirst,npy-2), bl(ifirst,npy-2), br(ifirst,npy-2), 1)
961  endif
962  end if
963 
964 endif
965 
966  do j=js,je+1
967  do i=ifirst,ilast
968  if( c(i,j)>0. ) then
969  flux(i,j) = q(i,j-1) + (1.-c(i,j))*(br(i,j-1)-c(i,j)*(bl(i,j-1)+br(i,j-1)))
970  else
971  flux(i,j) = q(i,j ) + (1.+c(i,j))*(bl(i,j )+c(i,j)*(bl(i,j)+br(i,j)))
972  endif
973  enddo
974  enddo
975  end subroutine yppm
976 
977 
978 
979  subroutine mp_ghost_ew(im, jm, km, nq, ifirst, ilast, jfirst, jlast, &
980  kfirst, klast, ng_w, ng_e, ng_s, ng_n, q_ghst, q)
981 !
982 ! !INPUT PARAMETERS:
983  integer, intent(in):: im, jm, km, nq
984  integer, intent(in):: ifirst, ilast
985  integer, intent(in):: jfirst, jlast
986  integer, intent(in):: kfirst, klast
987  integer, intent(in):: ng_e
988  integer, intent(in):: ng_w
989  integer, intent(in):: ng_s
990  integer, intent(in):: ng_n
991  real, intent(inout):: q_ghst(ifirst-ng_w:ilast+ng_e,jfirst-ng_s:jlast+ng_n,kfirst:klast,nq)
992  real, optional, intent(in):: q(ifirst:ilast,jfirst:jlast,kfirst:klast,nq)
993 !
994 ! !DESCRIPTION:
995 !
996 ! Ghost 4d east/west
997 !
998 ! !REVISION HISTORY:
999 ! 2005.08.22 Putman
1000 !
1001 !EOP
1002 !------------------------------------------------------------------------------
1003 !BOC
1004  integer :: i,j,k,n
1005 
1006  if (present(q)) then
1007  q_ghst(ifirst:ilast,jfirst:jlast,kfirst:klast,1:nq) = &
1008  q(ifirst:ilast,jfirst:jlast,kfirst:klast,1:nq)
1009  endif
1010 
1011 ! Assume Periodicity in X-dir and not overlapping
1012  do n=1,nq
1013  do k=kfirst,klast
1014  do j=jfirst-ng_s,jlast+ng_n
1015  do i=1, ng_w
1016  q_ghst(ifirst-i,j,k,n) = q_ghst(ilast-i+1,j,k,n)
1017  enddo
1018  do i=1, ng_e
1019  q_ghst(ilast+i,j,k,n) = q_ghst(ifirst+i-1,j,k,n)
1020  enddo
1021  enddo
1022  enddo
1023  enddo
1024 
1025  end subroutine mp_ghost_ew
1026 
1027 
1028 
1029  subroutine pert_ppm(im, a0, al, ar, iv)
1030  integer, intent(in):: im
1031  integer, intent(in):: iv
1032  real, intent(in) :: a0(im)
1033  real, intent(inout):: al(im), ar(im)
1034 ! Local:
1035  real a4, da1, da2, a6da, fmin
1036  integer i
1037  real, parameter:: r12 = 1./12.
1038 
1039 !-----------------------------------
1040 ! Optimized PPM in perturbation form:
1041 !-----------------------------------
1042 
1043  if ( iv==0 ) then
1044 ! Positive definite constraint
1045  do i=1,im
1046  if ( a0(i) <= 0. ) then
1047  al(i) = 0.
1048  ar(i) = 0.
1049  else
1050  a4 = -3.*(ar(i) + al(i))
1051  da1 = ar(i) - al(i)
1052  if( abs(da1) < -a4 ) then
1053  fmin = a0(i) + 0.25/a4*da1**2 + a4*r12
1054  if( fmin < 0. ) then
1055  if( ar(i)>0. .and. al(i)>0. ) then
1056  ar(i) = 0.
1057  al(i) = 0.
1058  elseif( da1 > 0. ) then
1059  ar(i) = -2.*al(i)
1060  else
1061  al(i) = -2.*ar(i)
1062  endif
1063  endif
1064  endif
1065  endif
1066  enddo
1067  else
1068 ! Standard PPM constraint
1069  do i=1,im
1070  if ( al(i)*ar(i) < 0. ) then
1071  da1 = al(i) - ar(i)
1072  da2 = da1**2
1073  a6da = 3.*(al(i)+ar(i))*da1
1074 ! abs(a6da) > da2 --> 3.*abs(al+ar) > abs(al-ar)
1075  if( a6da < -da2 ) then
1076  ar(i) = -2.*al(i)
1077  elseif( a6da > da2 ) then
1078  al(i) = -2.*ar(i)
1079  endif
1080  else
1081 ! effect of dm=0 included here
1082  al(i) = 0.
1083  ar(i) = 0.
1084  endif
1085  enddo
1086  endif
1087 
1088  end subroutine pert_ppm
1089 
1090 
1091  subroutine deln_flux(nord,is,ie,js,je, npx, npy, damp, q, fx, fy, gridstruct, bd, mass )
1092 ! Del-n damping for the cell-mean values (A grid)
1093 !------------------
1098 !------------------
1099  type(fv_grid_bounds_type), intent(IN) :: bd
1100  integer, intent(in):: nord
1101  integer, intent(in):: is,ie,js,je, npx, npy
1102  real, intent(in):: damp
1103  real, intent(in):: q(bd%isd:bd%ied, bd%jsd:bd%jed) ! q ghosted on input
1104  type(fv_grid_type), intent(IN), target :: gridstruct
1105  real, optional, intent(in):: mass(bd%isd:bd%ied, bd%jsd:bd%jed) ! q ghosted on input
1106 ! diffusive fluxes:
1107  real, intent(inout):: fx(bd%is:bd%ie+1,bd%js:bd%je), fy(bd%is:bd%ie,bd%js:bd%je+1)
1108 ! local:
1109  real fx2(bd%isd:bd%ied+1,bd%jsd:bd%jed), fy2(bd%isd:bd%ied,bd%jsd:bd%jed+1)
1110  real d2(bd%isd:bd%ied,bd%jsd:bd%jed)
1111  real damp2
1112  integer i,j, n, nt, i1, i2, j1, j2
1113 
1114 #ifdef USE_SG
1115  real, pointer, dimension(:,:) :: dx, dy, rdxc, rdyc
1116  real, pointer, dimension(:,:,:) :: sin_sg
1117  dx => gridstruct%dx
1118  dy => gridstruct%dy
1119  rdxc => gridstruct%rdxc
1120  rdyc => gridstruct%rdyc
1121  sin_sg => gridstruct%sin_sg
1122 #endif
1123 
1124  i1 = is-1-nord; i2 = ie+1+nord
1125  j1 = js-1-nord; j2 = je+1+nord
1126 
1127  if ( .not. present(mass) ) then
1128  do j=j1, j2
1129  do i=i1,i2
1130  d2(i,j) = damp*q(i,j)
1131  enddo
1132  enddo
1133  else
1134  do j=j1, j2
1135  do i=i1,i2
1136  d2(i,j) = q(i,j)
1137  enddo
1138  enddo
1139  endif
1140 
1141  if( nord>0 ) call copy_corners(d2, npx, npy, 1, gridstruct%bounded_domain, bd, &
1142  gridstruct%sw_corner, gridstruct%se_corner, gridstruct%nw_corner, gridstruct%ne_corner)
1143 
1144  do j=js-nord,je+nord
1145  do i=is-nord,ie+nord+1
1146 #ifdef USE_SG
1147  fx2(i,j) = 0.5*(sin_sg(i-1,j,3)+sin_sg(i,j,1))*dy(i,j)*(d2(i-1,j)-d2(i,j))*rdxc(i,j)
1148 #else
1149  fx2(i,j) = gridstruct%del6_v(i,j)*(d2(i-1,j)-d2(i,j))
1150 #endif
1151  enddo
1152  enddo
1153 
1154  if( nord>0 ) call copy_corners(d2, npx, npy, 2, gridstruct%bounded_domain, bd, &
1155  gridstruct%sw_corner, gridstruct%se_corner, gridstruct%nw_corner, gridstruct%ne_corner)
1156  do j=js-nord,je+nord+1
1157  do i=is-nord,ie+nord
1158 #ifdef USE_SG
1159  fy2(i,j) = 0.5*(sin_sg(i,j-1,4)+sin_sg(i,j,2))*dx(i,j)*(d2(i,j-1)-d2(i,j))*rdyc(i,j)
1160 #else
1161  fy2(i,j) = gridstruct%del6_u(i,j)*(d2(i,j-1)-d2(i,j))
1162 #endif
1163  enddo
1164  enddo
1165 
1166  if ( nord>0 ) then
1167 
1168 !----------
1169 ! high-order
1170 !----------
1171 
1172  do n=1, nord
1173 
1174  nt = nord-n
1175 
1176  do j=js-nt-1,je+nt+1
1177  do i=is-nt-1,ie+nt+1
1178  d2(i,j) = (fx2(i,j)-fx2(i+1,j)+fy2(i,j)-fy2(i,j+1))*gridstruct%rarea(i,j)
1179  enddo
1180  enddo
1181 
1182  call copy_corners(d2, npx, npy, 1, gridstruct%bounded_domain, bd, &
1183  gridstruct%sw_corner, gridstruct%se_corner, gridstruct%nw_corner, gridstruct%ne_corner)
1184  do j=js-nt,je+nt
1185  do i=is-nt,ie+nt+1
1186 #ifdef USE_SG
1187  fx2(i,j) = 0.5*(sin_sg(i-1,j,3)+sin_sg(i,j,1))*dy(i,j)*(d2(i,j)-d2(i-1,j))*rdxc(i,j)
1188 #else
1189  fx2(i,j) = gridstruct%del6_v(i,j)*(d2(i,j)-d2(i-1,j))
1190 #endif
1191  enddo
1192  enddo
1193 
1194  call copy_corners(d2, npx, npy, 2, gridstruct%bounded_domain, bd, &
1195  gridstruct%sw_corner, gridstruct%se_corner, gridstruct%nw_corner, gridstruct%ne_corner)
1196  do j=js-nt,je+nt+1
1197  do i=is-nt,ie+nt
1198 #ifdef USE_SG
1199  fy2(i,j) = 0.5*(sin_sg(i,j-1,4)+sin_sg(i,j,2))*dx(i,j)*(d2(i,j)-d2(i,j-1))*rdyc(i,j)
1200 #else
1201  fy2(i,j) = gridstruct%del6_u(i,j)*(d2(i,j)-d2(i,j-1))
1202 #endif
1203  enddo
1204  enddo
1205  enddo
1206 
1207  endif
1208 
1209 !---------------------------------------------
1210 ! Add the diffusive fluxes to the flux arrays:
1211 !---------------------------------------------
1212 
1213  if ( present(mass) ) then
1214 ! Apply mass weighting to diffusive fluxes:
1215  damp2 = 0.5*damp
1216  do j=js,je
1217  do i=is,ie+1
1218  fx(i,j) = fx(i,j) + damp2*(mass(i-1,j)+mass(i,j))*fx2(i,j)
1219  enddo
1220  enddo
1221  do j=js,je+1
1222  do i=is,ie
1223  fy(i,j) = fy(i,j) + damp2*(mass(i,j-1)+mass(i,j))*fy2(i,j)
1224  enddo
1225  enddo
1226  else
1227  do j=js,je
1228  do i=is,ie+1
1229  fx(i,j) = fx(i,j) + fx2(i,j)
1230  enddo
1231  enddo
1232  do j=js,je+1
1233  do i=is,ie
1234  fy(i,j) = fy(i,j) + fy2(i,j)
1235  enddo
1236  enddo
1237  endif
1238 
1239  end subroutine deln_flux
1240 
1241 
1242 end module tp_core_mod
real, parameter b1
Definition: tp_core.F90:75
subroutine, public fv_tp_2d(q, crx, cry, npx, npy, hord, fx, fy, xfx, yfx, gridstruct, bd, ra_x, ra_y, lim_fac, mfx, mfy, mass, nord, damp_c)
The subroutine &#39;fv_tp_2d&#39; contains the FV advection scheme .
Definition: tp_core.F90:109
The type &#39;fv_grid_type&#39; is made up of grid-dependent information from fv_grid_tools and fv_grid_utils...
Definition: fv_arrays.F90:123
real, parameter c1
Definition: tp_core.F90:87
subroutine xppm(flux, q, c, iord, is, ie, isd, ied, jfirst, jlast, jsd, jed, npx, npy, dxa, bounded_domain, grid_type, lim_fac)
Definition: tp_core.F90:326
real, parameter b3
Definition: tp_core.F90:77
real, parameter b5
Definition: tp_core.F90:79
real, parameter p1
Definition: tp_core.F90:93
subroutine deln_flux(nord, is, ie, js, je, npx, npy, damp, q, fx, fy, gridstruct, bd, mass)
Definition: tp_core.F90:1092
real, parameter ppm_limiter
Definition: tp_core.F90:63
real, parameter c3
Definition: tp_core.F90:89
The module &#39;tp_core&#39; is a collection of routines to support FV transport.
Definition: tp_core.F90:24
real, parameter t12
Definition: tp_core.F90:81
real, parameter s14
Definition: tp_core.F90:82
real, parameter near_zero
Definition: tp_core.F90:62
real, parameter t13
Definition: tp_core.F90:81
The module &#39;fv_arrays&#39; contains the &#39;fv_atmos_type&#39; and associated datatypes.
Definition: fv_arrays.F90:24
real, parameter, public big_number
subroutine, public pert_ppm(im, a0, al, ar, iv)
Definition: tp_core.F90:1030
real, parameter s15
Definition: tp_core.F90:82
real, parameter c2
Definition: tp_core.F90:88
real, parameter ppm_fac
nonlinear scheme limiter: between 1 and 2
Definition: tp_core.F90:60
real, parameter p2
Definition: tp_core.F90:94
real, parameter b4
Definition: tp_core.F90:78
The module &#39;fv_grid_utils&#39; contains routines for setting up and computing grid-related quantities...
real, parameter s11
Definition: tp_core.F90:82
subroutine mp_ghost_ew(im, jm, km, nq, ifirst, ilast, jfirst, jlast, kfirst, klast, ng_w, ng_e, ng_s, ng_n, q_ghst, q)
Definition: tp_core.F90:981
subroutine, public copy_corners(q, npx, npy, dir, bounded_domain, bd, sw_corner, se_corner, nw_corner, ne_corner)
Definition: tp_core.F90:248
real, parameter r3
Definition: tp_core.F90:61
subroutine yppm(flux, q, c, jord, ifirst, ilast, isd, ied, js, je, jsd, jed, npx, npy, dya, bounded_domain, grid_type, lim_fac)
Definition: tp_core.F90:635
real, parameter b2
Definition: tp_core.F90:76
real, parameter t11
Definition: tp_core.F90:81