Skip to content
ilist_group.F90 12.1 KiB
Newer Older
Fabio Roberto Vitello's avatar
Fabio Roberto Vitello committed
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197 198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217 218 219 220 221 222 223 224 225 226 227 228 229 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252 253 254 255 256 257 258 259 260 261 262 263 264 265 266 267 268 269 270 271 272 273 274 275 276 277 278 279 280 281 282 283 284 285 286 287 288 289 290 291 292 293 294 295 296 297 298 299 300 301 302 303 304 305 306 307 308 309 310 311 312 313 314 315 316 317 318 319 320 321 322 323 324 325 326 327 328 329 330 331 332 333 334 335 336 337 338 339 340 341 342 343 344 345 346 347 348 349 350 351 352 353 354 355 356 357 358 359 360 361 362 363 364 365 366 367 368 369 370 371 372 373 374 375 376 377 378 379 380 381 382 383 384 385 386 387 388 389 390 391 392 393 394 395 396 397 398 399 400 401 402 403 404 405 406 407 408 409 410 411 412 413 414 415 416 417 418 419 420 421 422 423 424 425 426 427 428 429 430 431 432 433 434 435 436 437 438 439 440 441 442 443 444 445 446 447 448 449 450 451 452 453 454 455 456 457 458 459 460 461
!-----------------------------------------------------------------------
!
!
       SUBROUTINE ilist_group(p,nterms,nterms_gr,bcount_ele,iterms,iterms_gr, &
        pmass, pmass_gr, pquad, pquad_gr, drdotdr_gr,dx_gr,dy_gr,dz_gr)
!
!
!-----------------------------------------------------------------------
!
!
!     Subroutine to form the interaction list of a grouping cell.
!
!	P= number of cell group
!	nterms= number of elements INside Sphere
!	nterms_gr= number of elements OUTside Sphere
!	bcount_ele= number of elements INside C_group
!	iterms_gr=list of global elements outside the spere
!

!-----------------------------------------------------------------------

	 USE fly_h 
        implicit none

!   Declaration of local variables.
!   -------------------------------
	INTEGER(KIND=4) :: bcount_ele
	INTEGER(KIND=4) :: j,ind_in,ind_in3,indx,lmax1,ii
	INTEGER(KIND=4) ::p,i,nnodes,nsubdiv,nterms,nterms_gr,nl
	INTEGER(KIND=4), DIMENSION (nsubcell) :: isub  
	INTEGER(KIND=4), DIMENSION (ndim) ::dire
	INTEGER(KIND=4), DIMENSION (maxilf)::nodelist,twasubp,twisubset
	INTEGER :: il_sh
	
	LOGICAL ::tolcrit
 	REAL(KIND=8) :: dp_x,dp_y,dp_z,cc_test
 	REAL(KIND=8) :: ddx,ddy,ddz,dd2,sphere,cl2,cl_s,mass_s
	REAL(KIND=8) :: ddr,dd_min
 	REAL(KIND=8), DIMENSION (ndim) ::pos_l, pos_cl,d_c,dr2,dp
 	REAL(KIND=8), DIMENSION (ndim) ::sh
 	REAL(KIND=8), DIMENSION (ndim,ndim) ::dd_r
	REAL(KIND=8), DIMENSION (2*ndim-1) ::quad_s   

	INTEGER(KIND=4),  DIMENSION(maxnterm) :: iterms ,iterms_gr 
	REAL(KIND=8),  DIMENSION(maxnterm) :: pmass ,pmass_gr 
	REAL(KIND=8),  DIMENSION(2*ndim-1,maxnterm) :: pquad ,pquad_gr 
	REAL(KIND=8),  DIMENSION(maxnterm)::drdotdr_gr ,dx_gr ,dy_gr ,dz_gr 

	
!=======================================================================
! 	DO i=nb_loc+1,cell_ss(lmax,2)
!	write(140+me,*)"il1 PE=",me," cella=",i," pos=",pos_cell(1:3,i-nb_loc)
!	ENDDO
!	STOP

!-----------------------------------------------------------------------
!	Group-Cell element properties
!-----------------------------------------------------------------------

	il_sh = p - nb_loc
	

		
        do i=1,lmax
           if ((p .ge. cell_ss(i,1)) .and. (p .le. cell_ss(i,2))) then
              cl2=size_level(i)
              exit
           endif
        end do
        
	cl2=cl2*cl2
        sphere=(27./4.)*cl2
	bcount_ele=0


