Skip to content
find_group.F90_new 2.37 KiB
Newer Older
Fabio Roberto Vitello's avatar
Fabio Roberto Vitello committed
!***********************************************************************
!
!
                     SUBROUTINE find_group
!
!
!***********************************************************************
!
!
!     Subroutine to find the cells of the grouping.
!
!=======================================================================
! Find_group check for grouping cells and prepare a local array
! grouping(1:cg_loc <= nc_loc)  containing the grouping cells belonging
! to the PE (it is the PE executor). It is fill up to cg_loc elements.	
!=======================================================================

	 USE fly_h 
	implicit none
 	INCLUDE 'mpif.h'

!   Declaration of local variables.
!   -------------------------------
        

	
	
 
	INTEGER		:: ns,nliv,jliv
	INTEGER(KIND=4)	:: i
	INTEGER(KIND=4) :: tot_bod_grou,count_group
  	
!=======================================================================

	
	ns=1	! nsubdiv future
	
        cg_loc=0	! number of cell belong to group
	tot_bod_grou=0
	count_group=0   !zeroing total number of gr cells

        nliv=ncrit+1    ! starting critical level

        IF(nliv.GT.lmax) GOTO 150

        ns=cell_ss(nliv,2)-cell_ss(nliv,1)+1 !number of cells in this level

        IF(ns.eq.0) GOTO 150
	
	   i_sh = cell_ss(nliv,1)- nbodsmax


100     CONTINUE

!-------------------------------------------------------------------
! Look for Cgroup cells
!------------------------------------------------------------------- 

        DO jliv=nliv,lmax 


          DO  i=cell_ss(jliv,1),cell_ss(jliv,2)  !execute the loop only for mem. res. cells
	      
	      	ind_loc=i-nbodsmax
		  
	      
	      	IF(mark_gr_cell(ind_loc).lt.1) CYCLE  	!not a grouping cell
	      	tot_bod_grou=tot_bod_grou+mark_gr_cell(ind_loc)
		
		

		count_group=count_group+1		!it is a grouping cell
		grouping(count_group)=i	
!

	  ENDDO  !do i=cell_ss(....
!-------------------------------------------------------------------
!  analyze the next level of the tree
!-------------------------------------------------------------------        

	ENDDO  ! do jliv=nliv,lmax
150	cg_loc=count_group
		IF(me.eq.0) THEN
	        WRITE(uterm,*)' Cells of the grouping =',count_group
		WRITE(uterm,*)' Body TOTAL in cells of the grouping =', tot_bod_grou

		IF(count_group.gt.0) WRITE(uterm,*) ' Body average (integer) in a group', &
     							tot_bod_grou/count_group
		ENDIF
	
	
	
	
	RETURN
        END