Report Typos and Errors    
Semi-Lagrangian Library
Modular library for kinetic and gyrokinetic simulations of plasmas in fusion energy devices.
sll_m_mesh_calculus_2d.F90
Go to the documentation of this file.
2 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
3 #include "sll_assert.h"
4 #include "sll_memory.h"
5 #include "sll_working_precision.h"
6 
7  use sll_m_cartesian_meshes, only: &
9 
12 
15 
16  implicit none
17 
18  public :: &
25 
26  private
27 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
28 
29  ! --------------------------------------------------------------------------
30  !
31  ! The mesh calculus module aims at providing the means of computing
32  ! quantities like edge-lengths, areas, volumes and normals of cell elements
33  ! in a deformed mesh.
34  !
35  ! --------------------------------------------------------------------------
36 
37 contains
38 
39  function sll_f_cell_volume(T, ic, jc, integration_degree) result(vol)
40  intrinsic :: abs
41  class(sll_c_coordinate_transformation_2d_base), pointer :: t
42  sll_int32, intent(in) :: ic
43  sll_int32, intent(in) :: jc
44  sll_int32, intent(in) :: integration_degree
45  sll_real64 :: vol ! volume in physical space
46  sll_real64 :: jac
47  sll_real64, dimension(2, integration_degree) :: pts_g1 ! gauss-legendre pts.
48  sll_real64, dimension(2, integration_degree) :: pts_g2 ! gauss-legendre pts.
49  sll_real64 :: eta1_min
50  sll_real64 :: eta2_min
51  sll_real64 :: delta1
52  sll_real64 :: delta2
53  sll_real64 :: max1
54  sll_real64 :: min1
55  sll_real64 :: max2
56  sll_real64 :: min2
57  !sll_real64 :: factor1
58  !sll_real64 :: factor2
59  sll_int32 :: i
60  sll_int32 :: j
61 
62  ! Verify arguments
63  sll_assert(associated(t))
64  associate(m => t%mesh)
65  ! verify that the indices requested are within the logical mesh.
66  sll_assert(ic <= m%num_cells1)
67  sll_assert(jc <= m%num_cells2)
68 
69  vol = 0.0_f64
70 
71  eta1_min = m%eta1_min
72  delta1 = m%delta_eta1
73  eta2_min = m%eta2_min
74  delta2 = m%delta_eta2
75 
76  end associate
77 
78  ! This function carries out the integral of the jacobian evaluated on
79  ! gauss-legendre points within the cell.
80  ! The limits of integration are the limits of the cell in eta-space
81  min1 = eta1_min + (ic - 1)*delta1
82  max1 = eta1_min + ic*delta1
83  min2 = eta2_min + (jc - 1)*delta2
84  max2 = eta2_min + jc*delta2
85  !factor1 = 0.5_f64*(max1-min1)
86  !factor2 = 0.5_f64*(max2-min2)
87  pts_g1(:, :) = &
88  sll_f_gauss_legendre_points_and_weights(integration_degree, min1, max1)
89  !gauss_points(integration_degree, min1, max1)
90  pts_g2(:, :) = &
91  sll_f_gauss_legendre_points_and_weights(integration_degree, min2, max2)
92  ! gauss_points(integration_degree, min2, max2)
93 
94  do j = 1, integration_degree
95  do i = 1, integration_degree
96  jac = t%jacobian(pts_g1(1, i), pts_g2(1, j))
97  vol = vol + abs(jac)*pts_g1(2, i)*pts_g2(2, j)
98  end do
99  end do
100  !vol = vol*factor1*factor2
101 
102  end function sll_f_cell_volume
103 
104  ! length of the 'east' edge of the cell.
105  function sll_f_edge_length_eta1_plus(T, ic, jc, integration_degree) result(len)
106  intrinsic :: abs
107  class(sll_c_coordinate_transformation_2d_base), pointer :: t
108  sll_int32, intent(in) :: ic
109  sll_int32, intent(in) :: jc
110  sll_int32, intent(in) :: integration_degree
111  sll_real64 :: len ! length of edge in physical space
112  sll_real64, dimension(2, 2) :: jac_mat
113 ! sll_real64, dimension(2,integration_degree) :: pts_g1 ! gauss-legendre pts.
114  sll_real64, dimension(2, integration_degree) :: pts_g2 ! gauss-legendre pts.
115  sll_real64 :: eta1
116  !sll_real64 :: eta1_min
117  sll_real64 :: eta2_min
118  sll_real64 :: delta1
119  sll_real64 :: delta2
120  !sll_real64 :: max1
121  !sll_real64 :: min1
122  sll_real64 :: max2
123  sll_real64 :: min2
124  !sll_real64 :: factor1
125  !sll_real64 :: factor2
126  sll_int32 :: j
127  sll_real64 :: x1_eta2 ! derivative of x1(eta1,eta2) with respect to eta2
128  sll_real64 :: x2_eta2 ! derivative of x1(eta1,eta2) with respect to eta2
129 
130  ! Verify arguments
131  sll_assert(associated(t))
132 
133  associate(m => t%mesh)
134 
135  ! verify that the indices requested are within the logical mesh.
136  sll_assert(ic <= m%num_cells1)
137  sll_assert(jc <= m%num_cells2)
138 
139  len = 0.0_f64
140 
141 ! eta1_min = T%mesh%eta1_min
142  delta1 = m%delta_eta1
143  eta2_min = m%eta2_min
144  delta2 = m%delta_eta2
145 
146  end associate
147 
148  ! The limits of integration are the limits of the cell in eta-space
149  eta1 = ic*delta1 ! only difference with sll_f_edge_length_eta1_minus function
150  min2 = eta2_min + (jc - 1)*delta2
151  max2 = eta2_min + jc*delta2
152  pts_g2(:, :) = &
153  sll_f_gauss_legendre_points_and_weights(integration_degree, min2, max2)
154 
155  do j = 1, integration_degree
156  ! this can be made more efficient if we could access directly each
157  ! term of the jacobian matrix independently.
158  jac_mat(:, :) = t%jacobian_matrix(eta1, pts_g2(1, j))
159  x1_eta2 = jac_mat(1, 2)
160  x2_eta2 = jac_mat(2, 2)
161  len = len + sqrt(x1_eta2**2 + x2_eta2**2)*pts_g2(2, j)
162  end do
163  !len = len*factor2
164  end function sll_f_edge_length_eta1_plus
165 
166  ! length of the 'west' edge of the cell.
167  function sll_f_edge_length_eta1_minus(T, ic, jc, integration_degree) result(len)
168  intrinsic :: abs
169  class(sll_c_coordinate_transformation_2d_base), pointer :: t
170  sll_int32, intent(in) :: ic
171  sll_int32, intent(in) :: jc
172  sll_int32, intent(in) :: integration_degree
173  sll_real64 :: len ! length of edge in physical space
174  sll_real64, dimension(2, 2) :: jac_mat
175 ! sll_real64, dimension(2,integration_degree) :: pts_g1 ! gauss-legendre pts.
176  sll_real64, dimension(2, integration_degree) :: pts_g2 ! gauss-legendre pts.
177  sll_real64 :: eta1
178  !sll_real64 :: eta1_min
179  sll_real64 :: eta2_min
180  sll_real64 :: delta1
181  sll_real64 :: delta2
182  !sll_real64 :: max1
183  !sll_real64 :: min1
184  sll_real64 :: max2
185  sll_real64 :: min2
186  ! sll_real64 :: factor1
187  ! sll_real64 :: factor2
188  sll_int32 :: j
189  sll_real64 :: x1_eta2 ! derivative of x1(eta1,eta2) with respect to eta2
190  sll_real64 :: x2_eta2 ! derivative of x1(eta1,eta2) with respect to eta2
191 
192  ! Verify arguments
193  sll_assert(associated(t))
194 
195  associate(m => t%mesh)
196 
197  ! verify that the indices requested are within the logical mesh.
198  sll_assert(ic <= m%num_cells1)
199  sll_assert(jc <= m%num_cells2)
200 
201  len = 0.0_f64
202 
203  ! eta1_min = T%mesh%eta1_min
204  delta1 = m%delta_eta1
205  eta2_min = m%eta2_min
206  delta2 = m%delta_eta2
207 
208  end associate
209 
210  ! The limits of integration are the limits of the cell in eta-space
211  eta1 = (ic - 1)*delta1
212  min2 = eta2_min + (jc - 1)*delta2
213  max2 = eta2_min + jc*delta2
214  ! factor1 = 0.5_f64*(max1-min1)
215  ! factor2 = 0.5_f64*(max2-min2)
216  ! pts_g1(:,:) = gauss_points(integration_degree, min1, max1)
217  pts_g2(:, :) = &
218  sll_f_gauss_legendre_points_and_weights(integration_degree, min2, max2)
219  !gauss_points(integration_degree, min2, max2)
220 
221  do j = 1, integration_degree
222  ! this can be made more efficient if we could access directly each
223  ! term of the jacobian matrix independently.
224  jac_mat(:, :) = t%jacobian_matrix(eta1, pts_g2(1, j))
225  x1_eta2 = jac_mat(1, 2)
226  x2_eta2 = jac_mat(2, 2)
227  len = len + sqrt(x1_eta2**2 + x2_eta2**2)*pts_g2(2, j)
228  end do
229  !len = len*factor2
230  end function sll_f_edge_length_eta1_minus
231 
232  ! length of the 'north' edge of the cell.
233  function sll_f_edge_length_eta2_plus(T, ic, jc, integration_degree) result(len)
234  intrinsic :: abs
235  class(sll_c_coordinate_transformation_2d_base), pointer :: t
236  sll_int32, intent(in) :: ic
237  sll_int32, intent(in) :: jc
238  sll_int32, intent(in) :: integration_degree
239  sll_real64 :: len ! length of edge in physical space
240  sll_real64, dimension(2, 2) :: jac_mat
241  sll_real64, dimension(2, integration_degree) :: pts_g1 ! gauss-legendre pts.
242 ! sll_real64, dimension(2,integration_degree) :: pts_g2 ! gauss-legendre pts.
243  sll_real64 :: eta2
244  sll_real64 :: eta1_min
245  !sll_real64 :: eta2_min
246  sll_real64 :: delta1
247  sll_real64 :: delta2
248  sll_real64 :: max1
249  sll_real64 :: min1
250  sll_int32 :: i
251  sll_real64 :: x1_eta1 ! derivative of x1(eta1,eta2) with respect to eta1
252  sll_real64 :: x2_eta1 ! derivative of x1(eta1,eta2) with respect to eta1
253 
254  ! Verify arguments
255  sll_assert(associated(t))
256  associate(m => t%mesh)
257 
258  ! verify that the indices requested are within the logical mesh.
259  sll_assert(ic <= m%num_cells1)
260  sll_assert(jc <= m%num_cells2)
261 
262  len = 0.0_f64
263 
264  eta1_min = m%eta1_min
265  delta1 = m%delta_eta1
266  delta2 = m%delta_eta2 ! is this used?
267 
268  end associate
269 
270  ! The limits of integration are the limits of the cell in eta-space
271  min1 = eta1_min + (ic - 1)*delta1
272  max1 = eta1_min + ic*delta1
273  eta2 = jc*delta2 ! only difference with sll_f_edge_length_eta2_minus function
274  pts_g1(:, :) = &
275  sll_f_gauss_legendre_points_and_weights(integration_degree, min1, max1)
276  !gauss_points(integration_degree, min1, max1)
277  ! pts_g2(:,:) = gauss_points(integration_degree, min2, max2)
278 
279  do i = 1, integration_degree
280  ! this can be made more efficient if we could access directly each
281  ! term of the jacobian matrix independently.
282  jac_mat(:, :) = t%jacobian_matrix(pts_g1(1, i), eta2)
283  x1_eta1 = jac_mat(1, 1)
284  x2_eta1 = jac_mat(2, 1)
285  len = len + sqrt(x1_eta1**2 + x2_eta1**2)*pts_g1(2, i)
286  end do
287  ! len = len*factor1
288  end function sll_f_edge_length_eta2_plus
289 
290  ! length of the 'south' edge of the cell.
291  function sll_f_edge_length_eta2_minus(T, ic, jc, integration_degree) result(len)
292  intrinsic :: abs
293  class(sll_c_coordinate_transformation_2d_base), pointer :: t
294  sll_int32, intent(in) :: ic
295  sll_int32, intent(in) :: jc
296  sll_int32, intent(in) :: integration_degree
297  sll_real64 :: len ! length of edge in physical space
298  sll_real64, dimension(2, 2) :: jac_mat
299  sll_real64, dimension(2, integration_degree) :: pts_g1 ! gauss-legendre pts.
300  ! sll_real64, dimension(2,integration_degree) :: pts_g2 ! gauss-legendre pts.
301  sll_real64 :: eta2
302  sll_real64 :: eta1_min
303  !sll_real64 :: eta2_min
304  sll_real64 :: delta1
305  sll_real64 :: delta2
306  sll_real64 :: max1
307  sll_real64 :: min1
308  !sll_real64 :: max2
309  !sll_real64 :: min2
310  !sll_real64 :: factor1
311  ! sll_real64 :: factor2
312  sll_int32 :: i
313  sll_real64 :: x1_eta1 ! derivative of x1(eta1,eta2) with respect to eta1
314  sll_real64 :: x2_eta1 ! derivative of x1(eta1,eta2) with respect to eta1
315 
316  ! Verify arguments
317  sll_assert(associated(t))
318 
319  associate(m => t%mesh)
320 
321  ! verify that the indices requested are within the logical mesh.
322  sll_assert(ic <= m%num_cells1)
323  sll_assert(jc <= m%num_cells2)
324 
325  len = 0.0_f64
326 
327  eta1_min = m%eta1_min
328  delta1 = m%delta_eta1
329  delta2 = m%delta_eta2 ! is this used?
330 
331  end associate
332 
333  ! The limits of integration are the limits of the cell in eta-space
334  min1 = eta1_min + (ic - 1)*delta1
335  max1 = eta1_min + ic*delta1
336  eta2 = (jc - 1)*delta2 !only difference with sll_f_edge_length_eta2_plus function
337  ! min2 = eta2_min + (jc-1)*delta2
338  ! max2 = eta2_min + jc*delta2
339  !factor1 = 0.5_f64*(max1-min1)
340  ! factor2 = 0.5_f64*(max2-min2)
341  pts_g1(:, :) = &
342  sll_f_gauss_legendre_points_and_weights(integration_degree, min1, max1)
343  !gauss_points(integration_degree, min1, max1)
344  ! pts_g2(:,:) = gauss_points(integration_degree, min2, max2)
345 
346  do i = 1, integration_degree
347  ! this can be made more efficient if we could access directly each
348  ! term of the jacobian matrix independently.
349  jac_mat(:, :) = t%jacobian_matrix(pts_g1(1, i), eta2)
350  x1_eta1 = jac_mat(1, 1)
351  x2_eta1 = jac_mat(2, 1)
352  len = len + sqrt(x1_eta1**2 + x2_eta1**2)*pts_g1(2, i)
353  end do
354  !len = len*factor1
355  end function sll_f_edge_length_eta2_minus
356 
357  ! integral of the normal vector over the 'east' edge of the cell.
358  function sll_f_normal_integral_eta1_plus(T, ic, jc, integration_degree) result(res)
359  class(sll_c_coordinate_transformation_2d_base), pointer :: t
360  sll_int32, intent(in) :: ic
361  sll_int32, intent(in) :: jc
362  sll_int32, intent(in) :: integration_degree
363  sll_real64, dimension(2) :: res
364 
365  sll_real64, dimension(2, 2) :: inv_jac_mat ! inverse jacobian matrix
366  ! sll_real64, dimension(2,integration_degree) :: pts_g1 ! gauss-legendre pts.
367  sll_real64, dimension(2, integration_degree) :: pts_g2 ! gauss-legendre pts.
368  sll_real64 :: eta1
369  !sll_real64 :: eta1_min
370  sll_real64 :: eta2_min
371  sll_real64 :: delta1
372  sll_real64 :: delta2
373  !sll_real64 :: max1
374  !sll_real64 :: min1
375  sll_real64 :: max2
376  sll_real64 :: min2
377  !sll_real64 :: factor1
378  !sll_real64 :: factor2
379  sll_int32 :: j
380  sll_real64 :: eta1_x1 ! derivative of eta1(x1,x2) with respect to x1
381  sll_real64 :: eta1_x2 ! derivative of eta1(x1,x2) with respect to x2
382  sll_real64 :: edge_length
383 
384  ! Verify arguments
385  sll_assert(associated(t))
386 
387  associate(m => t%mesh)
388 
389  ! verify that the indices requested are within the logical mesh.
390  sll_assert(ic <= m%num_cells1)
391  sll_assert(jc <= m%num_cells2)
392 
393  ! eta1_min = T%mesh%eta1_min
394  delta1 = m%delta_eta1
395  eta2_min = m%eta2_min
396  delta2 = m%delta_eta2
397 
398  end associate
399 
400  ! The limits of integration are the limits of the cell in eta-space
401  ! min1 = eta1_min + (ic-1)*delta1
402  ! max1 = eta1_min + ic*delta1
403  eta1 = ic*delta1 ! <- line differs w/ normal_integral_eta1_minus()
404  min2 = eta2_min + (jc - 1)*delta2
405  max2 = eta2_min + jc*delta2
406  ! factor1 = 0.5_f64*(max1-min1)
407  !factor2 = 0.5_f64*(max2-min2)
408  ! pts_g1(:,:) = gauss_points(integration_degree, min1, max1)
409  pts_g2(:, :) = &
410  sll_f_gauss_legendre_points_and_weights(integration_degree, min2, max2)
411  !gauss_points(integration_degree, min2, max2)
412 
413  ! For efficiency, this code should be refactored. Consider:
414  ! - adding direct access functions to the jacobian matrix elements and the
415  ! inverse jacobian matrix elements
416  ! - use macros to eliminate the massive code redundancy in this module's
417  ! functions.
418  ! - same macros can be used to improve a function call like the one next.
419  edge_length = sll_f_edge_length_eta1_plus(t, ic, jc, integration_degree)
420  res(:) = 0.0_f64
421 
422  do j = 1, integration_degree
423  ! this can be made more efficient if we could access directly each
424  ! term of the jacobian matrix independently.
425  inv_jac_mat(:, :) = t%inverse_jacobian_matrix(eta1, pts_g2(1, j))
426  eta1_x1 = inv_jac_mat(1, 1)
427  eta1_x2 = inv_jac_mat(2, 1)
428  sll_assert(t%jacobian(eta1, pts_g2(1, j)) > 0.0_f64)
429  res(1) = res(1) + eta1_x1*pts_g2(2, j)
430  res(2) = res(2) + eta1_x2*pts_g2(2, j)
431  end do
432  res(1) = res(1)*edge_length !res(1) = res(1)*factor2*edge_length
433  res(2) = res(2)*edge_length ! res(2) = res(2)*factor2*edge_length
435 
436  ! integral of the normal vector over the 'west' edge of the cell.
437  function normal_integral_eta1_minus(T, ic, jc, integration_degree) result(res)
438  class(sll_c_coordinate_transformation_2d_base), pointer :: t
439  sll_int32, intent(in) :: ic
440  sll_int32, intent(in) :: jc
441  sll_int32, intent(in) :: integration_degree
442  sll_real64, dimension(2) :: res
443 
444  sll_real64, dimension(2, 2) :: inv_jac_mat ! inverse jacobian matrix
445  sll_real64, dimension(2, integration_degree) :: pts_g2 ! gauss-legendre pts.
446  sll_real64 :: eta1
447  !sll_real64 :: eta1_min
448  sll_real64 :: eta2_min
449  sll_real64 :: delta1
450  sll_real64 :: delta2
451  !sll_real64 :: max1
452  !sll_real64 :: min1
453  sll_real64 :: max2
454  sll_real64 :: min2
455  !sll_real64 :: factor1
456  !sll_real64 :: factor2
457  sll_int32 :: j
458  sll_real64 :: eta1_x1 ! derivative of eta1(x1,x2) with respect to x1
459  sll_real64 :: eta1_x2 ! derivative of eta1(x1,x2) with respect to x2
460  sll_real64 :: edge_length
461 
462  ! Verify arguments
463  sll_assert(associated(t))
464 
465  associate(m => t%mesh)
466 
467  ! verify that the indices requested are within the logical mesh.
468  sll_assert(ic <= m%num_cells1)
469  sll_assert(jc <= m%num_cells2)
470 
471  delta1 = m%delta_eta1
472  eta2_min = m%eta2_min
473  delta2 = m%delta_eta2
474 
475  end associate
476 
477  ! The limits of integration are the limits of the cell in eta-space
478  ! min1 = eta1_min + (ic-1)*delta1
479  ! max1 = eta1_min + ic*delta1
480  eta1 = (ic - 1)*delta1 ! <- line differs w/ sll_f_normal_integral_eta1_plus()
481  min2 = eta2_min + (jc - 1)*delta2
482  max2 = eta2_min + jc*delta2
483  ! factor1 = 0.5_f64*(max1-min1)
484  !factor2 = 0.5_f64*(max2-min2)
485  ! pts_g1(:,:) = gauss_points(integration_degree, min1, max1)
486  pts_g2(:, :) = &
487  sll_f_gauss_legendre_points_and_weights(integration_degree, min2, max2)
488  !gauss_points(integration_degree, min2, max2)
489 
490  ! For efficiency, this code should be refactored. Consider:
491  ! - adding direct access functions to the jacobian matrix elements and the
492  ! inverse jacobian matrix elements
493  ! - use macros to eliminate the massive code redundancy in this module's
494  ! functions.
495  ! - same macros can be used to improve a function call like the one next.
496  edge_length = sll_f_edge_length_eta1_minus(t, ic, jc, integration_degree)
497 
498  do j = 1, integration_degree
499  ! this can be made more efficient if we could access directly each
500  ! term of the jacobian matrix independently.
501  inv_jac_mat(:, :) = t%inverse_jacobian_matrix(eta1, pts_g2(1, j))
502  eta1_x1 = inv_jac_mat(1, 1)
503  eta1_x2 = inv_jac_mat(2, 1)
504  sll_assert(t%jacobian(eta1, pts_g2(1, j)) > 0.0_f64)
505  res(1) = res(1) + eta1_x1*pts_g2(2, j)
506  res(2) = res(2) + eta1_x2*pts_g2(2, j)
507  end do
508  ! change of sign due to the direction in which the integral is done
509  res(1) = -res(1)*edge_length
510  res(2) = -res(2)*edge_length
511 !!$ res(1) = -res(1)*factor2*edge_length
512 !!$ res(2) = -res(2)*factor2*edge_length
513  end function normal_integral_eta1_minus
514 
515  ! integral of the normal vector over the 'north' edge of the cell.
516  function normal_integral_eta2_plus(T, ic, jc, integration_degree) result(res)
517  class(sll_c_coordinate_transformation_2d_base), pointer :: t
518  sll_int32, intent(in) :: ic
519  sll_int32, intent(in) :: jc
520  sll_int32, intent(in) :: integration_degree
521  sll_real64, dimension(2) :: res
522 
523  sll_real64, dimension(2, 2) :: inv_jac_mat ! inverse jacobian matrix
524  sll_real64, dimension(2, integration_degree) :: pts_g1 ! gauss-legendre pts.
525  ! sll_real64, dimension(2,integration_degree) :: pts_g2 ! gauss-legendre pts.
526  sll_real64 :: eta2
527  sll_real64 :: eta1_min
528  !sll_real64 :: eta2_min
529  sll_real64 :: delta1
530  sll_real64 :: delta2
531  sll_real64 :: max1
532  sll_real64 :: min1
533  !sll_real64 :: max2
534  !sll_real64 :: min2
535  !sll_real64 :: factor1
536  !sll_real64 :: factor2
537  sll_int32 :: i
538  sll_real64 :: eta2_x1 ! derivative of eta2(x1,x2) with respect to x1
539  sll_real64 :: eta2_x2 ! derivative of eta2(x1,x2) with respect to x2
540  sll_real64 :: edge_length
541 
542  ! Verify arguments
543  sll_assert(associated(t))
544 
545  associate(m => t%mesh)
546 
547  ! verify that the indices requested are within the logical mesh.
548  sll_assert(ic <= m%num_cells1)
549  sll_assert(jc <= m%num_cells2)
550 
551  eta1_min = m%eta1_min
552  delta1 = m%delta_eta1
553  delta2 = m%delta_eta2
554 
555  end associate
556 
557  ! The limits of integration are the limits of the cell in eta-space
558  min1 = eta1_min + (ic - 1)*delta1
559  max1 = eta1_min + ic*delta1
560  eta2 = jc*delta2 ! <- line differs w/ normal_integral_eta2_minus()
561  ! min2 = eta2_min + (jc-1)*delta2
562  ! max2 = eta2_min + jc*delta2
563  ! factor1 = 0.5_f64*(max1-min1)
564  ! factor2 = 0.5_f64*(max2-min2)
565  pts_g1(:, :) = sll_f_gauss_legendre_points_and_weights(integration_degree, min1, max1)
566  !gauss_points(integration_degree, min1, max1)
567  ! pts_g2(:,:) = gauss_points(integration_degree, min2, max2)
568 
569  ! For efficiency, this code should be refactored. Consider:
570  ! - adding direct access functions to the jacobian matrix elements and the
571  ! inverse jacobian matrix elements
572  ! - use macros to eliminate the massive code redundancy in this module's
573  ! functions.
574  ! - same macros can be used to improve a function call like the one next.
575  edge_length = sll_f_edge_length_eta2_plus(t, ic, jc, integration_degree)
576  res(:) = 0.0_f64
577 
578  do i = 1, integration_degree
579  ! this can be made more efficient if we could access directly each
580  ! term of the jacobian matrix independently.
581  inv_jac_mat(:, :) = t%inverse_jacobian_matrix(pts_g1(1, i), eta2)
582  eta2_x1 = inv_jac_mat(2, 1)
583  eta2_x2 = inv_jac_mat(2, 2)
584  sll_assert(t%jacobian(pts_g1(1, i), eta2) > 0.0_f64)
585  res(1) = res(1) + eta2_x1*pts_g1(2, i)
586  res(2) = res(2) + eta2_x2*pts_g1(2, i)
587  end do
588  res(1) = res(1)*edge_length
589  res(2) = res(2)*edge_length
590 !!$ res(1) = res(1)*factor1*edge_length
591 !!$ res(2) = res(2)*factor1*edge_length
592  end function normal_integral_eta2_plus
593 
594  ! integral of the normal vector over the 'southth' edge of the cell.
595  function normal_integral_eta2_minus(T, ic, jc, integration_degree) result(res)
596  class(sll_c_coordinate_transformation_2d_base), pointer :: t
597  sll_int32, intent(in) :: ic
598  sll_int32, intent(in) :: jc
599  sll_int32, intent(in) :: integration_degree
600  sll_real64, dimension(2) :: res
601 
602  sll_real64, dimension(2, 2) :: inv_jac_mat ! inverse jacobian matrix
603  sll_real64, dimension(2, integration_degree) :: pts_g1 ! gauss-legendre pts.
604  ! sll_real64, dimension(2,integration_degree) :: pts_g2 ! gauss-legendre pts.
605  sll_real64 :: eta2
606  sll_real64 :: eta1_min
607  !sll_real64 :: eta2_min
608  sll_real64 :: delta1
609  sll_real64 :: delta2
610  sll_real64 :: max1
611  sll_real64 :: min1
612  !sll_real64 :: max2
613  !sll_real64 :: min2
614  !sll_real64 :: factor1
615  !sll_real64 :: factor2
616  sll_int32 :: i
617  sll_real64 :: eta2_x1 ! derivative of eta2(x1,x2) with respect to x1
618  sll_real64 :: eta2_x2 ! derivative of eta2(x1,x2) with respect to x2
619  sll_real64 :: edge_length
620 
621  ! Verify arguments
622  sll_assert(associated(t))
623 
624  associate(m => t%mesh)
625 
626  ! verify that the indices requested are within the logical mesh.
627  sll_assert(ic <= m%num_cells1)
628  sll_assert(jc <= m%num_cells2)
629 
630  eta1_min = m%eta1_min
631  delta1 = m%delta_eta1
632  delta2 = m%delta_eta2
633 
634  end associate
635 
636  ! The limits of integration are the limits of the cell in eta-space
637  min1 = eta1_min + (ic - 1)*delta1
638  max1 = eta1_min + ic*delta1
639  eta2 = (jc - 1)*delta2 ! <- line differs w/ normal_integral_eta2_pluus()
640  ! min2 = eta2_min + (jc-1)*delta2
641  ! max2 = eta2_min + jc*delta2
642  !factor1 = 0.5_f64*(max1-min1)
643  ! factor2 = 0.5_f64*(max2-min2)
644  pts_g1(:, :) = sll_f_gauss_legendre_points_and_weights(integration_degree, min1, max1)
645  !gauss_points(integration_degree, min1, max1)
646  ! pts_g2(:,:) = gauss_points(integration_degree, min2, max2)
647 
648  ! For efficiency, this code should be refactored. Consider:
649  ! - adding direct access functions to the jacobian matrix elements and the
650  ! inverse jacobian matrix elements
651  ! - use macros to eliminate the massive code redundancy in this module's
652  ! functions.
653  ! - same macros can be used to improve a function call like the one next.
654  edge_length = sll_f_edge_length_eta2_minus(t, ic, jc, integration_degree)
655  res(:) = 0.0_f64
656 
657  do i = 1, integration_degree
658  ! this can be made more efficient if we could access directly each
659  ! term of the jacobian matrix independently.
660  inv_jac_mat(:, :) = t%inverse_jacobian_matrix(pts_g1(1, i), eta2)
661  eta2_x1 = inv_jac_mat(2, 1)
662  eta2_x2 = inv_jac_mat(2, 2)
663  sll_assert(t%jacobian(pts_g1(1, i), eta2) > 0.0_f64)
664  res(1) = res(1) + eta2_x1*pts_g1(2, i)
665  res(2) = res(2) + eta2_x2*pts_g1(2, i)
666  end do
667  ! change of sign due to direction of integration
668  res(1) = -res(1)*edge_length
669  res(2) = -res(2)*edge_length
670 !!$ res(1) = -res(1)*factor1*edge_length
671 !!$ res(2) = -res(2)*factor1*edge_length
672  end function normal_integral_eta2_minus
673 
674 end module sll_m_mesh_calculus_2d
675 
Cartesian mesh basic types.
Abstract class for coordinate transformations.
real(kind=f64) function, dimension(2, 1:npoints), public sll_f_gauss_legendre_points_and_weights(npoints, a, b)
Returns a 2d array of size (2,npoints) containing gauss-legendre points and weights in the interval [...
real(kind=f64) function, dimension(2), public sll_f_normal_integral_eta1_plus(T, ic, jc, integration_degree)
real(kind=f64) function, public sll_f_edge_length_eta1_minus(T, ic, jc, integration_degree)
dimension(2) normal_integral_eta1_minus(T, ic, jc, integration_degree)
dimension(2) normal_integral_eta2_minus(T, ic, jc, integration_degree)
real(kind=f64) function, public sll_f_edge_length_eta1_plus(T, ic, jc, integration_degree)
real(kind=f64) function, public sll_f_edge_length_eta2_minus(T, ic, jc, integration_degree)
real(kind=f64) function, dimension(2) normal_integral_eta2_plus(T, ic, jc, integration_degree)
real(kind=f64) function, public sll_f_cell_volume(T, ic, jc, integration_degree)
real(kind=f64) function, public sll_f_edge_length_eta2_plus(T, ic, jc, integration_degree)
    Report Typos and Errors