MFIX  2016-1
exchange.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! SUBROUTINE: EXCHANGE C
4 ! Purpose: Calls routines to drive calculations of the interphase C
5 ! momentum, and energy exchange coefficients/terms C
6 ! if directed to do so by the corresponding flags C
7 ! C
8 ! Author: M. Syamlal Date: 25-APR-96 C
9 ! C
10 ! C
11 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
12  SUBROUTINE exchange(IER)
13 
14 ! Global Variables
15 !---------------------------------------------------------------------//
16 ! Flags for calculating drag coefficient.
17  use coeff, only: dragcoef
18 ! Flags for calculating heat transfer coefficient.
19  use coeff, only: heat_tr
20 
21  use param1, only: zero
22  use physprop, only: smax, ro_g0
23  use run, only: granular_energy
24  use run, only: kt_type_enum, ia_2005
25 
26  use discretelement, only: des_explicitly_coupled
27  use discretelement, only: des_continuum_coupled
28  use discretelement, only: des_continuum_hybrid
29 
30 
31  implicit none
32 
33 ! Dummy arguments
34 !---------------------------------------------------------------------//
35  INTEGER, INTENT(INOUT) :: IER ! Error index
36 
37 ! Local variables
38 !---------------------------------------------------------------------//
39 ! loop counter
40  INTEGER :: M, L
41 !---------------------------------------------------------------------//
42 
43 ! calculate gas-solids drag based on relatively velocity differences
44  IF (.NOT.des_continuum_coupled .OR. des_continuum_hybrid) THEN
45  DO m = 1, smax
46  IF (dragcoef(0,m) .AND. ro_g0/=zero) CALL drag_gs(m, ier)
47  ENDDO
48 
49 ! calculate solilds-solids drag based on relative velocity differences
50  DO m = 1, smax
51  DO l = 1, m - 1
52  IF (dragcoef(l,m)) CALL drag_ss (l, m, ier)
53  ENDDO
54  ENDDO
55  ENDIF
56 
57 ! Calculate additional interphase interaction coefficients (between
58 ! continuum solids phases)
59  IF (granular_energy) THEN
60  SELECT CASE(kt_type_enum)
61  CASE(ia_2005)
62  DO m=1,smax
63  DO l=1,smax
64  CALL coll_momentum_coeff_ia(l, m)
65  ENDDO
66  ENDDO
67  CASE DEFAULT
68  END SELECT
69  ENDIF
70 
71 ! Calculate interphase heat transfer coefficients
72  DO m=1,smax
73  IF(heat_tr(0,m)) CALL calc_gama(m)
74  ENDDO
75 
76  return
77  END SUBROUTINE exchange
subroutine drag_ss(L, M)
Definition: drag_ss.f:12
double precision ro_g0
Definition: physprop_mod.f:59
Definition: run_mod.f:13
subroutine exchange(IER)
Definition: exchange.f:13
subroutine calc_gama(M)
Definition: calc_gama.f:9
integer smax
Definition: physprop_mod.f:22
Definition: coeff_mod.f:9
logical granular_energy
Definition: run_mod.f:112
subroutine drag_gs(M, IER)
Definition: drag_gs.f:22
logical, dimension(:,:), allocatable heat_tr
Definition: coeff_mod.f:29
subroutine coll_momentum_coeff_ia(L, M)
logical, dimension(:,:), allocatable dragcoef
Definition: coeff_mod.f:28
double precision, parameter zero
Definition: param1_mod.f:27