!-----------------------------------------------------------------------
!   Initialize list of cells to examine.
!-----------------------------------------------------------------------
        
	nterms=0
        nterms_gr=0
        nnodes=1
        nodelist(1)=root
        lmax1=0

! CACHE

	    pos_l(1:ndim)=pos_cell(1:ndim,il_sh)

!-----------------------------------------------------------------------
!   Loop until no cells are left to examine.
!-----------------------------------------------------------------------! 
	
 	DO WHILE (nnodes.GT.0)

        lmax1 = lmax1 + 1
        cl_s = size_level(lmax1)
	nsubdiv=0

!-----------------------------------------------------------------------
!   Apply tolerance criterion to list of cells.
!-----------------------------------------------------------------------

           DO i=1,nnodes
              nl=nodelist(i)

	      IF( nl .le. nb_loc) THEN
	      
		   
	            pos_cl(1:ndim)=pos(1:ndim,nl)
         

	             
		     ddx=pos_l(1)-pos_cl(1)
	             ddy=pos_l(2)-pos_cl(2)
	             ddz=pos_l(3)-pos_cl(3)
	             dd2=ddx**2+ddy**2+ddz**2
	            
          	  IF(dd2.GT.sphere) THEN
                     
		     nterms_gr=nterms_gr+1
		     iterms_gr(nterms_gr)=nl
		     pmass_gr(nterms_gr)=mass_read
		     dx_gr(nterms_gr)=ddx
		     dy_gr(nterms_gr)=ddy
		     dz_gr(nterms_gr)=ddz
		     drdotdr_gr(nterms_gr)=dd2		
		     	
		  ELSE	    

                     nterms=nterms+1
		     iterms(nterms)=nl
		     pmass(nterms)=mass_read
		  	
		  ENDIF
	         CYCLE 			! goto  next nodelist(i) element
		 
              
	      ELSE  !IF( nl .le. nb_loc)
	      

	     	
		il_sh=nl-nb_loc
		


		   pos_cl(1:ndim)=pos_cell(1:ndim,il_sh)

	      
	      cc_test = cl_s**2*tol2inv

	      ddx=pos_l(1)-pos_cl(1)
	      ddy=pos_l(2)-pos_cl(2)
	      ddz=pos_l(3)-pos_cl(3)
	      dd2=ddx**2+ddy**2+ddz**2
     	       

              tolcrit= dd2 .GE. cc_test

!-----------------------------------------------------------------------
! Ewald boundary periodic conditions section
!-----------------------------------------------------------------------

	      IF(tolcrit) THEN
	      

!-----------------------------------------------------------------------
!   Ewald: Search for "mirror" cells.
!
! For each simmetry plane checks whether the 
! distance body[pos(p)]--cell[pos(pc)] is such
! that the reflexion w.r.t. direction i
! will make a nearest cell to body pos(p).
!-----------------------------------------------------------------------
		
		dp(1)=0.
		dp(2)=0.
		dp(3)=0.
		
	ind_in=0
	DO ii=1, ndim
	sh(ii)=pos_l(ii)-pos_cl(ii)
	ddr=abs(sh(ii))
	if(ddr.gt.L2)then
	ind_in=ind_in+1
	dire(ind_in)=ii


	
!	ind_in3=INT(sh(ii)/ddr)
	ind_in3=1
	IF(sh(ii).lt.0) ind_in3=-1
		
	d_c(ind_in)=ind_in3*Lbox
	
	endif
	ENDDO

! If no reflection w.r.t. any plane can produce nearest cell, go to end
	
	IF(ind_in.eq.0) THEN

		   mass_s=mass_cell(il_sh)
		   quad_s(1:2*ndim-1)=quad(1:2*ndim-1,il_sh)
          	
		IF(dd2.GT.sphere) THEN
                     nterms_gr=nterms_gr+1
		     iterms_gr(nterms_gr)=nl
		     pmass_gr(nterms_gr)=mass_s
                     pquad_gr(1:2*ndim-1,nterms_gr)=quad_s(1:2*ndim-1)
		     dx_gr(nterms_gr)=ddx
		     dy_gr(nterms_gr)=ddy
		     dz_gr(nterms_gr)=ddz
		     drdotdr_gr(nterms_gr)=dd2

		     	
		
		ELSE	   
                   IF(nl.NE.p) THEN 
                     nterms=nterms+1
		     iterms(nterms)=nl
		     pmass(nterms)=mass_s
                     pquad(1:2*ndim-1,nterms)=quad_s(1:2*ndim-1)

		   
		   ENDIF	
		ENDIF
		   
	        CYCLE 			! goto  next nodelist(i) element
	ENDIF

