IMEX_SfloW2D  0.9
Shallowwatergranularflowmodel
init_2d.f90
Go to the documentation of this file.
1 !********************************************************************************
3 !
6 !********************************************************************************
7 
8 MODULE init_2d
9 
12 
13  IMPLICIT none
14 
15  REAL*8, ALLOCATABLE :: q_init(:,:,:)
16 
17  REAL*8, ALLOCATABLE :: thickness_init(:,:)
18 
21  REAL*8 :: riemann_interface
22 
23 
24  REAL*8 :: hb_w
25  REAL*8 :: u_w
26  REAL*8 :: v_w
27  REAL*8 :: xs_w
28  REAL*8 :: t_w
29 
30  REAL*8 :: hb_e
31  REAL*8 :: u_e
32  REAL*8 :: v_e
33  REAL*8 :: xs_e
34  REAL*8 :: t_e
35 
36 
37 CONTAINS
38 
39 
40  !******************************************************************************
42  !
47  !******************************************************************************
48 
49  SUBROUTINE riemann_problem
50 
51  USE constitutive_2d, ONLY : qp_to_qc
52 
54 
55  ! USE geometry_2d, ONLY : x0 , xN , y0 , yN
56 
57  USE parameters_2d, ONLY : n_vars , verbose_level
58 
59  USE solver_2d, ONLY : q
60 
61  IMPLICIT none
62 
63  ! REAL*8 :: hB !< height + topography
64  ! REAL*8 :: u !< velocity
65  ! REAL*8 :: v !< velocity
66 
67  REAL*8 :: qp(n_vars,comp_cells_x,comp_cells_y) , qj(n_vars)
68 
69  INTEGER :: j,k
70  INTEGER :: i1
71 
72  REAL*8 :: eps
73 
74  IF ( verbose_level .GE. 1 ) WRITE(*,*) 'Riemann problem initialization'
75 
76  i1 = 0
77 
78  riemann_int_search:DO j = 1,comp_cells_x
79 
80  IF ( x_comp(j) .LT. riemann_interface ) THEN
81 
82  i1 = j
83 
84  ELSE
85 
86  EXIT riemann_int_search
87 
88  END IF
89 
90  END DO riemann_int_search
91 
92  eps = 1.d-10
93 
94  ! Left initial state
95  qp(1,1:i1,:) = hb_w
96  qp(2,1:i1,:) = u_w
97  qp(3,1:i1,:) = v_w
98 
99  IF ( solid_transport_flag ) THEN
100 
101  qp(4,1:i1,:) = xs_w
102 
103  IF ( temperature_flag ) qp(5,1:i1,:) = t_w
104 
105  ELSE
106 
107  IF ( temperature_flag ) qp(4,1:i1,:) = t_w
108 
109  END IF
110 
111 
112  IF ( verbose_level .GE. 1 ) WRITE(*,*) 'Left state'
113 
114  DO j = 1,i1
115 
116  DO k = 1,comp_cells_y
117 
118  ! evaluate the vector of conservative variables
119  CALL qp_to_qc( qp(:,j,k) , b_cent(j,k) , qj )
120 
121  q(1:n_vars,j,k) = qj
122 
123  IF ( verbose_level .GE. 1 ) THEN
124 
125  WRITE(*,*) j,k,b_cent(j,k)
126  WRITE(*,*) qp(:,j,k)
127  WRITE(*,*) q(1:n_vars,j,k)
128 
129  END IF
130 
131  ENDDO
132 
133  END DO
134 
135  IF ( verbose_level .GE. 1 ) READ(*,*)
136 
137  ! Right initial state
138  qp(1,i1+1:comp_cells_x,:) = hb_e
139  qp(2,i1+1:comp_cells_x,:) = u_e
140  qp(3,i1+1:comp_cells_x,:) = v_e
141 
142  IF ( solid_transport_flag ) THEN
143 
144  qp(4,i1+1:comp_cells_x,:) = xs_e
145 
146  IF ( temperature_flag ) qp(5,i1+1:comp_cells_x,:) = t_e
147 
148  ELSE
149 
150  IF ( temperature_flag ) qp(4,i1+1:comp_cells_x,:) = t_e
151 
152  END IF
153 
154 
155  IF ( verbose_level .GE. 1 ) WRITE(*,*) 'Right state'
156 
157  DO j = i1+1,comp_cells_x
158 
159  DO k = 1,comp_cells_y
160 
161  ! evaluate the vector of conservative variables
162  CALL qp_to_qc( qp(:,j,k) , b_cent(j,k) , qj )
163 
164  q(1:n_vars,j,k) = qj
165 
166  IF ( verbose_level .GE. 1 ) THEN
167 
168  WRITE(*,*) j,k,b_cent(j,k)
169  WRITE(*,*) qp(:,j,k)
170  WRITE(*,*) q(1:n_vars,j,k)
171 
172  END IF
173 
174  END DO
175 
176  ENDDO
177 
178  IF ( verbose_level .GE. 1 ) READ(*,*)
179 
180  RETURN
181 
182  END SUBROUTINE riemann_problem
183 
184  !******************************************************************************
186  !
190  !******************************************************************************
191 
192  SUBROUTINE initial_conditions
194  USE constitutive_2d, ONLY : qp_to_qc
195 
196  USE geometry_2d, ONLY : x_comp , comp_cells_x, y_comp , comp_cells_y , &
197  b_cent
198 
199  USE geometry_2d, ONLY : dx , dy
200 
203 
204  USE solver_2d, ONLY : q
205 
206  IMPLICIT none
207 
208  REAL*8 :: qp(n_vars,comp_cells_x,comp_cells_y) , qj(n_vars)
209 
210  INTEGER :: j,k
211 
212  DO j=1,comp_cells_x
213 
214  DO k=1,comp_cells_y
215 
216  qp(1,j,k) = thickness_function(x_comp(j),y_comp(k),b_cent(j,k))
217 
218  qp(2,j,k) = velocity_u_function(x_comp(j),y_comp(k))
219 
220  qp(3,j,k) = velocity_v_function(x_comp(j),y_comp(k))
221 
222  IF ( solid_transport_flag ) THEN
223 
224  qp(4,j,k) = sediment_function(x_comp(j),y_comp(k))
225 
226  IF ( temperature_flag ) THEN
227 
228  qp(5,j,k) = temperature_function(x_comp(j),y_comp(k))
229 
230  END IF
231 
232  ELSE
233 
234  IF ( temperature_flag ) THEN
235 
236  qp(4,j,k) = temperature_function(x_comp(j),y_comp(k))
237 
238  END IF
239 
240  END IF
241 
242  ENDDO
243 
244  ENDDO
245 
246  IF ( released_volume .GT. ( dx * dy * sum( qp(1,:,:)-b_cent(:,:) ) ) ) THEN
247 
248  ! Correction for the released volume
249  qp(1,:,:) = b_cent(:,:) + ( qp(1,:,:)-b_cent(:,:) ) * released_volume &
250  / ( dx * dy * sum( qp(1,:,:)-b_cent(:,:) ) )
251 
252  END IF
253 
254  WRITE(*,*) 'Initial volume =',dx * dy * sum( qp(1,:,:)-b_cent(:,:) )
255 
256 
257  DO j = 1,comp_cells_x
258 
259  DO k = 1,comp_cells_y
260 
261  ! evaluate the vector of conservative variables
262  CALL qp_to_qc( qp(:,j,k) , b_cent(j,k) , qj )
263 
264  q(1:n_vars,j,k) = qj
265 
266  IF ( verbose_level .GE. 1 ) WRITE(*,*) j,k,b_cent(j,k),qp(:,j,k)
267 
268  END DO
269 
270  ENDDO
271 
272  IF ( verbose_level .GE. 1 ) READ(*,*)
273 
274  IF ( source_flag ) CALL init_source
275 
276  RETURN
277 
278  END SUBROUTINE initial_conditions
279 
280  !******************************************************************************
282  !
285  !******************************************************************************
286 
287  SUBROUTINE init_source
290  USE geometry_2d, ONLY : dx , dy
291 
292  USE parameters_2d, ONLY : x_source , y_source , r_source
293  USE parameters_2d, ONLY : vfr_source , vel_source
294 
295  USE solver_2d, ONLY : source_xy
296 
297  IMPLICIT NONE
298 
299  INTEGER :: h,j,k
300 
301  REAL*8, ALLOCATABLE :: x_subgrid(:) , y_subgrid(:)
302  INTEGER, ALLOCATABLE :: check_subgrid(:)
303 
304  INTEGER n_points , n_points2
305  REAL*8 :: source_area
306 
307  n_points = 200
308  n_points2 = n_points**2
309 
310  ALLOCATE( x_subgrid(n_points2) )
311  ALLOCATE( y_subgrid(n_points2) )
312  ALLOCATE( check_subgrid(n_points2) )
313 
314  x_subgrid = 0.d0
315  y_subgrid = 0.d0
316 
317  DO h = 1,n_points
318 
319  x_subgrid(h:n_points2:n_points) = h
320  y_subgrid((h-1)*n_points+1:h*n_points) = h
321 
322  END DO
323 
324  x_subgrid = x_subgrid / ( n_points +1 )
325  y_subgrid = y_subgrid / ( n_points +1 )
326 
327  x_subgrid = ( x_subgrid - 0.5d0 ) * dx
328  y_subgrid = ( y_subgrid - 0.5d0 ) * dy
329 
330  source_xy(:,:) = 0.d0
331 
332  DO j=1,comp_cells_x
333 
334  DO k=1,comp_cells_y
335 
336  check_subgrid = 0
337 
338  WHERE ( ( x_comp(j) + x_subgrid - x_source )**2 &
339  + ( y_comp(k) + y_subgrid - y_source )**2 < r_source**2 )
340 
341  check_subgrid = 1
342 
343  END WHERE
344 
345  ! WRITE(*,*) x_comp(j),y_comp(k),REAL(SUM(check_subgrid))/10201.D0
346 
347  source_xy(j,k) = REAL(sum(check_subgrid))/n_points2
348 
349  ENDDO
350 
351  ENDDO
352 
353  source_area = dx*dy*sum(source_xy)
354 
355  WRITE(*,*) 'Source area =',source_area,' Error =',abs( 1.d0 - &
356  dx*dy*sum(source_xy) / ( 4.d0*atan(1.d0)*r_source**2 ) )
357 
358  vel_source = vfr_source / source_area
359 
360  WRITE(*,*) 'Vel source =',vel_source
361 
362  END SUBROUTINE init_source
363 
364  !******************************************************************************
366  !
373  !******************************************************************************
374 
375  REAL*8 FUNCTION thickness_function(x,y,Bj)
378 
379  IMPLICIT NONE
380 
381  REAL*8, INTENT(IN) :: x,y
382  REAL*8, INTENT(IN) :: Bj
383 
384  REAL*8, PARAMETER :: pig = 4.d0*atan(1.d0)
385  REAL*8 :: R
386 
387  ! example 1D from Kurganov and Petrova 2007
388  !IF(y.LE.0.d0)THEN
389  ! thickness_function=0.4d0+Bj
390  !ELSE
391  ! thickness_function=Bj
392  !ENDIF
393 
394  ! example 2D from Kurganov and Petrova 2007
395  ! thickness_function=MAX(0.25,Bj)
396 
397  r = ( released_volume / pig )**(1.0/3.0)
398 
399  IF ( dsqrt( (x-x_release)**2 + (y-y_release)**2 ) .LE. r ) THEN
400 
401  thickness_function = bj + r
402 
403  ELSE
404 
405  thickness_function = bj
406 
407  ENDIF
408 
409  END FUNCTION thickness_function
410 
411  !******************************************************************************
413  !
419  !******************************************************************************
420 
421  REAL*8 FUNCTION velocity_u_function(x,y)
422 
425 
426  USE geometry_2d, ONLY : x0 , y0 , dx , dy
427  USE geometry_2d, ONLY : x_stag , y_stag , b_ver
428 
429  IMPLICIT NONE
430 
431  REAL*8, INTENT(IN) :: x,y
432 
433  REAL*8, PARAMETER :: pig = 4.0*atan(1.0)
434  REAL*8 :: R
435 
436  INTEGER :: idx1 , idy1
437  REAL*8 :: coeff_x , coeff_y
438 
439  REAL*8 :: dBdx1 , dBdx2 , dBdx
440  REAL*8 :: dBdy1 , dBdy2 , dBdy
441 
442  REAL*8 :: max_slope_angle_rad
443  REAL*8 :: velocity_ang_release_rad
444 
445 
446  r = ( released_volume / pig )**(1.d0/3.d0)
447 
448  ! indexes of the lower-left vertex of the cell in the computational grid
449  idx1 = ceiling( ( x_release - x0 ) / dx )
450  idy1 = ceiling( ( y_release - y0 ) / dy )
451 
452  ! relative coordinates of (x_release,y_release) within the cell
453  coeff_x = ( x_release - x_stag(idx1) ) / dx
454  coeff_y = ( y_release - y_stag(idy1) ) / dy
455 
456 
457  ! x-derivatives at bottom and top edges of the cell
458  dbdx1 = ( b_ver(idx1+1,idy1) - b_ver(idx1,idy1) ) / dx
459  dbdx2 = ( b_ver(idx1+1,idy1+1) - b_ver(idx1,idy1+1) ) / dx
460 
461  ! x-derivative of terrain at (x_release,y_release)
462  dbdx = coeff_y * dbdx2 + ( 1.d0 - coeff_y ) * dbdx1
463 
464  ! y-derivatives at left and right edges of the cell
465  dbdy1 = ( b_ver(idx1,idy1+1) - b_ver(idx1,idy1) ) / dy
466  dbdy2 = ( b_ver(idx1+1,idy1+1) - b_ver(idx1+1,idy1) ) / dx
467 
468  ! y-derivative of terrain at (x_release,y_release)
469  dbdy = coeff_x * dbdy2 + ( 1.d0 - coeff_x ) * dbdy1
470 
471 
472  ! direction of maximum slope in radians
473  max_slope_angle_rad = datan2(dbdy,dbdx)
474 
475  IF ( verbose_level .GE. 1 ) THEN
476 
477  WRITE(*,*) x0,x_stag(1),y0,y_stag(1),dx,dy
478  WRITE(*,*) '---',x_stag(idx1),x_release,x_stag(idx1+1),coeff_x
479  WRITE(*,*) '---',y_stag(idy1),y_release,y_stag(idy1+1),coeff_y
480 
481  WRITE(*,*) b_ver(idx1,idy1),b_ver(idx1+1,idy1)
482  WRITE(*,*) b_ver(idx1,idy1+1),b_ver(idx1+1,idy1+1)
483  WRITE(*,*) 'dbdx,dbdy,angle',dbdx,dbdy,max_slope_angle_rad*180.d0/pig
484 
485  READ(*,*)
486 
487  END IF
488 
489  IF ( dsqrt( (x-x_release)**2 + (y-y_release)**2 ) .LE. r ) THEN
490 
491  velocity_ang_release_rad = velocity_ang_release * pig / 180.d0
492 
493  IF ( velocity_ang_release .GE. 0.d0 ) THEN
494 
495  ! angle departing from positive x-axis
497  * cos( velocity_ang_release * ( 2.d0 * pig / 360.d0 ) )
498 
499  ELSE
500 
501  ! angle departing from maximum slope direction
503  * cos( max_slope_angle_rad + velocity_ang_release_rad )
504 
505  END IF
506 
507  ELSE
508 
509  velocity_u_function = 0.d0
510 
511  ENDIF
512 
513  END FUNCTION velocity_u_function
514 
515  !******************************************************************************
517  !
523  !******************************************************************************
524 
525  REAL*8 FUNCTION velocity_v_function(x,y)
526 
529 
530  USE geometry_2d, ONLY : x0 , y0 , dx , dy
531  USE geometry_2d, ONLY : x_stag , y_stag , b_ver
532 
533  IMPLICIT NONE
534 
535  REAL*8, INTENT(IN) :: x,y
536 
537  REAL*8, PARAMETER :: pig = 4.0*atan(1.0)
538  REAL*8 :: R
539 
540  INTEGER :: idx1 , idy1
541  REAL*8 :: coeff_x , coeff_y
542 
543  REAL*8 :: dBdx1 , dBdx2 , dBdx
544  REAL*8 :: dBdy1 , dBdy2 , dBdy
545 
546  REAL*8 :: max_slope_angle_rad
547  REAL*8 :: velocity_ang_release_rad
548 
549 
550  r = ( released_volume / pig )**(1.0/3.0)
551 
552  ! indexes of the lower-left vertex of the cell in the computational grid
553  idx1 = ceiling( ( x_release - x0 ) / dx )
554  idy1 = ceiling( ( y_release - y0 ) / dy )
555 
556  ! relative coordinates of (x_release,y_release) within the cell
557  coeff_x = ( x_release - x_stag(idx1) ) / dx
558  coeff_y = ( y_release - y_stag(idy1) ) / dy
559 
560 
561  ! x-derivatives at bottom and top edges of the cell
562  dbdx1 = ( b_ver(idx1+1,idy1) - b_ver(idx1,idy1) ) / dx
563  dbdx2 = ( b_ver(idx1+1,idy1+1) - b_ver(idx1,idy1+1) ) / dx
564 
565  ! x-derivative of terrain at (x_release,y_release)
566  dbdx = coeff_y * dbdx2 + ( 1.d0 - coeff_y ) * dbdx1
567 
568  ! y-derivatives at left and right edges of the cell
569  dbdy1 = ( b_ver(idx1,idy1+1) - b_ver(idx1,idy1) ) / dy
570  dbdy2 = ( b_ver(idx1+1,idy1+1) - b_ver(idx1+1,idy1) ) / dx
571 
572  ! y-derivative of terrain at (x_release,y_release)
573  dbdy = coeff_x * dbdy2 + ( 1.d0 - coeff_x ) * dbdy1
574 
575 
576 
577  IF ( dsqrt( (x-x_release)**2 + (y-y_release)**2 ) .LE. r ) THEN
578 
579  velocity_ang_release_rad = velocity_ang_release * pig / 180.d0
580 
581  IF ( velocity_ang_release .GE. 0.d0 ) THEN
582 
583  ! angle departing from positive x-axis
585  * sin( velocity_ang_release * ( 2.d0 * pig / 360.d0 ) )
586 
587  ELSE
588 
589  ! angle departing from maximum slope direction
591  * sin( max_slope_angle_rad + velocity_ang_release_rad )
592 
593  END IF
594 
595  ELSE
596 
597  velocity_v_function = 0.d0
598 
599  ENDIF
600 
601  END FUNCTION velocity_v_function
602 
603  !******************************************************************************
605  !
611  !******************************************************************************
612 
613  REAL*8 FUNCTION sediment_function(x,y)
614 
616  USE parameters_2d, ONLY : xs_init , xs_ambient
617 
618  IMPLICIT NONE
619 
620  REAL*8, INTENT(IN) :: x,y
621 
622  REAL*8, PARAMETER :: pig = 4.0*atan(1.0)
623  REAL*8 :: R
624 
625  r = ( released_volume / pig )**(1.0/3.0)
626 
627  IF ( dsqrt( (x-x_release)**2 + (y-y_release)**2 ) .LE. r ) THEN
628 
630 
631  ELSE
632 
634 
635  ENDIF
636 
637  END FUNCTION sediment_function
638 
639 
640 
641  !******************************************************************************
643  !
649  !******************************************************************************
650 
651  REAL*8 FUNCTION temperature_function(x,y)
652 
654  USE parameters_2d, ONLY : t_init , t_ambient
655 
656  IMPLICIT NONE
657 
658  REAL*8, INTENT(IN) :: x,y
659 
660  REAL*8, PARAMETER :: pig = 4.0*atan(1.0)
661  REAL*8 :: R
662 
663  r = ( released_volume / pig )**(1.0/3.0)
664 
665  IF ( dsqrt( (x-x_release)**2 + (y-y_release)**2 ) .LE. r ) THEN
666 
668 
669  ELSE
670 
672 
673  ENDIF
674 
675  END FUNCTION temperature_function
676 
677 END MODULE init_2d
real *8 dy
Control volumes size.
Definition: geometry_2d.f90:59
real *8, dimension(:), allocatable x_comp
Location of the centers (x) of the control volume of the domain.
Definition: geometry_2d.f90:14
real *8 y0
Bottom of the physical domain.
Definition: geometry_2d.f90:60
real *8, dimension(:,:), allocatable b_cent
Topography at the centers of the control volumes.
Definition: geometry_2d.f90:35
integer comp_cells_x
Number of control volumes x in the comp. domain.
Definition: geometry_2d.f90:64
real *8 vel_source
real *8, dimension(:,:), allocatable thickness_init
Definition: init_2d.f90:17
real *8, dimension(:), allocatable y_comp
Location of the centers (y) of the control volume of the domain.
Definition: geometry_2d.f90:20
logical temperature_flag
Flag to choose if we model temperature transport.
real *8, dimension(:,:), allocatable source_xy
Array defining fraction of cells affected by source term.
Definition: solver_2d.f90:62
real *8 t_init
Initial temperature of the pile of material.
real *8 u_e
Right velocity x.
Definition: init_2d.f90:31
real *8 v_w
Left velocity y.
Definition: init_2d.f90:26
Parameters.
real *8 dx
Control volumes size.
Definition: geometry_2d.f90:56
real *8 y_release
Initial y-coordinate of the pile.
integer comp_cells_y
Number of control volumes y in the comp. domain.
Definition: geometry_2d.f90:66
Numerical solver.
Definition: solver_2d.f90:12
real *8 function sediment_function(x, y)
Sediment function.
Definition: init_2d.f90:614
real *8 riemann_interface
Riemann problem interface relative position. It is a value between 0 and 1.
Definition: init_2d.f90:21
Initial solution.
Definition: init_2d.f90:8
real *8 u_w
Left velocity x.
Definition: init_2d.f90:25
real *8 function thickness_function(x, y, Bj)
Thickness function.
Definition: init_2d.f90:376
real *8 velocity_ang_release
Initial velocity direction (angle in degree): .
real *8 velocity_mod_release
Initial velocity module of the pile.
real *8 released_volume
Initial volume of the flow.
integer n_vars
Number of conservative variables.
real *8 t_ambient
Ambient temperature.
subroutine initial_conditions
Problem initialization.
Definition: init_2d.f90:193
logical source_flag
Flag to choose if there is a source of mass within the domain.
real *8 vfr_source
Constitutive equations.
real *8 x_release
Initial x-coordiante of the pile.
real *8 x0
Left of the physical domain.
Definition: geometry_2d.f90:57
real *8, dimension(:,:), allocatable b_ver
Topography at the vertices of the control volumes.
Definition: geometry_2d.f90:32
Grid module.
Definition: geometry_2d.f90:7
real *8 t_w
Left temperature.
Definition: init_2d.f90:28
real *8 v_e
Right velocity y.
Definition: init_2d.f90:32
real *8 function velocity_u_function(x, y)
Velocity u function.
Definition: init_2d.f90:422
integer verbose_level
real *8 xs_init
Initial sediment concentration in the pile of material.
real *8, dimension(:), allocatable x_stag
Location of the boundaries (x) of the control volumes of the domain.
Definition: geometry_2d.f90:17
real *8 xs_ambient
Ambient sediment concentration.
real *8 function temperature_function(x, y)
Temperature function.
Definition: init_2d.f90:652
real *8 function velocity_v_function(x, y)
Velocity v function.
Definition: init_2d.f90:526
real *8 t_e
Right temperature.
Definition: init_2d.f90:34
subroutine qp_to_qc(qp, B, qc)
Physical to conservative variables.
subroutine riemann_problem
Riemann problem initialization.
Definition: init_2d.f90:50
real *8 xs_e
Right sediment concentration.
Definition: init_2d.f90:33
real *8 xs_w
Left sediment concentration.
Definition: init_2d.f90:27
real *8, dimension(:), allocatable y_stag
Location of the boundaries (x) of the control volumes of the domain.
Definition: geometry_2d.f90:23
real *8, dimension(:,:,:), allocatable q_init
Definition: init_2d.f90:15
logical solid_transport_flag
Flag to choose if we model solid phase transport.
real *8 hb_w
Left height.
Definition: init_2d.f90:24
real *8 hb_e
Right height.
Definition: init_2d.f90:30
subroutine init_source
Source initialization.
Definition: init_2d.f90:288
real *8, dimension(:,:,:), allocatable q
Conservative variables.
Definition: solver_2d.f90:33