MFIX  2016-1
time_march_pic.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! Subroutine: PIC_TIME_MARCH !
3 ! Author: R. Garg !
4 ! !
5 ! Purpose: Main PIC driver routine. !
6 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
7  SUBROUTINE pic_time_march
8 
9 ! Global variables
10 !---------------------------------------------------------------------//
11 ! Fluid time, simulation end time, time step size, number of time steps
12  use run, only: time, tstop, dt, nstep
13 ! Discrete particle time, time step size
14  use discretelement, only: s_time, dtsolid
15 ! MPPIC model step-size bounds
17 ! Local particle count
18  use discretelement, only: pip
19 ! Flag: Coupled fluid-solids simulation
20  use discretelement, only: des_continuum_coupled
21 ! Flag: Store _OLD arrays
22  use discretelement, only: do_old
23 ! Flag: Call user defined subroutines
24  use run, only: call_usr
25 ! Flag: Explicitly coupled gas-solids drag
26  use discretelement, only: des_explicitly_coupled
27 ! Number of mass outflows/inflows
28  use pic_bc, only: pic_bcmo, pic_bcmi
29 
30 ! Module procedures
31 !---------------------------------------------------------------------//
32  use desgrid, only: desgrid_pic
33  use error_manager
35  use mpi_utility, only: global_all_sum
36  use output_man, only: output_manager
37 
38  IMPLICIT NONE
39 
40 ! Local variables
41 !---------------------------------------------------------------------//
42 ! time till which the PIC loop will be run
43  double precision :: TEND_PIC_LOOP
44 ! number of PIC time steps
45  Integer :: PIC_ITERS
46 ! Global number of parcels.
47  INTEGER :: gPIP
48 !......................................................................!
49 
50 
51 ! Set solids time to fluid time.
52  s_time = time
53 
54  IF(des_continuum_coupled) THEN
55  tend_pic_loop = time+dt
56  dtsolid = min(dtpic_max, dt)
57  ELSE
58  tend_pic_loop = tstop
59  dtsolid = dt
60  ENDIF
61  pic_iters = 0
62 
63 
64  IF(call_usr) CALL usr0_des
65 
66 ! Compute the gas-phase pressure gradient
67  IF(des_continuum_coupled) THEN
68  IF(des_explicitly_coupled) CALL drag_gs_des1
69  CALL calc_pg_grad
70  ENDIF
71 
72 
73 ! If the current time in the discrete loop exceeds the current time in
74 ! the continuum simulation, exit the lagrangian loop
75  DO WHILE(s_time.LT.tend_pic_loop)
76 
77  pic_iters = pic_iters + 1
78 
79 ! Set the solids time step
80 ! DTSOLID = MERGE(MIN(DTPIC_MAX, DT), DTPIC_MAX, &
81 ! DES_CONTINUUM_COUPLED)
82 
83 ! If next time step in the discrete loop will exceed the current time
84 ! in the continuum simulation, modify the discrete time step so final
85 ! time will match
86  IF(s_time + dtsolid > tend_pic_loop) &
87  dtsolid = tend_pic_loop - s_time
88 
89 ! Calculate the solids pressure
90  CALL calc_ps_pic
91  CALL calc_ps_grad_pic
92  CALL interpolate_pic
93 
94  IF(des_continuum_coupled) CALL calc_drag_des
95 
96  IF (do_old) CALL cfupdateold
97 
98  CALL integrate_time_pic
99 
100 ! CALL WRITE_PARTICLE(6010)
101 
102 ! Apply mass outflow/inflow boundary conditions
103  IF(pic_bcmo > 0) CALL mass_outflow_pic
104  IF(pic_bcmi > 0) CALL mass_inflow_pic
105 
106 ! Impose the wall-particle boundary condition
107  CALL apply_wall_bc_pic
108 
109 ! Exchange particle crossing processor boundaries
110  CALL desgrid_pic(.true.)
111  CALL des_par_exchange
112 
113  IF(s_time + dtsolid < tend_pic_loop .OR. &
114  .NOT.des_explicitly_coupled ) THEN
115 ! Bin particles to the fluid grid
116  CALL particles_in_cell
117 ! Calculate interpolation weights
119 ! Calculate mean fields
120  CALL comp_mean_fields
121  ENDIF
122 
123 ! This was moved from particles in cell and the passed variables should
124 ! be added to particles in cell or made global.
125  CALL report_stats_pic
126 ! Update time to reflect changes
127  s_time = s_time + dtsolid
128 
130 
131 ! When coupled, all write calls are made in time_march (the continuum
132 ! portion) according to user settings for spx_time and res_time.
133 ! The following section targets data writes for DEM only cases:
134  IF(.NOT.des_continuum_coupled) THEN
135 ! Keep track of TIME for DEM simulations
136  time = s_time
137  nstep = nstep + 1
138 ! Call the output manager to write RES and SPx data.
139  CALL output_manager(.false., .false.)
140  ENDIF ! end if (.not.des_continuum_coupled)
141 
142  ENDDO
143 
144  CALL global_all_sum(pip, gpip)
145  WRITE(err_msg, 3000) trim(ival(pic_iters)), trim(ival(gpip))
146  CALL flush_err_msg(header=.false., footer=.false.)
147 
148  3000 FORMAT(/'PIC NITs: ',a,3x,'Total PIP: ', a)
149 
150  RETURN
151  END SUBROUTINE pic_time_march
152 
153 
154 
155 
156 ! !DTPIC_MAX = MIN( 1e-04, DTPIC_MAX)
157 ! IF(MOD(PIC_ITERS, 10).eq.0) then
158 ! IF(DES_CONTINUUM_COUPLED) then
159 ! WRITE(ERR_MSG, 2000) DTSOLID, DTPIC_CFL, DTPIC_TAUP, DT
160 ! ELSE
161 ! WRITE(ERR_MSG, 2001) S_TIME, DTSOLID, DTPIC_CFL, DTPIC_TAUP, DT
162 ! ENDIF
163 ! CALL FLUSH_ERR_MSG(HEADER = .FALSE., FOOTER = .FALSE.)
164 ! ENDIF
165 !
166 ! 2000 FORMAT(/5x,'DTSOLID CURRENT = ',g17.8,/5x,'DTPIC_CFL',8x,'= ', &
167 ! g17.8, /5x,'DTPIC TAUP',7x,'= ',g17.8,/5x,'DT FLOW',10x,'= ', &
168 ! g17.8)
169 !
170 ! 2001 FORMAT(/5x,'TIME',13X,'= ',g17.8,/5x,'DTSOLID CURRENT = ',g17.8,&
171 ! /5x,'DTPIC_CFL',8X,'= ', g17.8,/5x,'DTPIC TAUP',7x,'= ',g17.8,&
172 ! /5x,'DT FLOW',10X,'= ', g17.8)
173 
174 
175 
176 
177  SUBROUTINE write_particle(NP)
179  Use usr
180  use compar
181  use discretelement
182 
183  IMPLICIT NONE
184 
185  INTEGER, INTENT(IN) :: NP
186 
187  INTEGER, SAVE :: CALLS = 0
188  CHARACTER(len=128) :: FNAME
189 
190  fname=''; WRITE(fname, 2000) np, mype, calls
191  2000 FORMAT('DBG/DBG_',i9.9,'_',i4.4,'_',i5.5,'.vtp')
192 
193  OPEN(unit=555, file=trim(fname), status='UNKNOWN')
194 
195  write(*,"('Saving: ',A,' at ',F15.8)") trim(fname), s_time
196 
197 
198  WRITE(555, 3000)
199  3000 FORMAT('<?xml version="1.0"?>')
200 
201  WRITE(555, 3001)
202  3001 FORMAT('<VTKFile type="PolyData" ' &
203  'version="0.1" byte_order="LittleEndian">')
204 
205  WRITE(555,"('<PolyData>')")
206 
207  WRITE(555, 3002)
208  3002 FORMAT('<Piece NumberOfPoints="1" ', &
209  'NumberOfVerts="0" NumberOfLines="0" ', &
210  'NumberOfStrips="0" ', &
211  'NumberOfPolys="0">')
212 
213  WRITE(555,"('<Points>')")
214 
215  3003 FORMAT('<DataArray type="Float32" Name="Position" ', &
216  'NumberOfComponents="3" format="ascii">')
217  WRITE(555, 3003)
218  WRITE(555,"(3(3x,F15.8))") des_pos_new(np,:)
219  WRITE(555,"('</DataArray>')")
220 
221  WRITE(555,"('</Points>')")
222 
223  3004 FORMAT('<PointData Scalars="Diameter" Vectors="Velocity">')
224  WRITE(555, 3004)
225 
226  3005 FORMAT('<DataArray type="Float32" ', &
227  'Name="Diameter" format="ascii">')
228  WRITE(555, 3005)
229  WRITE(555,"(3x,F15.8)") des_radius(np)*2.0d0
230  WRITE(555,"('</DataArray>')")
231 
232  3006 FORMAT('<DataArray type="Float32" Name="Velocity" ',&
233  'NumberOfComponents="3" format="ascii">')
234  WRITE(555, 3006)
235  WRITE(555,"(3(3x,F15.8))") des_vel_new(np,:)
236  WRITE(555,"('</DataArray>')")
237 
238  WRITE(555,"('</PointData>')")
239  WRITE(555,"('<CellData></CellData>')")
240  WRITE(555,"('<Verts></Verts>')")
241  WRITE(555,"('<Lines></Lines>')")
242  WRITE(555,"('<Strips></Strips>')")
243  WRITE(555,"('<Polys></Polys>')")
244  WRITE(555,"('</Piece>')")
245  WRITE(555,"('</PolyData>')")
246  WRITE(555,"('</VTKFile>')")
247 
248  close(555)
249 
250  calls = calls+1
251 
252  RETURN
253  END SUBROUTINE write_particle
254 
subroutine comp_mean_fields
subroutine pic_time_march
Definition: time_march_pic.f:8
subroutine cfupdateold
Definition: cfupdateold.f:13
integer pic_bcmi
Definition: pic_bc_mod.f:18
subroutine mass_outflow_pic
double precision dtpic_cfl
Definition: mfix_pic_mod.f:70
subroutine calc_ps_pic
Definition: calc_ps_pic.f:8
subroutine usr0_des
Definition: usr0_des.f:18
subroutine calc_pg_grad
Definition: calc_pg_grad.f:15
subroutine output_manager(EXIT_SIGNAL, FINISHED)
subroutine desgrid_pic(plocate)
Definition: desgrid_mod.f:711
subroutine interpolate_pic
subroutine des_par_exchange()
double precision dt
Definition: run_mod.f:51
subroutine write_particle(NP)
subroutine report_stats_pic
subroutine calc_ps_grad_pic
subroutine apply_wall_bc_pic
subroutine calc_interp_weights
double precision tstop
Definition: run_mod.f:48
Definition: run_mod.f:13
subroutine particles_in_cell
double precision dtpic_taup
Definition: mfix_pic_mod.f:70
Definition: usr_mod.f:1
subroutine mass_inflow_pic
integer mype
Definition: compar_mod.f:24
integer nstep
Definition: run_mod.f:60
character(len=line_length), dimension(line_count) err_msg
subroutine calc_drag_des
Definition: calc_drag_des.f:11
double precision dtpic_max
Definition: mfix_pic_mod.f:65
integer pic_bcmo
Definition: pic_bc_mod.f:19
double precision time
Definition: run_mod.f:45
subroutine drag_gs_des1
Definition: drag_gs_des1.f:20
subroutine integrate_time_pic
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
logical call_usr
Definition: run_mod.f:121