Skip to content
Snippets Groups Projects
find_mat_numbers_from_cloud.f90 3.48 KiB
Newer Older
  • Learn to ignore specific revisions
  • !------------------------------------------------------------------------------|
    !------------------------------------------------------------------------------|
    !                                                                              |
    !              ||===\\                                                         | 
    !              ||    \\                                                        |
    !              ||     ||   //==\\   ||  ||   //==||  ||/==\\                   |
    !              ||     ||  ||    ||  ||  ||  ||   ||  ||    ||                  |
    !              ||    //   ||    ||  ||  ||  ||   ||  ||                        |
    !              ||===//     \\==//    \\==\\  \\==\\  ||                        |
    !                                                                              |
    !------------------------------------------------------------------------------|
    !------------------------------------------------------------------------------|
    !                                                                              |
    !             FIND MAT NUMBERS FROM CLOUD    OCT. 2012                         |
    !                                                                              |
    !------------------------------------------------------------------------------|
    !------------------------------------------------------------------------------|
    
    subroutine find_mat_numbers_from_cloud(params,cl,osolve,cloud_elem_mat_bins)
    
    use definitions
    
    !------------------------------------------------------------------------------|
    !(((((((((((((((( Purpose of the routine  ))))))))))))))))))))))))))))))))))))))
    !------------------------------------------------------------------------------|
    ! This routine loops over all of the cloud particles and fills and array of    |
    ! size nelem x nmat with the material numbers for the cloud particles within   |
    ! each element                                                                 |
    
    !------------------------------------------------------------------------------|
    !((((((((((((((((  declaration of the subroutine arguments  ))))))))))))))))))))
    !------------------------------------------------------------------------------|
    
    implicit none
    
    
    Dave Whipp's avatar
    Dave Whipp committed
    include 'mpif.h'
    
    
    type (parameters) params
    type (octreesolve) osolve
    type (cloud) cl
    integer :: cloud_elem_mat_bins(osolve%nleaves,0:params%nmat)
    
    !------------------------------------------------------------------------------|
    !(((((((((((((((( declaration of the subroutine internal variables )))))))))))))
    !------------------------------------------------------------------------------|
    
    double precision :: x0,y0,z0,dxyz
    integer :: i,iproc,nproc,ierr,leaf,level,locc,cl_matnum
    
    !-------------------------------------------------------------------------------
    !-------------------------------------------------------------------------------
    
    call mpi_comm_size (mpi_comm_world,nproc,ierr)
    call mpi_comm_rank (mpi_comm_world,iproc,ierr)
    
    ! Initialize cloud material bins array
    cloud_elem_mat_bins=0
    
    ! Loop over all cloud particles, find associated element and store mat num
    do i = 1,cl%np
      call octree_find_leaf (osolve%octree,osolve%noctree,cl%x(i),cl%y(i),cl%z(i), &
                            leaf,level,locc,x0,y0,z0,dxyz)
      cl_matnum = cl%matnum(i)
      cloud_elem_mat_bins(leaf,cl_matnum)=cloud_elem_mat_bins(leaf,cl_matnum)+1
    enddo
    
    end subroutine find_mat_numbers_from_cloud
    
    !-------------------------------------------------------------------------------
    
    Dave Whipp's avatar
    Dave Whipp committed
    !-------------------------------------------------------------------------------