Skip to content
Snippets Groups Projects
output_octree_osolve.f90 906 B
Newer Older
  • Learn to ignore specific revisions
  • subroutine output_octree_osolve (osolve,nnode,force)
    use definitions
    implicit none
    type (octreesolve) osolve
    integer nnode
    double precision :: force(nnode,3)
    
    integer i,j,is,k,iproc,nproc,ierr
    character*4 cs,cs2
    
    
    INCLUDE 'mpif.h'
    
    call mpi_comm_size (mpi_comm_world,nproc,ierr)
    call mpi_comm_rank (mpi_comm_world,iproc,ierr)
    
    if(iproc.eq.0) then
    
       open (9,file='VTK/osolve_forces.txt',status='unknown')
    
       ! write array lengths
       write (9,*) osolve%octree(3),osolve%nnode,osolve%nleaves,osolve%nlsf
    
       ! write info on octree solve nodes (x,y,z,u,v,w,lsf,temp)
       write (9,*) (osolve%x(i),osolve%y(i),osolve%z(i),force(i,1),force(i,2),force(i,3),(osolve%lsf(i,j),j=1,osolve%nlsf),i=1,osolve%nnode)
    
       ! write icon array
       write (9,*) ((osolve%icon(k,i),k=1,8),i=1,osolve%nleaves)
    
       ! write octree information
       write (9,*) (osolve%octree(i),i=1,osolve%octree(3))
    
       close (9)
    end if
    
    return
    end