MFIX  2016-1
report_stats_pic.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: REPORT_STATS_PIC !
4 ! !
5 ! Purpose: Output stats about PIC simulation. !
6 ! !
7 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
8  SUBROUTINE report_stats_pic
9 
10 ! Global Variables:
11 !---------------------------------------------------------------------//
12 ! Flag to report minimum EP_G
13  use mfix_pic, only: pic_report_min_epg
14 ! Gas phase volume fraction
15  use fldvar, only: ep_g
16 ! Location of cell faces (East, North, Top)
17  use discretelement, only: xe, yn, zt
18 
19  use param1, only: large_number
20  use mpi_utility
21  USE error_manager
22  USE functions
23 
24  IMPLICIT NONE
25 
26 ! Local Variables:
27 !----------------------------------------------------------------------!
28 ! Loop counters
29  INTEGER I, J, K, IJK, IPROC
30 
31  INTEGER :: EPg_MIN_loc(0:numpes-1, 4), EPg_MIN_loc2(1)
32  DOUBLE PRECISION :: EPg_MIN(0:numpes-1), EPg_min2
33 
34 !-----------------------------------------------
35 
36  CALL init_err_msg("REPORT_STATS_PIC")
37 
38 
39  IF(pic_report_min_epg) THEN
40 
41  epg_min(:) = 0
42  epg_min(mype) = large_number
43 
44  epg_min_loc(:,:) = 0
45  epg_min_loc(mype,:) = -1
46 
47  DO k = kstart1, kend1
48  DO j = jstart1, jend1
49  DO i = istart1, iend1
50  ijk = funijk(i,j,k)
51 
52  IF(ep_g(ijk) < epg_min(mype)) THEN
53  epg_min_loc(mype,1) = i
54  epg_min_loc(mype,2) = j
55  epg_min_loc(mype,3) = k
56  epg_min_loc(mype,4) = ijk
57  epg_min(mype) = ep_g(ijk)
58  ENDIF
59  ENDDO
60  ENDDO
61  ENDDO
62 
63  call global_all_sum(epg_min)
64  CALL global_all_sum(epg_min_loc)
65 
66  epg_min2 = minval(epg_min(0:numpes-1))
67  epg_min_loc2 = minloc(epg_min(0:numpes-1)) - 1
68  !-1, since minloc goes from 1:size of the array.
69  !If not corrected by -1, then the proc id will be off by 1
70 
71  iproc = epg_min_loc2(1)
72 
73  i = epg_min_loc(iproc, 1)
74  j = epg_min_loc(iproc, 2)
75  k = epg_min_loc(iproc, 3)
76  ijk = epg_min_loc(iproc, 4)
77  WRITE(err_msg,1014) epg_min2, iproc, i, j, k, ijk, &
78  xe(i) - 0.5*dx(i), yn(j)-0.5*dy(j), zt(k) - 0.5*dz(k)
79 
80  1014 FORMAT( /, &
81  & 5x,'EPGMIN = ', 2x,g17.8,/ &
82  & 5x,'EPGMIN PROC RANK = ', 2x, i10, / &
83  & 5x,'EPGMIN (I, J, K, IJK) = ', 3(2x,i5),2x,i10,/ &
84  & 5x,'XMID, YMID, ZMID FOR CELL = ', 3(2x,g17.8))
85 
86  call flush_err_msg(header = .false., footer = .false.)
87 
88  ENDIF
89 
90  CALL finl_err_msg
91 
92  RETURN
93  END SUBROUTINE report_stats_pic
94 
95 
double precision, dimension(:), allocatable ep_g
Definition: fldvar_mod.f:15
subroutine finl_err_msg
subroutine report_stats_pic
subroutine init_err_msg(CALLER)
double precision, parameter large_number
Definition: param1_mod.f:23
character(len=line_length), dimension(line_count) err_msg
logical pic_report_min_epg
Definition: mfix_pic_mod.f:90
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)