Skip to content
Snippets Groups Projects
define_ov.f90 9.24 KiB
Newer Older
!------------------------------------------------------------------------------|
!------------------------------------------------------------------------------|
!                                                                              |
!              ||===\\                                                         | 
!              ||    \\                                                        |
!              ||     ||   //==\\   ||  ||   //==||  ||/==\\                   |
!              ||     ||  ||    ||  ||  ||  ||   ||  ||    ||                  |
!              ||    //   ||    ||  ||  ||  ||   ||  ||                        |
!              ||===//     \\==//    \\==\\  \\==\\  ||                        |
!                                                                              |
!------------------------------------------------------------------------------|
!------------------------------------------------------------------------------|
!                                                                              |
!              DEFINE_OV    Nov. 2006                                          |
!                                                                              |
!------------------------------------------------------------------------------|
!------------------------------------------------------------------------------|

subroutine define_ov (ov,params,threadinfo)

!------------------------------------------------------------------------------|
!(((((((((((((((( Purpose of the routine  ))))))))))))))))))))))))))))))))))))))
!------------------------------------------------------------------------------|
! creates a uniform octree that will be used to store the velocity
! for the next time step or reads it from a restart file
! ov is the object holding the octree
! noctreemax is the maximum allowed octree size
! leveluniform_oct is the minimum/uniform octree level
! irestart is a flag to decide if this is a restart job or not
! restartfile is the name of the restart file if it is needed
 

!------------------------------------------------------------------------------|
!((((((((((((((((  declaration of the subroutine arguments  ))))))))))))))))))))
!------------------------------------------------------------------------------|

use threads
use definitions

implicit none

type (octreev) ov
type (parameters) params
type (thread) threadinfo