! i=index of the mirror cell j=direction (x,y or z)
	
	do  ii=1, ind_in
	  do  j=1, ndim
	    dd_r(ii,j)=pos_cl(j)
	    if(j.eq.dire(ii))dd_r(ii,j)=dd_r(ii,j)+d_c(ii)
	  enddo
	enddo

! Search the nearest cell among the 3 reflexions
	
	if(ind_in.eq.1)then
	indx=ind_in
	go to 200
	endif
	
	DO  ii=1, ind_in
	dr2(ii)=(pos_l(1)-dd_r(ii,1))*                                         &
        (pos_l(1)-dd_r(ii,1)) +                                         &
        (pos_l(2)-dd_r(ii,2))*(pos_l(2)-dd_r(ii,2))+                    &
        (pos_l(3)-dd_r(ii,3))*(pos_l(3)-dd_r(ii,3))
	ENDDO

	indx=1
	dd_min=dr2(1)
	if(ind_in.eq.2)then
	  if(dr2(2) .le. dd_min) indx=2
	endif
	if(ind_in.eq.3)then
	  if(dr2(2).le.dd_min)indx=2
	  if(dr2(3).le.dd_min.and.dr2(3).le.dr2(2))indx=3
	endif

! Assigns to dp(i=1,ndim) the coordinate shift to reach
! from cell "pc" the nearest (to particle "p") cell outside the domain.
!

200	continue
	
	DO ii=1, ndim
	   dp(ii)=dd_r(indx,ii)-pos_cl(ii)
	ENDDO
	
		
		dp_x=pos_l(1)-(pos_cl(1)+dp(1))
		dp_y=pos_l(2)-(pos_cl(2)+dp(2))
		dp_z=pos_l(3)-(pos_cl(3)+dp(3))
		
		tolcrit=(dp_x*dp_x+dp_y*dp_y+dp_z*dp_z).GE.cc_test
	     
	     ENDIF
!-----------------------------------------------------------------------
! End of Ewald section
!-----------------------------------------------------------------------
		
		IF(tolcrit) THEN
		

		   mass_s=mass_cell(il_sh) 
		   quad_s(1:2*ndim-1)=quad(1:2*ndim-1,il_sh) 

                  IF(dd2.GT.sphere) THEN
                     nterms_gr=nterms_gr+1
                     iterms_gr(nterms_gr)=nl
                     pmass_gr(nterms_gr)=mass_s
                     pquad_gr(1:2*ndim-1,nterms_gr)=quad_s(1:2*ndim-1)
                     dx_gr(nterms_gr)=ddx
                     dy_gr(nterms_gr)=ddy
                     dz_gr(nterms_gr)=ddz
                     drdotdr_gr(nterms_gr)=dd2
                  
		  ELSE
                     IF(nl.NE.p) THEN
                     nterms=nterms+1
                     iterms(nterms)=nl
                     pmass(nterms)=mass_s
                     pquad(1:2*ndim-1,nterms)=quad_s(1:2*ndim-1)

                     
		     ENDIF
                  ENDIF
		
		ELSE !IF(tolcrit)
		   
		   IF(nl.ne.p) THEN
			nsubdiv=nsubdiv+1
			twisubset(nsubdiv)=i  !nodelist index: cell to be opened
		   ENDIF
		   
		
		ENDIF  !IF(tolcrit)
		
              
	      ENDIF  !IF( nl .le. nb_loc)
        
	END DO 			! DO i=1,nnodes
