Report Typos and Errors    
Semi-Lagrangian Library
Modular library for kinetic and gyrokinetic simulations of plasmas in fusion energy devices.
sll_m_euler_2d_hex.F90
Go to the documentation of this file.
1 
3 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
4 #include "sll_memory.h"
5 #include "sll_working_precision.h"
6 
7  implicit none
8 
9  public :: &
12 
13  private
14 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
15 
16 ! type,extends(sll_characteristics_2d_base) :: euler_2d_hex_charac_computer
17 ! sll_int32 :: Num_cells ! num_cells is the step used for a hexagonal mesh
18 ! sll_real64 :: radius ! the mesh is determined by the radius ( in contrast to eta in a cartesian mesh)
19 
20 ! ! since there are 6 boundary conditions
21 ! procedure(signature_process_outside_point), pointer, nopass :: &
22 ! process_outside_point1
23 ! procedure(signature_process_outside_point), pointer, nopass :: &
24 ! process_outside_point2
25 ! procedure(signature_process_outside_point), pointer, nopass :: &
26 ! process_outside_point3
27 ! procedure(signature_process_outside_point), pointer, nopass :: &
28 ! process_outside_point4
29 ! procedure(signature_process_outside_point), pointer, nopass :: &
30 ! process_outside_point5
31 ! procedure(signature_process_outside_point), pointer, nopass :: &
32 ! process_outside_point6
33 
34 ! contains
35 
36 ! procedure, pass(charac) :: initialize => &
37 ! initialize_euler_2d_hex_charac
38 ! procedure, pass(charac) :: compute_characteristics => &
39 ! compute_euler_2d_hex_charac
40 
41 ! end type euler_2d_hex_charac_computer
42 
43 contains
44 
45 ! function new_euler_2d_hex_charac(&
46 ! Npts,
47 ! bc_type_1, &
48 ! bc_type_2, &
49 ! bc_type_3, &
50 ! bc_type_4, &
51 ! bc_type_5, &
52 ! bc_type_6, &
53 ! radius, &
54 ! process_outside_point1, &
55 ! process_outside_point2, &
56 ! process_outside_point3, &
57 ! process_outside_point4, &
58 ! process_outside_point5, &
59 ! process_outside_point6) &
60 ! result(charac)
61 
62 ! type(euler_2d_hex_charac_computer),pointer :: charac
63 ! sll_int32, intent(in) :: Num_cells
64 ! sll_int32, intent(in), optional :: bc_type_1
65 ! sll_int32, intent(in), optional :: bc_type_2
66 ! sll_int32, intent(in), optional :: bc_type_3
67 ! sll_int32, intent(in), optional :: bc_type_4
68 ! sll_int32, intent(in), optional :: bc_type_5
69 ! sll_int32, intent(in), optional :: bc_type_6
70 ! sll_real64, intent(in), optional :: radius
71 ! procedure(signature_process_outside_point), optional :: &
72 ! process_outside_point1
73 ! procedure(signature_process_outside_point), optional :: &
74 ! process_outside_point2
75 ! procedure(signature_process_outside_point), optional :: &
76 ! process_outside_point3
77 ! procedure(signature_process_outside_point), optional :: &
78 ! process_outside_point4
79 ! procedure(signature_process_outside_point), optional :: &
80 ! process_outside_point5
81 ! procedure(signature_process_outside_point), optional :: &
82 ! process_outside_point6
83 ! sll_int32 :: ierr
84 
85 ! SLL_ALLOCATE(charac,ierr)
86 
87 ! call initialize_euler_2d_hex_charac(&
88 ! charac, &
89 ! Num_cells, &
90 ! bc_type_1, &
91 ! bc_type_2, &
92 ! bc_type_3, &
93 ! bc_type_4, &
94 ! bc_type_5, &
95 ! bc_type_6, &
96 ! radius, &
97 ! process_outside_point1, &
98 ! process_outside_point2, &
99 ! process_outside_point3, &
100 ! process_outside_point4, &
101 ! process_outside_point5, &
102 ! process_outside_point6)
103 
104 ! end function new_euler_2d_hex_charac
105 
106 ! subroutine initialize_euler_2d_hex_charac(&
107 ! charac, &
108 ! Num_cells, &
109 ! bc_type_1, &
110 ! bc_type_2, &
111 ! bc_type_3, &
112 ! bc_type_4, &
113 ! bc_type_5, &
114 ! bc_type_6, &
115 ! radius, &
116 ! process_outside_point1, &
117 ! process_outside_point2, &
118 ! process_outside_point3, &
119 ! process_outside_point4, &
120 ! process_outside_point5, &
121 ! process_outside_point6)
122 
123 ! class(euler_2d_hex_charac_computer) :: charac
124 ! sll_int32, intent(in) :: Num_cells
125 ! sll_int32, intent(in), optional :: bc_type_1
126 ! sll_int32, intent(in), optional :: bc_type_2
127 ! sll_int32, intent(in), optional :: bc_type_3
128 ! sll_int32, intent(in), optional :: bc_type_4
129 ! sll_int32, intent(in), optional :: bc_type_5
130 ! sll_int32, intent(in), optional :: bc_type_6
131 ! sll_real64, intent(in), optional :: radius
132 ! procedure(signature_process_outside_point), optional :: &
133 ! process_outside_point1
134 ! procedure(signature_process_outside_point), optional :: &
135 ! process_outside_point2
136 ! procedure(signature_process_outside_point), optional :: &
137 ! process_outside_point3
138 ! procedure(signature_process_outside_point), optional :: &
139 ! process_outside_point4
140 ! procedure(signature_process_outside_point), optional :: &
141 ! process_outside_point5
142 ! procedure(signature_process_outside_point), optional :: &
143 ! process_outside_point6
144 
145 ! charac%Num_cells = Num_cells
146 
147 ! if(present(radius))then
148 ! charac%eta1_min = eta1_min
149 ! else
150 ! charac%eta1_min = 0._f64
151 ! endif
152 
153 ! if(present(process_outside_point1)) then
154 ! charac%process_outside_point1 => process_outside_point1
155 ! else if(.not.(present(bc_type_1))) then
156 ! print *,'#provide boundary condition'
157 ! print *,'#bc_type_1 or process_outside_point1 function'
158 ! print *,'#in initialize_euler_2d_hex_charac'
159 ! stop
160 ! else
161 ! select case (bc_type_1)
162 ! case (sll_p_periodic)
163 ! charac%process_outside_point1 => process_outside_point_periodic
164 ! case (SLL_SET_TO_LIMIT)
165 ! charac%process_outside_point1 => process_outside_point_set_to_limit
166 ! case default
167 ! print *,'#bad value of boundary condition'
168 ! print *,'#in initialize_euler_2d_hex_charac_computer'
169 ! stop
170 ! end select
171 ! endif
172 
173 ! if((present(process_outside_point1)).and.(present(bc_type_1)))then
174 ! print *,'#provide either process_outside_point1 or bc_type_1'
175 ! print *,'#and not both'
176 ! print *,'#in initialize_euler_2d_hex_charac_computer'
177 ! stop
178 ! endif
179 
180 ! if(present(process_outside_point2)) then
181 ! charac%process_outside_point2 => process_outside_point2
182 ! else if(.not.(present(bc_type_2))) then
183 ! print *,'#provide boundary condition'
184 ! print *,'#bc_type_2 or process_outside_point1 function'
185 ! stop
186 ! else
187 ! select case (bc_type_2)
188 ! case (sll_p_periodic)
189 ! charac%process_outside_point2 => process_outside_point_periodic
190 ! case (SLL_SET_TO_LIMIT)
191 ! charac%process_outside_point2 => process_outside_point_set_to_limit
192 ! case default
193 ! print *,'#bad value of boundary condition'
194 ! print *,'#in initialize_euler_2d_hex_charac_computer'
195 ! stop
196 ! end select
197 ! endif
198 
199 ! if((present(process_outside_point2)).and.(present(bc_type_2)))then
200 ! print *,'#provide either process_outside_point2 or bc_type_2'
201 ! print *,'#and not both'
202 ! print *,'#in initialize_euler_2d_hex_charac_computer'
203 ! stop
204 ! endif
205 
206 ! end subroutine initialize_euler_2d_hex_charac
207 
208 ! subroutine compute_euler_2d_hex_charac( &
209 ! charac, &
210 ! A1, &
211 ! A2, &
212 ! dt, &
213 ! input1, &
214 ! input2, &
215 ! output1, &
216 ! output2)
217 
218 ! class(euler_2d_hex_charac_computer) :: charac
219 ! sll_real64, dimension(:,:), intent(in) :: A1
220 ! sll_real64, dimension(:,:), intent(in) :: A2
221 ! sll_real64, intent(in) :: dt
222 ! sll_real64, dimension(:), intent(in) :: input1
223 ! sll_real64, dimension(:), intent(in) :: input2
224 ! sll_real64, dimension(:,:), intent(out) :: output1
225 ! sll_real64, dimension(:,:), intent(out) :: output2
226 ! sll_int32 :: i
227 ! sll_int32 :: j
228 ! sll_int32 :: Num_cells
229 ! sll_real64 :: radius
230 ! sll_real64 :: step
231 
232 ! Num_cells = charac%Num_cells
233 ! radius = charac%radius
234 
235 ! do j = - Num_cells,Num_cells
236 ! do i = - Num_cells,Num_cells
237 
238 ! if ( i*j < 0 .and. abs(i) + abs(j) == Num_cells ) then
239 ! ! these are not mesh points
240 ! else ! these are mesh points
241 
242 ! call sll_s_compute_characteristic_euler_2d_hex( &
243 ! input1(i),input2(i),A1,A2,i,j,output1(i,j),output2(i,j),dt,step )
244 
245 ! !output1(i,j) = input1(i)-dt*A1(i,j) ! euler
246 ! !output2(i,j) = input2(j)-dt*A2(i,j) ! euler
247 
248 ! ! in the case the output is outside : find through which one
249 ! ! of the 6 sides it 'came from'
250 ! ! then we use the appropriate procedure
251 
252 ! if( output1(i,j) output2(i,j) )then
253 ! output1(i,j)=charac%process_outside_point6(output2(i,j),radius)
254 ! output2(i,j)=charac%process_outside_point6(output2(i,j),radius)
255 ! endif
256 
257 ! enddo
258 ! enddo
259 
260 ! end subroutine compute_euler_2d_hex_charac
261 
262  subroutine sll_s_compute_characteristic_euler_2d_hex(x1, x2, uxn, uyn, i, y1, y2, dt)
263 
264  sll_real64, dimension(:), intent(in):: uxn, uyn
265  sll_real64, intent(in) :: dt
266  sll_real64, intent(in) :: x1, x2 ! point of the characteristic at tn+1
267  sll_real64, intent(out) :: y1, y2 ! point of the characteristic at tn
268  sll_int32, intent(in) :: i
269 
270  y1 = x1 - dt*uxn(i)
271  y2 = x2 - dt*uyn(i)
272 
274 
275  ! subroutine compute_characteristic_verlet_2d_hex( z1,z2,uxn,uyn,dxux,dyux,dxuy,dyuy,i,zz1,zz2,dt, aire, mesh)
276 
277  ! type(sll_hex_mesh_2d), pointer :: mesh
278  ! sll_real64,dimension(:),intent(in):: uxn, uyn,dxux,dyux,dxuy,dyuy
279  ! sll_real64, intent(in) :: dt, aire
280  ! sll_real64, intent(in) :: z1, z2 ! point of the characteristic at tn+1
281  ! sll_real64, intent(out) :: zz1, zz2 ! point of the characteristic at tn
282  ! sll_int32, intent(in) :: i
283  ! sll_real64 :: x1,x2,x3,y1,y2,y3,xx,ey,erreur,f
284 
285  ! step = mesh%delta
286 
287  ! ! premier newton
288 
289  ! erreur = 1._f64
290 
291  ! do while(erreur > 1.E-12)
292 
293  ! f =
294 
295  ! xx =
296 
297  ! erreur = abs(f)
298 
299  ! enddo
300 
301  ! xx = z1 - uyn(n_j)
302 
303  ! ! deuxième newton
304 
305  ! zz2 =
306 
307  ! ! dernière égalité
308 
309  ! call get_cell_vertices_index( xx, zz2, mesh, i1, i2, i3 )
310 
311  ! x1 = mesh%cartesian_coord(1,i1)
312  ! x2 = mesh%cartesian_coord(1,i2)
313  ! x3 = mesh%cartesian_coord(1,i3)
314  ! y1 = mesh%cartesian_coord(2,i1)
315  ! y2 = mesh%cartesian_coord(2,i2)
316  ! y3 = mesh%cartesian_coord(2,i3)
317 
318  ! a2 = 0.5_f64/aire
319  ! y3y = y3 - y
320  ! y2y = y2 - y
321  ! y1y = y1 - y
322  ! x3x = x3 - x
323  ! x2x = x2 - x
324  ! x1x = x1 - x
325 
326  ! l1 = a2 * abs( x2x*y3y - x3x*y2y ) ! barycentric coordinates
327  ! l2 = a2 * abs( x1x*y3y - x3x*y1y )
328  ! l3 = 1._f64 - l1 - l2
329  ! ey = l1*uxn(i1) + l2*uxn(i2) + l3*uxn(i3)
330 
331  ! zz1 = z1 - ey * dt * 0.5_f64
332 
333  ! end subroutine compute_characteristic_verlet_2d_hex
334 
335  subroutine compute_characteristic_leapfrog_2d_hex(x1, x2, uxn, uyn, dxux, dyux, dxuy, dyuy, i, y1, y2, dt)
336 
337  sll_real64, dimension(:), intent(in):: uxn, uyn, dxux, dyux, dxuy, dyuy
338  sll_real64, intent(in) :: dt
339  sll_real64, intent(in) :: x1, x2 ! point of the characteristic at tn+1
340  sll_real64, intent(out) :: y1, y2 ! point of the characteristic at tn
341  sll_int32, intent(in) :: i
342  sll_real64 :: d1x, d1y, dij0, dij1
343 
344  d1x = dt*uxn(i)
345  d1y = dt*uyn(i)
346 
347  dij0 = d1x - dt*(d1x*dxux(i) + d1y*dyux(i))
348  dij1 = d1y - dt*(d1y*dyuy(i) + d1x*dxuy(i))
349 
350  y1 = x1 - 2._f64*dij0
351  y2 = x2 - 2._f64*dij1
352 
354 
355  subroutine sll_s_compute_characteristic_adams2_2d_hex(x1, x2, uxn, uyn, uxn_1, uyn_1, &
356  dxuxn, dyuxn, dxuyn, dyuyn, i, y1, y2, dt)
357  sll_real64, dimension(:), intent(in):: uxn, uyn, uxn_1, uyn_1
358  sll_real64, dimension(:), intent(in):: dxuxn, dyuxn, dxuyn, dyuyn
359  sll_real64, intent(in) :: dt
360  sll_real64, intent(in) :: x1, x2 ! point of the characteristic at tn+1
361  sll_real64, intent(out) :: y1, y2 ! point of the characteristic at tn
362  sll_int32, intent(in) :: i
363  sll_real64 :: d1x, d1y, dij0, dij1, uxn1, uyn1
364 
365  uxn1 = 2._f64*uxn(i) - uxn_1(i)
366  uyn1 = 2._f64*uyn(i) - uyn_1(i)
367 
368  d1x = 0.5_f64*dt*(uxn1 + uxn(i))
369  d1y = 0.5_f64*dt*(uyn1 + uyn(i))
370 
371  dij0 = d1x - 0.5_f64*dt*(d1x*dxuxn(i) + d1y*dyuxn(i))
372  dij1 = d1y - 0.5_f64*dt*(d1x*dxuyn(i) + d1y*dyuyn(i))
373 
374  y1 = x1 - dij0
375  y2 = x2 - dij1
376 
378 
379  subroutine compute_characteristic_adams3_2d_hex(x1, x2, uxn, uyn, uxn_1, uyn_1, &
380  uxn_2, uyn_2, dxuxn, dyuxn, dxuyn, dyuyn, i, y1, y2, dt)
381  sll_real64, dimension(:), intent(in):: uxn, uyn, uxn_1, uyn_1, uxn_2, uyn_2
382  sll_real64, dimension(:), intent(in):: dxuxn, dyuxn, dxuyn, dyuyn
383  sll_real64, intent(in) :: dt
384  sll_real64, intent(in) :: x1, x2 ! point of the characteristic at tn+1
385  sll_real64, intent(out) :: y1, y2 ! point of the characteristic at tn
386  sll_int32, intent(in) :: i
387  sll_real64 :: d1x, d1y, dij0, dij1, uxn1, uyn1, erreur
388  sll_real64 :: a, b, c, d, det, gx, gy, xn, yn, xn_1, yn_1
389  sll_real64 :: uxn_loc, uyn_loc, uxn_1_loc, uyn_1_loc
390  sll_real64 :: dxuxn_loc, dyuxn_loc, dxuyn_loc, dyuyn_loc
391  sll_real64 :: dxuxn_1_loc, dyuxn_1_loc, dxuyn_1_loc, dyuyn_1_loc
392 
393 #ifdef DEBUG
394  sll_real64 :: dummy
395  dummy = dxuxn(1) + dxuyn(1) + dyuxn(1) + dyuyn(1)
396 #endif
397 
398  uxn1 = 3._f64*uxn(i) - 3._f64*uxn_1(i) + uxn_2(i)
399  uyn1 = 3._f64*uyn(i) - 3._f64*uyn_1(i) + uyn_2(i)
400 
401  ! Uxn1 = 0.5*x1*tan(tn+dt)
402  ! Uyn1 = 0.5*x2*tan(tn+dt)
403 
404  d1x = dt*(5._f64*uxn1 + 8._f64*uxn_1(i) - uxn_2(i))/12._f64
405  d1y = dt*(5._f64*uyn1 + 8._f64*uyn_1(i) - uyn_2(i))/12._f64
406 
407  erreur = 1._f64
408 
409  do while (erreur > 1.e-12)
410 
411  xn = x1 - d1x
412  yn = x2 - d1y
413 
414  ! interpolation de uxn(xn), uyn(yn), dxUxn,dyUxn,dxUyn,dyUyn
415  ! à faire ici
416 
417  xn_1 = x1 - 2._f64*dt*(uxn1 + 2*uxn_loc) + 4._f64*d1x
418  yn_1 = x2 - 2._f64*dt*(uyn1 + 2*uyn_loc) + 4._f64*d1y
419 
420  ! interpolation de uxn_1(xn_1), uyn_1(yn_1), dxUxn_1,dyUxn_1,dxUyn_1,dyUyn_1
421  ! à faire ici
422 
423  a = 1._f64 + dt*(2._f64*dxuxn_loc - dxuxn_1_loc)/3._f64
424  b = dt*(2._f64*dyuxn_loc - dyuxn_1_loc)/3._f64
425  c = dt*(2._f64*dxuyn_loc - dxuyn_1_loc)/3._f64
426  d = 1._f64 + dt*(2._f64*dyuyn_loc - dyuyn_1_loc)/3._f64
427 
428  det = a*d - b*c
429 
430  a = a/det
431  b = b/det
432  c = c/det
433  d = d/det
434 
435  gx = d1x - dt*(8._f64*uxn_loc - uxn_1_loc + 5._f64*uxn1)/12._f64
436  gy = d1y - dt*(8._f64*uyn_loc - uyn_1_loc + 5._f64*uyn1)/12._f64
437 
438  dij0 = d1x - (+d*gx - b*gy)
439  dij1 = d1y - (-c*gx + a*gy)
440 
441  erreur = abs(gx) + abs(gy)
442  d1x = dij0
443  d1y = dij1
444 
445  end do
446 
447  y1 = x1 - d1x
448  y2 = x2 - d1y
449 
451 
452  subroutine compute_characteristic_adams4_2d_hex(x1, x2, uxn, uyn, uxn_1, uyn_1, &
453  uxn_2, uyn_2, uxn_3, uyn_3, dxuxn, dyuxn, dxuyn, dyuyn, i, y1, y2, dt)
454  sll_real64, dimension(:), intent(in):: uxn, uyn, uxn_1, uyn_1, uxn_2, uyn_2
455  sll_real64, dimension(:), intent(in):: uxn_3, uyn_3
456  sll_real64, dimension(:), intent(in):: dxuxn, dyuxn, dxuyn, dyuyn
457  sll_real64, intent(in) :: dt
458  sll_real64, intent(in) :: x1, x2 ! point of the characteristic at tn+1
459  sll_real64, intent(out) :: y1, y2 ! point of the characteristic at tn
460  sll_int32, intent(in) :: i
461  sll_real64 :: d1x, d1y, dij0, dij1, uxn1, uyn1, erreur
462  sll_real64 :: a, b, c, d, det, gx, gy, xn, yn, xn_1, yn_1
463  sll_real64 :: xn_2, yn_2
464  sll_real64 :: uxn_loc, uyn_loc, uxn_1_loc, uyn_1_loc, uxn_2_loc, uyn_2_loc
465  sll_real64 :: dxuxn_loc, dyuxn_loc, dxuyn_loc, dyuyn_loc
466  sll_real64 :: dxuxn_1_loc, dyuxn_1_loc, dxuyn_1_loc, dyuyn_1_loc
467  sll_real64 :: dxuxn_2_loc, dyuxn_2_loc, dxuyn_2_loc, dyuyn_2_loc
468 #ifdef DEBUG
469  sll_real64 :: dummy
470  dummy = dxuxn(1) + dxuyn(1) + dyuxn(1) + dyuyn(1) + uyn_3(1)
471 #endif
472 
473  uxn1 = 4._f64*uxn(i) - 6._f64*uxn_1(i) + 4._f64*uxn_2(i) - uxn_3(i)
474  uyn1 = 4._f64*uyn(i) - 6._f64*uyn_1(i) + 4._f64*uxn_2(i) - uxn_3(i)
475 
476  d1x = dt*(9._f64*uxn1 + 19._f64*uxn(i) - 5._f64*uxn_1(i) + uxn_2(i))/24._f64
477  d1y = dt*(9._f64*uyn1 + 19._f64*uyn(i) - 5._f64*uyn_1(i) + uyn_2(i))/24._f64
478 
479  erreur = 1._f64
480 
481  do while (erreur > 1.e-12)
482 
483  xn = x1 - d1x
484  yn = y2 - d1y
485  ! interpolation de uxn(xn), uyn(yn), dxUxn,dyUxn,dxUyn,dyUyn
486  ! à faire ici
487 
488  xn_1 = x1 + 4._f64*d1x - 2._f64*dt*(2._f64*uxn_loc + uxn1)
489  yn_1 = y2 + 4._f64*d1y - 2._f64*dt*(2._f64*uyn_loc + uyn1)
490  ! interpolation de uxn_1(xn_1), uyn_1(yn_1), dxUxn_1,dyUxn_1,dxUyn_1,dyUyn_1
491 
492  ! xn_2 = x1 + 9.*d1x - 3.*dt*(3.*uxn + uxn1)
493  ! yn_2 = y2 + 9.*d1y - 3.*dt*(3.*uyn + uyn1)
494 
495  xn_2 = x1 + 27._f64*d1x - dt*(18._f64*uxn_loc + 12._f64*uxn1)
496  yn_2 = x2 + 27._f64*d1y - dt*(18._f64*uyn_loc + 12._f64*uyn1)
497 
498  ! interpolation de uxn_2(xn_2), uyn_2(yn_2), dxUxn_2,dyUxn_2,dxUyn_2,dyUyn_2
499 
500  a = 1._f64 + dt*(19._f64*dxuxn_loc + 20._f64*dxuxn_1_loc &
501  - 9._f64*dxuxn_2_loc)/24._f64
502  b = dt*(19._f64*dyuxn_loc + 20._f64*dyuxn_1_loc &
503  - 9._f64*dyuxn_2_loc)/24._f64
504  c = dt*(19._f64*dxuyn_loc + 20._f64*dxuyn_1_loc &
505  - 9._f64*dxuyn_2_loc)/24._f64
506  d = 1._f64 + dt*(19._f64*dyuyn_loc + 20._f64*dyuyn_1_loc &
507  - 9._f64*dyuyn_2_loc)/24._f64
508 
509  det = a*d - b*c
510 
511  a = a/det
512  b = b/det
513  c = c/det
514  d = d/det
515 
516  gx = d1x - dt*(9.*uxn1 + 19.*uxn_loc - 5.*uxn_1_loc + uxn_2_loc)/24._f64
517  gy = d1y - dt*(9.*uyn1 + 19.*uyn_loc - 5.*uyn_1_loc + uyn_2_loc)/24._f64
518 
519  dij0 = d1x - (+d*gx - b*gy)
520  dij1 = d1y - (-c*gx + a*gy)
521 
522  erreur = abs(gx) + abs(gy)
523  d1x = dij0
524  d1y = dij1
525 
526  end do
527 
528  y1 = x1 - d1x
529  y2 = x2 - d1y
530 
532 
533 end module sll_m_euler_2d_hex
subroutine, public sll_s_compute_characteristic_adams2_2d_hex(x1, x2, uxn, uyn, uxn_1, uyn_1, dxuxn, dyuxn, dxuyn, dyuyn, i, y1, y2, dt)
subroutine, public sll_s_compute_characteristic_euler_2d_hex(x1, x2, uxn, uyn, i, y1, y2, dt)
subroutine compute_characteristic_leapfrog_2d_hex(x1, x2, uxn, uyn, dxux, dyux, dxuy, dyuy, i, y1, y2, dt)
subroutine compute_characteristic_adams4_2d_hex(x1, x2, uxn, uyn, uxn_1, uyn_1, uxn_2, uyn_2, uxn_3, uyn_3, dxuxn, dyuxn, dxuyn, dyuyn, i, y1, y2, dt)
subroutine compute_characteristic_adams3_2d_hex(x1, x2, uxn, uyn, uxn_1, uyn_1, uxn_2, uyn_2, dxuxn, dyuxn, dxuyn, dyuyn, i, y1, y2, dt)
    Report Typos and Errors