MFIX  2016-1
des_time_march.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: DES_TIME_MARCH !
4 ! Author: Jay Boyalakuntla Date: 21-Jun-04 !
5 ! !
6 ! Purpose: Main DEM driver routine !
7 ! !
8 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
9  SUBROUTINE des_time_march
10 
11 ! Modules
12 !---------------------------------------------------------------------//
14  use des_bc, only: dem_bcmi, dem_bcmo
15  use des_thermo, only: calc_radt_des
16  use desgrid, only: desgrid_pic
17  use discretelement
18  use error_manager
19  use functions
20  use machine
23  use mpi_utility
24  use output_man, only: output_manager
25  use run, only: any_species_eq
26  use run, only: call_usr
27  use run, only: energy_eq
28  use run, only: nstep
29  use run, only: time, tstop, dt
30  use sendrecv
31  IMPLICIT NONE
32 
33 ! Local variables
34 !---------------------------------------------------------------------//
35 ! Total number of particles
36  INTEGER, SAVE :: NP=0
37 
38  !type(sap_t) :: sap
39 
40 ! time step loop counter index
41  INTEGER :: NN,ii,nnn
42 ! loop counter index for any initial particle settling incoupled cases
43  INTEGER :: FACTOR
44 ! Temporary variables when des_continuum_coupled is T to track
45 ! changes in solid time step
46  DOUBLE PRECISION :: DTSOLID_TMP
47 ! Numbers to calculate wall time spent in DEM calculations.
48  DOUBLE PRECISION :: TMP_WALL
49 
50 !......................................................................!
51 
52 ! In case of restarts assign S_TIME from MFIX TIME
53  s_time = time
54  dtsolid_tmp = dtsolid
55  tmp_wall = wall_time()
56 
57 ! Initialize time stepping variables for coupled gas/solids simulations.
58  IF(des_continuum_coupled) THEN
59  IF(dt.GE.dtsolid) THEN
60  factor = ceiling(real(dt/dtsolid))
61  ELSE
62  factor = 1
63  dtsolid = dt
64  ENDIF
65 
66 ! Initialize time stepping variable for pure granular simulations.
67  ELSE
68  factor = ceiling(real((tstop-time)/dtsolid))
69  dt = dtsolid
70  CALL output_manager(.false., .false.)
71  ENDIF ! end if/else (des_continuum_coupled)
72 
73  np = pip - ighost_cnt
74  CALL global_all_sum(np)
75 
76  IF(des_continuum_coupled) THEN
77  WRITE(err_msg, 1000) trim(ival(factor)), trim(ival(np))
78  CALL flush_err_msg(header=.false., footer=.false., log=.false.)
79  ELSE
80  WRITE(err_msg, 1100) time, dtsolid, trim(ival(factor))
81  CALL flush_err_msg(header=.false., footer=.false., log=.false.)
82  ENDIF
83  1000 FORMAT(/'DEM NITs: ',a,3x,'Total PIP: ', a)
84  1100 FORMAT(/'Time: ',g12.5,3x,'DT: ',g12.5,3x,'DEM NITs: ',a)
85 
86  IF(call_usr) CALL usr0_des
87 
88  IF(des_continuum_coupled) THEN
89  IF(des_explicitly_coupled) THEN
90  CALL drag_gs_des1
91  IF(energy_eq) CALL conv_gs_des1
92  IF(any_species_eq) CALL des_reaction_model
93  ELSE
94  IF(any_species_eq) CALL zero_rrate_des
95  IF(energy_eq) CALL zero_energy_source
96  ENDIF
97  CALL calc_pg_grad
98  ENDIF
99 
100  IF(any(calc_radt_des)) CALL calc_avgts
101 
102 
103 ! Main DEM time loop
104 !----------------------------------------------------------------->>>
105  DO nn = 1, factor
106 
107  IF(des_continuum_coupled) THEN
108 ! If the current time in the discrete loop exceeds the current time in
109 ! the continuum simulation, exit the discrete loop
110  IF(s_time.GE.(time+dt)) EXIT
111 ! If next time step in the discrete loop will exceed the current time
112 ! in the continuum simulation, modify the discrete time step so final
113 ! time will match
114  IF((s_time+dtsolid).GT.(time+dt)) &
115  dtsolid = time + dt - s_time
116  ENDIF
117 
118 ! Calculate inter particle forces acting (collisional, cohesion)
119  CALL calc_force_dem
120 ! Calculate or distribute fluid-particle drag force.
121  CALL calc_drag_des
122 ! Calculate heat conduction to/from wall
123  IF(energy_eq)CALL calc_dem_thermo_with_wall_stl
124 
125 ! Update the old values of particle position and velocity with the new
126 ! values computed
127  IF (do_old) CALL cfupdateold
128 ! Calculate thermochemical sources (energy and rates of formation).
129  CALL calc_thermo_des
130 ! Call user functions.
131 
132  IF(call_usr) CALL usr1_des
133 
134  ! sap = multisap%saps(0)
135  ! ! CHECK SORT
136  ! do ii=2, sap%x_endpoints_len
137  ! if (sap%x_endpoints(ii)%value < sap%x_endpoints(ii-1)%value) then
138  ! print *,"****************************************************************************************"
139  ! print *,"ii:",ii," endpoints(ii):",sap%x_endpoints(ii)%box_id,sap%x_endpoints(ii)%value
140  ! print *,"****************************************************************************************"
141  ! stop __LINE__
142  ! endif
143  ! enddo
144 
145  ! do nnn=0, size(multisap%saps)-1
146  ! !print *,"nnn = ",nnn
147  ! if (.not.check_boxes(multisap%saps(nnn))) stop __LINE__
148  ! if (.not.check_sort(multisap%saps(nnn))) stop __LINE__
149  ! enddo
150 
151 ! Update position and velocities
152  CALL cfnewvalues
153 
154  ! do nnn=0, size(multisap%saps)-1
155  ! !print *,"nnn = ",nnn
156  ! if (.not.check_boxes(multisap%saps(nnn))) stop __LINE__
157  ! if (.not.check_sort(multisap%saps(nnn))) stop __LINE__
158  ! enddo
159 
160  ! sap = multisap%saps(0)
161  ! ! CHECK SORT
162  ! do ii=2, sap%x_endpoints_len
163  ! if (sap%x_endpoints(ii)%value < sap%x_endpoints(ii-1)%value) then
164  ! print *,"****************************************************************************************"
165  ! print *,"ii:",ii," endpoints(ii):",sap%x_endpoints(ii)%box_id,sap%x_endpoints(ii)%value
166  ! print *,"****************************************************************************************"
167  ! stop __LINE__
168  ! endif
169  ! enddo
170 
171 
172 ! Update particle temperatures
174 
175 ! Set DO_NSEARCH before calling DES_PAR_EXCHANGE.
176  do_nsearch = (nn == 1 .OR. mod(nn,neighbor_search_n) == 0)
177 
178 ! Add/Remove particles to the system via flow BCs.
179  IF(dem_bcmi > 0) CALL mass_inflow_dem
180  IF(dem_bcmo > 0) CALL mass_outflow_dem(do_nsearch)
181 
182 ! Call exchange particles - this will exchange particle crossing
183 ! boundaries as well as updates ghost particles information
184  IF (do_nsearch .OR. (numpes>1) .OR. des_periodic_walls) THEN
185  CALL desgrid_pic(.true.)
186  CALL des_par_exchange
187  ENDIF
188 
189  IF(do_nsearch) CALL neighbour
190 
191 ! Explicitly coupled simulations do not need to rebin particles to
192 ! the fluid grid every time step. However, this implies that the
193 ! fluid cell information and interpolation weights become stale.
194  IF(des_continuum_coupled .AND. &
195  .NOT.des_explicitly_coupled) THEN
196 ! Bin particles to fluid grid.
197  CALL particles_in_cell
198 ! Calculate interpolation weights
200 ! Calculate mean fields (EPg).
201  CALL comp_mean_fields
202  ENDIF
203 
204 ! Update time to reflect changes
205  s_time = s_time + dtsolid
206 
207 ! The following section targets data writes for DEM only cases:
208  IF(.NOT.des_continuum_coupled) THEN
209 ! Keep track of TIME and number of steps for DEM simulations
210  time = s_time
211  nstep = nstep + 1
212 ! Call the output manager to write RES and SPx data.
213  CALL output_manager(.false., .false.)
214  ENDIF ! end if (.not.des_continuum_coupled)
215 
216  IF(call_usr) CALL usr2_des
217 
218  ENDDO ! end do NN = 1, FACTOR
219 
220 ! END DEM time loop
221 !-----------------------------------------------------------------<<<
222 
223  IF(call_usr) CALL usr3_des
224 
225 ! Reset the discrete time step to original value.
226  dtsolid = dtsolid_tmp
227 
228  IF(des_continuum_coupled) CALL desmpi_send_recv_field_vars
229 
230  tmp_wall = wall_time() - tmp_wall
231  IF(tmp_wall > 1.0d-10) THEN
232  WRITE(err_msg, 9000) trim(ival(dble(factor)/tmp_wall))
233  ELSE
234  WRITE(err_msg, 9000) '+Inf'
235  ENDIF
236  CALL flush_err_msg(header=.false., footer=.false., log=.false.)
237 
238  9000 FORMAT(' NITs/SEC = ',a)
239 
240  RETURN
241  END SUBROUTINE des_time_march
subroutine comp_mean_fields
subroutine usr2_des
Definition: usr2_des.f:19
subroutine cfupdateold
Definition: cfupdateold.f:13
subroutine usr0_des
Definition: usr0_des.f:18
subroutine calc_pg_grad
Definition: calc_pg_grad.f:15
subroutine calc_thermo_des
subroutine output_manager(EXIT_SIGNAL, FINISHED)
subroutine mass_outflow_dem(FORCE_NSEARCH)
subroutine des_time_march
double precision function wall_time()
Definition: machine_mod.f:135
subroutine cfnewvalues
Definition: cfnewvalues.f:20
logical, dimension(dim_m) calc_radt_des
subroutine usr3_des
Definition: usr3_des.f:18
subroutine desgrid_pic(plocate)
Definition: desgrid_mod.f:711
integer dem_bcmo
Definition: des_bc_mod.f:19
subroutine des_par_exchange()
double precision dt
Definition: run_mod.f:51
subroutine conv_gs_des1
subroutine usr1_des
Definition: usr1_des.f:19
subroutine calc_interp_weights
subroutine des_thermo_newvalues
subroutine calc_force_dem
subroutine, public calc_dem_thermo_with_wall_stl
double precision tstop
Definition: run_mod.f:48
integer dem_bcmi
Definition: des_bc_mod.f:18
logical any_species_eq
Definition: run_mod.f:118
Definition: run_mod.f:13
subroutine zero_rrate_des
subroutine particles_in_cell
subroutine neighbour
Definition: neighbour.f:16
integer nstep
Definition: run_mod.f:60
logical energy_eq
Definition: run_mod.f:100
subroutine zero_energy_source
character(len=line_length), dimension(line_count) err_msg
subroutine desmpi_send_recv_field_vars
subroutine calc_drag_des
Definition: calc_drag_des.f:11
subroutine mass_inflow_dem
subroutine des_reaction_model
double precision time
Definition: run_mod.f:45
subroutine drag_gs_des1
Definition: drag_gs_des1.f:20
subroutine calc_avgts
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
logical call_usr
Definition: run_mod.f:121