!------------------------------------------------------------------------------|
!(((((((((((((((( declaration of the subroutine internal variables )))))))))))))
!------------------------------------------------------------------------------|

integer iproc, nproc, err, ierr, levelv
integer nface, nlsf, i, j, k, np, kfix
Dave Whipp's avatar
Dave Whipp committed
double precision s,e2d,xlsf,crit,wpreiso,evisc
integer ioctree_number_of_elements
external ioctree_number_of_elements
double precision current_time,activation_time
Dave Whipp's avatar
Dave Whipp committed
logical is_plas

!------------------------------------------------------------------------------|
!------------------------------------------------------------------------------|

INCLUDE 'mpif.h'

call mpi_comm_size (mpi_comm_world,nproc,ierr)
call mpi_comm_rank (mpi_comm_world,iproc,ierr)


ov%noctree=params%noctreemax
allocate (ov%octree(ov%noctree),stat=threadinfo%err) ;  call heap (threadinfo,'ov%octree','main',size(ov%octree),'int',+1)


if (params%irestart.eq.0) then
   ! creates the octree
   call octree_init (ov%octree,ov%noctree)
   levelv=params%leveluniform_oct
   call octree_create_uniform (ov%octree,ov%noctree,levelv)
   ov%nleaves=ioctree_number_of_elements (ov%octree,ov%noctree)
   ov%nnode=ov%nleaves*3

Douglas Guptill's avatar
Douglas Guptill committed
   allocate (ov%x(ov%nnode),stat=threadinfo%err)
   call heap (threadinfo,'ov%x','define_ov',size(ov%x),'dp',+1)
   allocate (ov%y(ov%nnode),stat=threadinfo%err)        ;  call heap (threadinfo,'ov%y','define_ov',size(ov%y),'dp',+1)
   allocate (ov%z(ov%nnode),stat=threadinfo%err)        ;  call heap (threadinfo,'ov%z','define_ov',size(ov%z),'dp',+1)
   allocate (ov%icon(8,ov%nleaves),stat=threadinfo%err) ;  call heap (threadinfo,'ov%icon','define_ov',size(ov%icon),'int',+1)
Douglas Guptill's avatar
Douglas Guptill committed
   allocate (ov%whole_leaf_in_fluid(ov%nleaves),stat=threadinfo%err)
   call heap (threadinfo,'ov%whole_leaf_in_fluid','define_ov',size(ov%whole_leaf_in_fluid),'bool',+1)
   ov%whole_leaf_in_fluid=.false.
   
   ! builds the nodal connectivity
   call octree_find_node_connectivity (ov%octree,ov%noctree,ov%icon, &
                                       ov%nleaves,ov%x,ov%y,ov%z,ov%nnode)
   ! ov%nnode has been changed by octree_find_node_connectivity, so  re-size x, y, z
Douglas Guptill's avatar
Douglas Guptill committed
   call octreev_shrink_xyz(ov, threadinfo)

   ! now that ov%nnode is known we can allocate the others
   allocate (ov%unode(ov%nnode),stat=threadinfo%err)    ;  call heap (threadinfo,'ov%unode','define_ov',size(ov%unode),'dp',+1)
   allocate (ov%vnode(ov%nnode),stat=threadinfo%err)    ;  call heap (threadinfo,'ov%vnode','define_ov',size(ov%vnode),'dp',+1)
   allocate (ov%wnode(ov%nnode),stat=threadinfo%err)    ;  call heap (threadinfo,'ov%wnode','define_ov',size(ov%wnode),'dp',+1)
   allocate (ov%wnodepreiso(ov%nnode),stat=threadinfo%err)    ;  call heap (threadinfo,'ov%wnodepreiso','define_ov',size(ov%wnodepreiso),'dp',+1)
   allocate (ov%temp(ov%nnode),stat=threadinfo%err)     ;  call heap (threadinfo,'ov%temp','define_ov',size(ov%temp),'dp',+1)
   ! Line below added by dwhipp - 12/09
Dave Whipp's avatar
Dave Whipp committed
   allocate (ov%pressure(ov%nleaves),stat=threadinfo%err) ; call heap (threadinfo,'ov%pressure','define_ov',size(ov%pressure),'dp',+1)
   ! Line below added by dwhipp - 12/09 
Dave Whipp's avatar
Dave Whipp committed
   allocate (ov%spressure(ov%nleaves),stat=threadinfo%err) ; call heap (threadinfo,'ov%spressure','define_ov',size(ov%spressure),'dp',+1)
   allocate (ov%temporary_nodal_pressure(ov%nnode),stat=threadinfo%err)
   call heap (threadinfo,'ov%temporary_nodal_pressure','define_ov',size(ov%temporary_nodal_pressure),'dp',+1)

   ! initializes temp and velo
   ov%unode=0.d0
   ov%vnode=0.d0
   ov%wnode=0.d0
   ! Line below uncommented by dwhipp - 12/09 
   ov%pressure=0.d0 
   ! Line below added by dwhipp - 12/09 
   ov%spressure=0.d0
   ov%temporary_nodal_pressure=0.d0
   call initialize_temperature (ov,params%ztemp)
   if (iproc.eq.0) write(8,*) ov%nnode,' nodes in initial velocity octree'

else
   ! reads the octree from a file
   open (9,file=trim(params%restartfile),status='old',form='unformatted')
   read (9) ov%octree(3), &
              ov%nnode,     &
              ov%nleaves,   &
              nface,        &
              nlsf,         &
              np,           &
              current_time
   allocate (ov%x(ov%nnode),stat=err) ; if (err.ne.0) call stop_run ('Error alloc ov%x in define_ov$')
   allocate (ov%y(ov%nnode),stat=err) ; if (err.ne.0) call stop_run ('Error alloc ov%y in define_ov$')
   allocate (ov%z(ov%nnode),stat=err) ; if (err.ne.0) call stop_run ('Error alloc ov%z in define_ov$')
   allocate (ov%icon(8,ov%nleaves),stat=err) ; if (err.ne.0) call stop_run ('Error alloc ov%icon in define_ov$')
   allocate (ov%unode(ov%nnode),stat=err) ; if (err.ne.0) call stop_run ('Error alloc ov%unode in define_ov$')
   allocate (ov%vnode(ov%nnode),stat=err) ; if (err.ne.0) call stop_run ('Error alloc ov%vnode in define_ov$')
   allocate (ov%wnode(ov%nnode),stat=err) ; if (err.ne.0) call stop_run ('Error alloc ov%wnode in define_ov$')
   allocate (ov%wnodepreiso(ov%nnode),stat=err) ; if (err.ne.0) call stop_run ('Error alloc ov%wnodepreiso in define_ov$')
   allocate (ov%temp(ov%nnode),stat=err) ; if (err.ne.0) call stop_run ('Error alloc ov%temp in define_ov$')
   ! Line below uncommented by dwhipp - 12/09 
   allocate (ov%pressure(ov%nleaves),stat=err) ; if (err.ne.0) call stop_run ('Error alloc ov%pressure in define_ov$') 
   ! Line below added by dwhipp - 12/09 
   allocate (ov%spressure(ov%nleaves),stat=err) ; if (err.ne.0) call stop_run ('Error alloc ov%spressure in define_ov$')
Douglas Guptill's avatar
Douglas Guptill committed
   allocate (ov%temporary_nodal_pressure(ov%nnode),stat=err)
   if (err.ne.0) call stop_run ('Error alloc ov%temp_nodal_pressure in define_ov$')
   allocate (ov%whole_leaf_in_fluid(ov%nleaves),stat=err)
   if (err.ne.0) call stop_run ('Error alloc ov%whole_leaf_in_fluid in define_ov$') !=====[21082007]=====
   read (9) (ov%x(i),         &
               ov%y(i),         &
               ov%z(i),         &
               ov%unode(i),     &
               ov%vnode(i),     &
               ov%wnode(i),     &
               (xlsf,j=1,nlsf), &
               ov%temp(i),      &
               ov%temporary_nodal_pressure(i), &
               s,               &
               kfix,            &
               kfix,            &
               kfix,            &
               kfix,            &
               i=1,ov%nnode)
   read (9) ((ov%icon(k,i),k=1,8),    &
   ! Line below uncommented by dwhipp - 12/09
              ov%pressure(i),           & 
   ! Line below added by dwhipp - 12/09 
              ov%spressure(i),    &
              crit,                     &
              e2d,                      &
              evisc,                    & 
              is_plas,                  &
              ov%whole_leaf_in_fluid(i),&
              i=1,ov%nleaves)
   read (9) (ov%octree(i),i=1,ov%octree(3))
   close (9)
endif

return
end

!------------------------------------------------------------------------------|
!------------------------------------------------------------------------------|