74 IF (
verbose_level .GE. 1 )
WRITE(*,*)
'Riemann problem initialization' 86 EXIT riemann_int_search
90 END DO riemann_int_search
99 IF ( solid_transport_flag )
THEN 103 IF ( temperature_flag ) qp(5,1:i1,:) =
t_w 107 IF ( temperature_flag ) qp(4,1:i1,:) =
t_w 125 WRITE(*,*) j,k,
b_cent(j,k)
142 IF ( solid_transport_flag )
THEN 168 WRITE(*,*) j,k,
b_cent(j,k)
208 REAL*8 :: qp(
n_vars,comp_cells_x,comp_cells_y) , qj(
n_vars)
222 IF ( solid_transport_flag )
THEN 226 IF ( temperature_flag )
THEN 234 IF ( temperature_flag )
THEN 249 qp(1,:,:) = b_cent(:,:) + ( qp(1,:,:)-b_cent(:,:) ) *
released_volume &
250 / (
dx *
dy * sum( qp(1,:,:)-b_cent(:,:) ) )
254 WRITE(*,*)
'Initial volume =',
dx *
dy * sum( qp(1,:,:)-b_cent(:,:) )
257 DO j = 1,comp_cells_x
259 DO k = 1,comp_cells_y
262 CALL qp_to_qc( qp(:,j,k) , b_cent(j,k) , qj )
266 IF (
verbose_level .GE. 1 )
WRITE(*,*) j,k,b_cent(j,k),qp(:,j,k)
301 REAL*8,
ALLOCATABLE :: x_subgrid(:) , y_subgrid(:)
302 INTEGER,
ALLOCATABLE :: check_subgrid(:)
304 INTEGER n_points , n_points2
305 REAL*8 :: source_area
308 n_points2 = n_points**2
310 ALLOCATE( x_subgrid(n_points2) )
311 ALLOCATE( y_subgrid(n_points2) )
312 ALLOCATE( check_subgrid(n_points2) )
319 x_subgrid(h:n_points2:n_points) = h
320 y_subgrid((h-1)*n_points+1:h*n_points) = h
324 x_subgrid = x_subgrid / ( n_points +1 )
325 y_subgrid = y_subgrid / ( n_points +1 )
327 x_subgrid = ( x_subgrid - 0.5d0 ) *
dx 328 y_subgrid = ( y_subgrid - 0.5d0 ) *
dy 338 WHERE ( ( x_comp(j) + x_subgrid - x_source )**2 &
339 + ( y_comp(k) + y_subgrid - y_source )**2 < r_source**2 )
347 source_xy(j,k) =
REAL(sum(check_subgrid))/n_points2
355 WRITE(*,*)
'Source area =',source_area,
' Error =',abs( 1.d0 - &
381 REAL*8,
INTENT(IN) :: x,y
382 REAL*8,
INTENT(IN) :: Bj
384 REAL*8,
PARAMETER :: pig = 4.d0*atan(1.d0)
431 REAL*8,
INTENT(IN) :: x,y
433 REAL*8,
PARAMETER :: pig = 4.0*atan(1.0)
436 INTEGER :: idx1 , idy1
437 REAL*8 :: coeff_x , coeff_y
439 REAL*8 :: dBdx1 , dBdx2 , dBdx
440 REAL*8 :: dBdy1 , dBdy2 , dBdy
442 REAL*8 :: max_slope_angle_rad
443 REAL*8 :: velocity_ang_release_rad
446 r = ( released_volume / pig )**(1.d0/3.d0)
449 idx1 = ceiling( ( x_release - x0 ) / dx )
450 idy1 = ceiling( ( y_release - y0 ) / dy )
453 coeff_x = ( x_release -
x_stag(idx1) ) / dx
454 coeff_y = ( y_release -
y_stag(idy1) ) / dy
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
462 dbdx = coeff_y * dbdx2 + ( 1.d0 - coeff_y ) * dbdx1
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
469 dbdy = coeff_x * dbdy2 + ( 1.d0 - coeff_x ) * dbdy1
473 max_slope_angle_rad = datan2(dbdy,dbdx)
475 IF ( verbose_level .GE. 1 )
THEN 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
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
489 IF ( dsqrt( (x-x_release)**2 + (y-y_release)**2 ) .LE. r )
THEN 503 * cos( max_slope_angle_rad + velocity_ang_release_rad )
535 REAL*8,
INTENT(IN) :: x,y
537 REAL*8,
PARAMETER :: pig = 4.0*atan(1.0)
540 INTEGER :: idx1 , idy1
541 REAL*8 :: coeff_x , coeff_y
543 REAL*8 :: dBdx1 , dBdx2 , dBdx
544 REAL*8 :: dBdy1 , dBdy2 , dBdy
546 REAL*8 :: max_slope_angle_rad
547 REAL*8 :: velocity_ang_release_rad
550 r = ( released_volume / pig )**(1.0/3.0)
553 idx1 = ceiling( ( x_release - x0 ) / dx )
554 idy1 = ceiling( ( y_release - y0 ) / dy )
557 coeff_x = ( x_release -
x_stag(idx1) ) / dx
558 coeff_y = ( y_release -
y_stag(idy1) ) / dy
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
566 dbdx = coeff_y * dbdx2 + ( 1.d0 - coeff_y ) * dbdx1
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
573 dbdy = coeff_x * dbdy2 + ( 1.d0 - coeff_x ) * dbdy1
577 IF ( dsqrt( (x-x_release)**2 + (y-y_release)**2 ) .LE. r )
THEN 591 * sin( max_slope_angle_rad + velocity_ang_release_rad )
620 REAL*8,
INTENT(IN) :: x,y
622 REAL*8,
PARAMETER :: pig = 4.0*atan(1.0)
625 r = ( released_volume / pig )**(1.0/3.0)
627 IF ( dsqrt( (x-x_release)**2 + (y-y_release)**2 ) .LE. r )
THEN 658 REAL*8,
INTENT(IN) :: x,y
660 REAL*8,
PARAMETER :: pig = 4.0*atan(1.0)
663 r = ( released_volume / pig )**(1.0/3.0)
665 IF ( dsqrt( (x-x_release)**2 + (y-y_release)**2 ) .LE. r )
THEN real *8 dy
Control volumes size.
real *8, dimension(:), allocatable x_comp
Location of the centers (x) of the control volume of the domain.
real *8 y0
Bottom of the physical domain.
real *8, dimension(:,:), allocatable b_cent
Topography at the centers of the control volumes.
integer comp_cells_x
Number of control volumes x in the comp. domain.
real *8, dimension(:,:), allocatable thickness_init
real *8, dimension(:), allocatable y_comp
Location of the centers (y) of the control volume of the domain.
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.
real *8 t_init
Initial temperature of the pile of material.
real *8 u_e
Right velocity x.
real *8 v_w
Left velocity y.
real *8 dx
Control volumes size.
real *8 y_release
Initial y-coordinate of the pile.
integer comp_cells_y
Number of control volumes y in the comp. domain.
real *8 function sediment_function(x, y)
Sediment function.
real *8 riemann_interface
Riemann problem interface relative position. It is a value between 0 and 1.
real *8 u_w
Left velocity x.
real *8 function thickness_function(x, y, Bj)
Thickness function.
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.
logical source_flag
Flag to choose if there is a source of mass within the domain.
real *8 x_release
Initial x-coordiante of the pile.
real *8 x0
Left of the physical domain.
real *8, dimension(:,:), allocatable b_ver
Topography at the vertices of the control volumes.
real *8 t_w
Left temperature.
real *8 v_e
Right velocity y.
real *8 function velocity_u_function(x, y)
Velocity u function.
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.
real *8 xs_ambient
Ambient sediment concentration.
real *8 function temperature_function(x, y)
Temperature function.
real *8 function velocity_v_function(x, y)
Velocity v function.
real *8 t_e
Right temperature.
subroutine qp_to_qc(qp, B, qc)
Physical to conservative variables.
subroutine riemann_problem
Riemann problem initialization.
real *8 xs_e
Right sediment concentration.
real *8 xs_w
Left sediment concentration.
real *8, dimension(:), allocatable y_stag
Location of the boundaries (x) of the control volumes of the domain.
real *8, dimension(:,:,:), allocatable q_init
logical solid_transport_flag
Flag to choose if we model solid phase transport.
real *8 hb_e
Right height.
subroutine init_source
Source initialization.
real *8, dimension(:,:,:), allocatable q
Conservative variables.