!-----------------------------------------------------------------------
!   Add cells which satisfy criterion to interaction list.  Note that,
!   depending on theta, self-interaction term will be included.
!-----------------------------------------------------------------------
           
	   IF(nterms_gr.GT.maxnterm) THEN
	      
	      write(uterm,*)'PE=',me,' nterms_gr=',nterms_gr,             &
                           ' p=',p,' nnodes=',nnodes
	      
	      call flush(uterm)
	      
	      CALL error('ilist_group error 1: overflow')
	   
	   ENDIF
           
	   IF(nterms.GT.maxnterm) THEN
	      
	      write(uterm,*)'PE=',me,' nterms=',nterms,                   &
                           ' p=',p,' nnodes=',nnodes
	      
	      call flush(uterm)
	      
	      CALL error('ilist_group error 2: overflow')
           
	   ENDIF

!-----------------------------------------------------------------------
!   Add subcells of cells which fail tolerance criterion to list of
!   cells to examine.
!-----------------------------------------------------------------------
          
	  IF(8*nsubdiv.GT.maxilf.OR.8*nsubdiv.GT.ncells) THEN
            	write(uterm,*)'Errore PE=',me,' nterms=',nterms,                   &
                           ' p=',p

		CALL error('ilist_group error 3: overflow')
	
	  ENDIF
	  
          
	  DO 40 i=1,nsubdiv
	     
	     il_sh=nodelist(twisubset(i))-nb_loc
	     isub(1:nsubcell)=subp(1:nsubcell,il_sh)
	      twasubp(i)=isub(1)
              twasubp(i+nsubdiv)=isub(2)
              twasubp(i+2*nsubdiv)=isub(3)
              twasubp(i+3*nsubdiv)=isub(4)
              twasubp(i+4*nsubdiv)=isub(5)
              twasubp(i+5*nsubdiv)=isub(6)
              twasubp(i+6*nsubdiv)=isub(7)
              twasubp(i+7*nsubdiv)=isub(8)
 40        CONTINUE

	   nnodes=0
	   DO i=1,8*nsubdiv
	      IF(twasubp(i).NE.0) THEN
	         nnodes=nnodes+1
	      	 twisubset(nnodes)=i
	      ENDIF
	    ENDDO
           
	   DO 60 i=1,nnodes
              nodelist(i)=twasubp(twisubset(i)) !list of the new cell to examin
 60        CONTINUE
        
	ENDDO  ! DO WHILE (nnodes.GT.0)  ! start new cycle with new nodelist(nnodes)

!-----------------------------------------------------------------------
!   Examin the group cell 'p' and put particles in the il_near list 
!-----------------------------------------------------------------------

	
        nsubdiv=1
        nodelist(1)=p

100     CONTINUE
        
	DO WHILE (nsubdiv.GT.0) 
          
	  DO  i = 1, nsubdiv

	     	il_sh=nodelist(i)-nb_loc
	           isub(1:nsubcell)=subp(1:nsubcell,il_sh)
              twasubp(i)=isub(1)
              twasubp(i+nsubdiv)=isub(2)
              twasubp(i+2*nsubdiv)=isub(3)
              twasubp(i+3*nsubdiv)=isub(4)
              twasubp(i+4*nsubdiv)=isub(5)
              twasubp(i+5*nsubdiv)=isub(6)
              twasubp(i+6*nsubdiv)=isub(7)
              twasubp(i+7*nsubdiv)=isub(8)
         END DO
	  nnodes=0
	  DO  i=1,8*nsubdiv
             IF(twasubp(i).GT.nb_loc) THEN
                nnodes=nnodes+1
                nodelist(nnodes)=twasubp(i)
             ELSE IF(twasubp(i).GT.0) THEN
                bcount_ele=bcount_ele+1
                nterms=nterms+1         
                iterms(nterms)=twasubp(i)
		pmass(nterms)=mass_read
  	                 
             ENDIF
          END DO
          
	  nsubdiv=nnodes
           
	   IF(nterms.GT.maxnterm) THEN
	      
	      write(uterm,*)'PE=',me,' nterms=',nterms,                   &
                           ' p=',p,' nnodes=',nnodes
	      
	      call flush(uterm)
	      
	      CALL error('ilist_group error 4: overflow')
	   ENDIF	
           
	   IF(8*nsubdiv.GT.maxilf .or. 8*nsubdiv.GT.ncells) THEN
	      
	      write(uterm,*)'PE=',me,' nsubiv=',nsubdiv,                  &
                           ' p=',p
	      
	      call flush(uterm)
	      
	      CALL error('ilist_group error 5: overflow')
	   ENDIF	

        ENDDO !dowhile
	
        RETURN
        END