MFIX  2016-1
solve_lin_eq.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! Subroutine: SOLVE_LIN_EQ C
4 ! Purpose: Interface for linear equation solver C
5 ! C
6 ! Author: M. Syamlal Date: 31-MAY-96 C
7 ! Reviewer: Date: C
8 ! C
9 ! C
10 ! Literature/Document References: C
11 ! Variables referenced: C
12 ! Variables modified: C
13 ! Local variables: C
14 ! C
15 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
16 
17  SUBROUTINE solve_lin_eq(VNAME, Vno, VAR, A_M, B_M, M, ITMAX,&
18  method, sweep, tol1, pc, ier)
19 
20 !-----------------------------------------------
21 ! Modules
22 !-----------------------------------------------
23  USE param
24  USE param1
25  USE geometry
26  USE compar
27  USE residual
28  USE toleranc
29  USE leqsol
30  IMPLICIT NONE
31 !-----------------------------------------------
32 ! Dummy arguments
33 !-----------------------------------------------
34 ! variable name
35  CHARACTER(LEN=*), INTENT(IN) :: Vname
36 ! variable number
37 ! Note: not really used beyond this subroutine. here it is
38 ! used for potentially adjusting the tolerances but it is
39 ! currently disabled code.
40 ! 1 = pressure correction equation
41 ! 2 = solids correction equation or gas/solids continuity
42 ! 3 = gas/solids u-momentum
43 ! 4 = gas/solids v-momentum
44 ! 5 = gas/solids w-momentum
45 ! 6 = temperature
46 ! 7 = species
47 ! 8 = granular temperature
48 ! 9 = scalar, E_Turb_G, k_Turb_G
49  INTEGER, INTENT(IN) :: Vno
50 ! variable
51 ! e.g., pp_g, epp, rop_g, rop_s, u_g, u_s, v_g, v_s, w_g,
52 ! w_s, T_g, T_s, x_g, x_s, Theta_m, scalar, K_Turb_G,
53 ! e_Turb_G
54  DOUBLE PRECISION, INTENT(INOUT) :: Var(dimension_3)
55 ! septadiagonal matrix A_m
56  DOUBLE PRECISION, INTENT(INOUT) :: A_m(dimension_3, -3:3, 0:dimension_m)
57 ! vector b_m
58  DOUBLE PRECISION, INTENT(INOUT) :: B_m(dimension_3, 0:dimension_m)
59 ! phase index
60  INTEGER, INTENT(IN) :: M
61 ! maximum number of iterations (generally leq_it)
62  INTEGER, INTENT(IN) :: ITMAX
63 ! linear equation solver method (generally leq_method)
64 ! 1 = sor
65 ! 2 = bicgstab (default)
66 ! 3 = gmres
67 ! 5 = cg
68  INTEGER, INTENT(IN) :: METHOD
69 ! sweep direction of leq solver (leq_sweep)
70 ! e.g., options = 'isis', 'rsrs' (default), 'asas'
71  CHARACTER(LEN=4), INTENT(IN) :: SWEEP
72 ! convergence tolerance for leq solver (leq_tol)
73  DOUBLE PRECISION, INTENT(IN) :: TOL1
74 ! preconditioner (leq_pc)
75 ! options = 'line' (default), 'diag', 'none'
76  CHARACTER(LEN=4), INTENT(IN) :: PC
77 ! error index
78  INTEGER, INTENT(INOUT) :: IER
79 !-----------------------------------------------
80 ! Local parameters
81 !-----------------------------------------------
82 ! Adjust LEQ tolerance flag
83  LOGICAL, PARAMETER :: adjust_leq_tol = .false.
84  LOGICAL, PARAMETER :: leq_tol_scheme1 = .false.
85 ! currently only used for gmres routine
86  INTEGER, PARAMETER :: MAX_IT = 1
87 !-----------------------------------------------
88 ! Local variables
89 !-----------------------------------------------
90 !
91  DOUBLE PRECISION :: max_resid_local, tol_resid_max
92 ! convergence tolerance for leq solver
93  DOUBLE PRECISION :: TOL
94 ! transpose of septadiaganol matrix A_M
95  DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:) :: A_MT
96 ! indices
97  INTEGER :: II, IJK
98 ! for constructing local character strings
99  CHARACTER(LEN=80) :: LINE0, LINE1
100 !-----------------------------------------------
101 
102 
103 ! Adjusting the tolerances
104 ! ---------------------------------------------------------------->>>
105  IF(adjust_leq_tol) THEN
106  max_resid_local = maxval(resid(:,m),1)
107  tol_resid_max = max(tol_resid, tol_resid_t, tol_resid_th, tol_resid_x)
108  IF(leq_tol_scheme1.AND.resid(vno,m).LT.1.0d-1) THEN
109  if(vno.le.5) then
110  tol = max(tol1,tol1*resid(vno,m)/tol_resid)
111  elseif (vno.eq.6) then
112  tol = max(tol1,tol1*resid(vno,m)/tol_resid_t)
113  elseif (vno.eq.7) then
114  tol = max(tol1,tol1*resid(vno,m)/tol_resid_x)
115  elseif (vno.eq.8) then
116  tol = max(tol1,tol1*resid(vno,m)/tol_resid_th)
117  endif
118  Write(*,*) 'Adjusting LEQ_Tolerance', vname, tol, resid(vno,m)
119  ELSEIF(max_resid_local.LT.1.0d-1) THEN
120  tol = max(tol1,tol1*max_resid_local/tol_resid_max)
121  Write(*,*) 'Adjusting LEQ_Tolerance', vname, tol, max_resid_local
122  ENDIF
123  ELSE
124  tol = tol1
125  ENDIF
126 ! ----------------------------------------------------------------<<<
127 
128 
129 ! Solve the linear system of equations
130 ! ---------------------------------------------------------------->>>
131  SELECT CASE (method)
132  CASE (1)
133 ! SOR: Successive Sver Relaxation method from Templates
134  CALL leq_sor (vname, vno, var, a_m(:,:,m), b_m(:,m), &
135  itmax, ier)
136 
137  CASE (2)
138 ! BICGSTAB: BIConjugate Gradients STabilized method
139  IF(do_transpose) THEN ! mfix.dat keyword default=false
140  allocate( a_mt(-3:3, ijkstart3:ijkend3 ))
141 !!$omp parallel do private(ijk,ii)
142  DO ijk=ijkstart3,ijkend3
143  do ii=-3,3
144  a_mt(ii,ijk) = a_m(ijk,ii,m)
145  enddo
146  ENDDO
147  call leq_bicgst(vname, vno, var, a_mt(:,:), b_m(:,m), &
148  sweep, tol, pc, itmax, ier)
149  deallocate( a_mt )
150  ELSE
151  call leq_bicgs(vname, vno, var, a_m(:,:,m), b_m(:,m),&
152  sweep, tol, pc, itmax, ier)
153  ENDIF
154 
155 
156  CASE (3)
157 ! GMRES: A Generalized Minimal RESidual Algorithm
158  call leq_gmres(vname, vno, var, a_m(:,:,m), b_m(:,m),&
159  sweep, tol, itmax, max_it, ier)
160 
161  CASE (4)
162 ! Mix:
163  ier = 0
164  call leq_bicgs(vname,vno, var, a_m(:,:,m), b_m(:,m), sweep,&
165  tol, pc, itmax, ier)
166  IF (ier .eq. -2) THEN
167  ier = 0
168  print*,'calling leq_gmres', vname
169  call leq_gmres(vname, vno, var, a_m(:,:,m), b_m(:,m),&
170  sweep, tol, itmax, max_it, ier)
171  ENDIF
172 
173 
174  CASE (5)
175 ! CG: Conjugate Gradients
176  call leq_cg(vname, vno, var, a_m(:,:,m), b_m(:,m), sweep,&
177  tol, pc, itmax, ier)
178 
179 ! CASE (6) - Disabled
180 ! LSOR: Line Successive Over Relaxation method
181 ! CALL LEQ_LSOR(VNAME, VAR, A_M(:,:,M), B_M(:,M), ITMAX, IER)
182 
183 
184  CASE DEFAULT
185  line0(1:14) = 'SOLVE_LIN_EQ: '
186  line0(15:80)= vname
187  WRITE(line1,'(A, I2, A)') &
188  'Error: LEQ_METHOD = ', method, ' is invalid'
189  CALL write_error(line0, line1, 1)
190  CALL mfix_exit(mype)
191  END SELECT
192 ! ----------------------------------------------------------------<<<
193 
194  RETURN
195  END SUBROUTINE solve_lin_eq
integer ijkend3
Definition: compar_mod.f:80
integer dimension_3
Definition: param_mod.f:11
subroutine write_error(NAME, LINE, LMAX)
Definition: write_error.f:21
double precision tol_resid_t
Definition: toleranc_mod.f:57
logical do_transpose
Definition: leqsol_mod.f:32
subroutine leq_gmres(VNAME, VNO, VAR, A_M, B_M, cmethod, TOL, ITMAX, MAX_IT, IER)
Definition: leq_gmres.f:19
double precision tol_resid_th
Definition: toleranc_mod.f:69
Definition: param_mod.f:2
subroutine leq_bicgst(VNAME, VNO, VAR, A_M, B_m, cmethod, TOL, PC
Definition: leq_bicgst.f:21
integer mype
Definition: compar_mod.f:24
double precision tol_resid
Definition: toleranc_mod.f:54
integer ijkstart3
Definition: compar_mod.f:80
double precision tol_resid_x
Definition: toleranc_mod.f:60
subroutine leq_cg(VNAME, VNO, VAR, A_M, B_m, cmethod, TOL, PC, ITMAX, IER)
Definition: leq_cg.f:19
double precision, dimension(:,:), allocatable resid
Definition: residual_mod.f:37
subroutine leq_sor(VNAME, VNO, VAR, A_M, B_M, ITMAX, IER)
Definition: leq_sor.f:18
integer dimension_m
Definition: param_mod.f:18
subroutine leq_bicgs(VNAME, VNO, VAR, A_M, B_m, cmethod, TOL, PC, ITMAX, IER)
Definition: leq_bicgs.f:25
subroutine solve_lin_eq(VNAME, Vno, VAR, A_M, B_M, M, ITMAX, METHOD, SWEEP, TOL1, PC, IER)
Definition: solve_lin_eq.f:19