Skip to content
Snippets Groups Projects
DOUAR.f90 104 KiB
Newer Older
  • Learn to ignore specific revisions
  •          !--------------------------------------------------------------------------------------
    
             if (params%first_step .and. params%first_iter .and. params%first_nliter) then
    
               call show_time (total,step,inc,1,'Write output initial step$')
               do is=1,osolve%nlsf
                 allocate(surface(is)%u(surface(is)%nsurface))
                 allocate(surface(is)%v(surface(is)%nsurface))
                 allocate(surface(is)%w(surface(is)%nsurface))
                 surface(is)%u=0.d0;surface(is)%v=0.d0;surface(is)%w=0.d0
               enddo
    
               call write_global_output (params,0,0,0.d0,osolve,ov,vo,surface,cl,bcdef,nest,'final')
    
               do is=1,osolve%nlsf
                 deallocate (surface(is)%u,surface(is)%v,surface(is)%w)
               enddo
               call mpi_barrier (mpi_comm_world,ierr)
             endif
    
    
             !--------------------------------------------------------------------------------------
             !--------------------------------------------------------------------------------------
    
             ! Calculate mechanical solution if not doing isostasy only
    
             !--------------------------------------------------------------------------------------
             !--------------------------------------------------------------------------------------
    
             if (bcdef%bctype == 'iso_only') then
               call show_time (total,step,inc,1,'Skipping wsmp solve and pressure calc$')
               ov%unode=0.d0
               ov%vnode=0.d0
               ov%wnode=0.d0
               ov%wnodeiso=0.d0
               osolve%u=ov%unode
               osolve%v=ov%vnode
               osolve%w=ov%wnode
               osolve%wiso=ov%wnodeiso
             else
               !--------------------------------------------------------------------------------------
               !--------------------------------------------------------------------------------------
               ! solve system with wsmp solver 
               !--------------------------------------------------------------------------------------
               !--------------------------------------------------------------------------------------
               call show_time (total,step,inc,1,'wsmp solve$')
    
               call solve_with_pwssmp (n,nz_loc,n_iproc,n_iproc_st,n_iproc_end,ia, &
                                      ja,ldb,nrhs,avals,b,params,osolve,ov,vo,     &
                                      threadinfo,ndof,istep,iter,iter_nl,weightel)
    
               !--------------------------------------------------------------------------------------
               !--------------------------------------------------------------------------------------
               !     calculate pressures
               !--------------------------------------------------------------------------------------
               !--------------------------------------------------------------------------------------
    
               call show_time (total,step,inc,1,'Calculate pressures$')
    
               call compute_pressure (params,osolve,ov,vo,mat,cl)
    
               !--------------------------------------------------------------------------------------
               !--------------------------------------------------------------------------------------
               !     smoothing pressures
               !--------------------------------------------------------------------------------------
               !--------------------------------------------------------------------------------------
               call show_time (total,step,inc,1,'Smoothing pressures$')
    
               call smooth_pressures (osolve,ov,params)
             endif
    
    
             !--------------------------------------------------------------------------------------
             !--------------------------------------------------------------------------------------
             !     leaf measurements
             !--------------------------------------------------------------------------------------
             !--------------------------------------------------------------------------------------
             call show_time (total,step,inc,1,'do leaf measurements$')
    
             call do_leaf_measurements (osolve,ov,params,istep,iter,iter_nl) 
     
             !--------------------------------------------------------------------------------------
             !--------------------------------------------------------------------------------------
             !     write all informations in a text file
             !--------------------------------------------------------------------------------------
             !--------------------------------------------------------------------------------------
             if (params%debug>=2) then
                call show_time (total,step,inc,1,'write global output$')
    
                call write_global_output(params,istep,iter,current_time,osolve,ov,vo,surface,cl,bcdef,nest,'debug')
    
                call mpi_barrier (mpi_comm_world,ierr)
    
    Douglas Guptill's avatar
    Douglas Guptill committed
    !            call slices (params,osolve,ov,vo,sections,istep,iter,iter_nl)
    
             end if
    
             !--------------------------------------------------------------------------------------
             !--------------------------------------------------------------------------------------
             !     convergence criterion computation
             !--------------------------------------------------------------------------------------
             !--------------------------------------------------------------------------------------
             call show_time (total,step,inc,1,'compute convergence criterion$')
    
    
             call compute_convergence_criterion(osolve,ov,vo,params,bcdef,istep,   &
                                               iter,iter_nl,velocity_converged)
    
    
             cltemp=current_level  !!++!!
    
             if (velocity_converged .and. increase_current_level) current_level=min(current_level+1,params%levelmax_oct)
    
             if (iproc.eq.0 .and. params%debug>=1) then
    
    Douglas Guptill's avatar
    Douglas Guptill committed
                write(*,'(a,L1)') shift//'increase_current_level ->',increase_current_level
    
                write(*,'(a,i2)') shift//'current_level ->',current_level
             end if
    
             if (cltemp+1 == params%levelmax_oct) increase_current_level=.false. !!++!!
    
    
             if (params%nonlinear_iterations.lt.0 .and. velocity_converged) exit
          
          end do
    
    
          if (params%debug.gt.1) call heap_hop3_f (threadinfo)
    
    
          call DoRuRe_nonlin_stats(params%doDoRuRe,istep,iter,iter_nl)
     
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
          !    end of non linear iterations
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
    
          call show_time (total,step,inc,1,'slicing the cube$')
    
    Douglas Guptill's avatar
    Douglas Guptill committed
    !      call slices(params,osolve,ov,vo,sections,istep,iter,iter_nl)
    
          !if (params%debug.gt.1) call heap (threadinfo,'osolve%eviscosity','main',size(osolve%eviscosity),'dp',-1)
          !deallocate (osolve%eviscosity)
          if (params%debug.gt.1) call heap (threadinfo,'osolve%q','main',size(osolve%q),'dp',-1)
          deallocate (osolve%q)                                                    
    
    
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
          !     estimating the divergence (to check if incompressibility has been respected)
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
          call show_time (total,step,inc,1,'Compute divergence$')
    
          call compute_divergence (params,osolve,ov,vo,istep,iter)
          
          !-------------------------------------------------------------------------!
          !-------------------------------------------------------------------------!
          ! deallocate memory used by the solver and terminates the solver's job
          !-------------------------------------------------------------------------!
          !-------------------------------------------------------------------------!
          call show_time (total,step,inc,1,'wsmp_cleanup$')
    
    
          if (params%debug.gt.1) call heap (threadinfo,'ia','main',size(ia),'int',-1)
          deallocate(ia)
          if (params%debug.gt.1) call heap (threadinfo,'ja','main',size(ja),'int',-1)
          deallocate(ja)
          if (params%debug.gt.1) call heap (threadinfo,'iproc_col','main',size(iproc_col),'bool',-1)
          deallocate(iproc_col)
          if (params%debug.gt.1) call heap (threadinfo,'avals','main',size(avals),'dp',-1)
          deallocate(avals) 
          if (params%debug.gt.1) call heap (threadinfo,'b','main',size(b),'dp',-1)
          deallocate(b)
          !if (params%debug.gt.1) call heap (threadinfo,'weightel','main',size(weightel),'dp',-1)
          !deallocate(weightel)
    
    
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
          ! check for convergence
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
    
          if (iter.eq.abs(params%griditer)) converge=.true.
    
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
          ! deallocate osolve
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
          ! note that osolve will be needed in the temperature calculations
          ! so if this is the last iteration (converge is true), we will not deallocate osolve
    
          if (.not.converge) then
    
             if (params%debug.gt.1) call heap (threadinfo,'osolve%icon','main',size(osolve%icon),'int',-1)
             deallocate (osolve%icon)                                     
             if (params%debug.gt.1) call heap (threadinfo,'osolve%x','main',size(osolve%x),'dp',-1)
             deallocate (osolve%x)    
             if (params%debug.gt.1) call heap (threadinfo,'osolve%y','main',size(osolve%y),'dp',-1)
             deallocate (osolve%y) 
             if (params%debug.gt.1) call heap (threadinfo,'osolve%z','main',size(osolve%z),'dp',-1)
             deallocate (osolve%z)
             if (params%debug.gt.1) call heap (threadinfo,'osolve%lsf','main',size(osolve%lsf),'dp',-1)
             deallocate (osolve%lsf) 
             if (params%debug.gt.1) call heap (threadinfo,'osolve%kfix','main',size(osolve%kfix),'int',-1)
             deallocate (osolve%kfix)  
             if (params%debug.gt.1) call heap (threadinfo,'osolve%iface','main',size(osolve%iface),'int',-1)
             deallocate (osolve%iface) 
             if (params%debug.gt.1) call heap (threadinfo,'osolve%strain','main',size(osolve%strain),'dp',-1)
    
             if (params%debug.gt.1) call heap (threadinfo,'osolve%pressure','main',size(osolve%pressure),'dp',-1)
             deallocate (osolve%pressure)  
             if (params%debug.gt.1) call heap (threadinfo,'osolve%spressure','main',size(osolve%spressure),'dp',-1)
             deallocate (osolve%spressure)
             if (params%debug.gt.1) call heap (threadinfo,'osolve%kfixt','main',size(osolve%kfixt),'int',-1)
             deallocate (osolve%kfixt) 
             if (params%debug.gt.1) call heap (threadinfo,'osolve%u','main',size(osolve%u),'dp',-1)
             deallocate (osolve%u) 
             if (params%debug.gt.1) call heap (threadinfo,'osolve%v','main',size(osolve%v),'dp',-1)
             deallocate (osolve%v) 
             if (params%debug.gt.1) call heap (threadinfo,'osolve%w','main',size(osolve%w),'dp',-1)
             deallocate (osolve%w)
             if (params%debug.gt.1) call heap (threadinfo,'osolve%wiso','main',size(osolve%wiso),'dp',-1)
             deallocate (osolve%wiso) 
             if (params%debug.gt.1) call heap (threadinfo,'osolve%temp','main',size(osolve%temp),'dp',-1)
             deallocate (osolve%temp) 
             if (params%debug.gt.1) call heap (threadinfo,'osolve%crit','main',size(osolve%crit),'dp',-1)
             deallocate (osolve%crit) 
             if (params%debug.gt.1) call heap (threadinfo,'osolve%e2d','main',size(osolve%e2d),'dp',-1)
             deallocate (osolve%e2d)  
             if (params%debug.gt.1) call heap (threadinfo,'osolve%e3d','main',size(osolve%e3d),'dp',-1)
             deallocate (osolve%e3d)  
             if (params%debug.gt.1) call heap (threadinfo,'osolve%lode','main',size(osolve%lode),'dp',-1)
             deallocate (osolve%lode)
             if (params%debug.gt.1) call heap (threadinfo,'osolve%eviscosity','main',size(osolve%eviscosity),'dp',-1)
             deallocate (osolve%eviscosity)
             if (params%debug.gt.1) call heap (threadinfo,'osolve%is_plastic','main',size(osolve%is_plastic),'bool',-1)
             deallocate (osolve%is_plastic)
             if (params%debug.gt.1) call heap (threadinfo,'osolve%dilatr','main',size(osolve%dilatr),'dp',-1)
             deallocate (osolve%dilatr)
             !if (params%debug.gt.1) call heap (threadinfo,'ov%wpreiso','main',size(ov%wpreiso),'dp',-1)
             !deallocate (ov%wpreiso)
    
             if (params%debug.gt.1) call heap (threadinfo,'osolve%yield_ratio','main',size(osolve%yield_ratio),'dp',-1)
             deallocate (osolve%yield_ratio)
    
             if (params%debug.gt.1) call heap (threadinfo,'osolve%frict_angle','main',size(osolve%frict_angle),'dp',-1)
             deallocate (osolve%frict_angle)
    
             if (params%debug.gt.1) call heap (threadinfo,'osolve%e2dp','main',size(osolve%e2dp),'dp',-1)
             deallocate (osolve%e2dp)
    
          end if
    
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
          ! finds courant condition time step in case this is the first iteration
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
          if (iter.eq.1) then
             umax=0.d0
             do i=1,ov%nnode
                if (vo%influid(i)) umax=max(umax,sqrt(ov%unode(i)**2+ov%vnode(i)**2+ov%wnode(i)**2))
             enddo
             dtcourant=.5d0**params%levelmax_oct/umax*params%courant
             if (usecourant) then
                params%dt=dtcourant
                if(iproc.eq.0 .and. params%debug .ge. 1) write(*,'(a,es15.6)') shift//'dt (CFL) =',params%dt 
             end if
    
          endif
    
          if (converge) iter=abs(params%griditer)
    
          call DoRuRe_dt_stats (params%doDoRuRe,istep,params%dt)
    
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
          ! reset surface geometry to original geometry
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
          call show_time(total,step,inc,1,'Reset surface geometry$')
          do is=1,params%ns
             surface(is)%r=surface0(is)%r
             surface(is)%s=surface0(is)%s
             surface(is)%x=surface0(is)%x
             surface(is)%y=surface0(is)%y
             surface(is)%z=surface0(is)%z
             surface(is)%xn=surface0(is)%xn
             surface(is)%yn=surface0(is)%yn
             surface(is)%zn=surface0(is)%zn
          enddo
    
    
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
    
          ! reset cloud geometry to original geometry
    
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
    
          call show_time(total,step,inc,1,'Reset cloud geometry$')
          do i=1,cl%np
            cl%x(i)=cl%x0mp(i)
            cl%y(i)=cl%y0mp(i)
            cl%z(i)=cl%z0mp(i)
          enddo
    
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
          ! update surface geometry and cloud by midpoint rule if not converge
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
    
          if (.not.converge) then
    
             olsf%nnode=ov%nnode
             olsf%nleaves=ov%nleaves
             olsf%noctree=ov%noctree
    
             allocate (olsf%octree(olsf%noctree),stat=threadinfo%err)             
    
             if (params%debug.gt.1) call heap (threadinfo,'olsf%octree','main',size(olsf%octree),'int',+1)
    
             allocate (olsf%x(olsf%nnode),stat=threadinfo%err)                    
    
             if (params%debug.gt.1) call heap (threadinfo,'olsf%x','main',size(olsf%x),'dp',+1)
    
             allocate (olsf%y(olsf%nnode),stat=threadinfo%err)                    
    
             if (params%debug.gt.1) call heap (threadinfo,'olsf%y','main',size(olsf%y),'dp',+1)
    
             allocate (olsf%z(olsf%nnode),stat=threadinfo%err)                    
    
             if (params%debug.gt.1) call heap (threadinfo,'olsf%z','main',size(olsf%z),'dp',+1)
    
             allocate (olsf%lsf(olsf%nnode),stat=threadinfo%err)                  
    
             if (params%debug.gt.1) call heap (threadinfo,'olsf%lsf','main',size(olsf%lsf),'dp',+1)
    
             allocate (olsf%icon(params%mpe,olsf%nleaves),stat=threadinfo%err)    
    
             if (params%debug.gt.1) call heap (threadinfo,'olsf%icon','main',size(olsf%icon),'int',+1)
    
             olsf%octree(1:olsf%noctree)=ov%octree(1:ov%noctree)
             olsf%x(1:olsf%nnode)=ov%x(1:ov%nnode)
             olsf%y(1:olsf%nnode)=ov%y(1:ov%nnode)
             olsf%z(1:olsf%nnode)=ov%z(1:ov%nnode)
             olsf%icon(:,1:olsf%nleaves)=ov%icon(:,1:ov%nleaves)
             do is=1,params%ns
    
                if (surface(is)%fixed_surf_spinup .and. params%in_spinup) then
    
                   if (iproc.eq.0 .and. params%debug.ge.1) write (*,'(a,i2,a)') shift//'Surface ',is,' will not be moved during spinup phase'
    
                elseif (surface(is)%fixed_surf .and. .not.params%in_spinup) then
    
                   if (iproc.eq.0 .and. params%debug.ge.1) write (*,'(a,i2,a)') shift//'Surface ',is,' will not be moved this step'
    
                   if (current_time+tiny(current_time).ge. surface(is)%activation_time) then
                      call move_surface (surface(is),surface0(is),1,0,ov,params%dt/2.d0,params,istep,is)
    
                      surface(is)%x=surface(1)%x
                      surface(is)%y=surface(1)%y
                      surface(is)%z=surface(1)%z
                      surface(is)%xn=surface(1)%xn
                      surface(is)%yn=surface(1)%yn
                      surface(is)%zn=surface(1)%zn
                      surface(is)%r=surface(1)%r
                      surface(is)%s=surface(1)%s
                   endif
    
                   ! erosion added by Jean on Dec 12 2007
                   if (material0.eq.0.and.params%erosion) then
                      call int_to_char(ic,2,is)
                      call show_time (total,step,inc,1,'Erode surface '//ic(1:2)//'$')
    
                      if (current_time+tiny(current_time).ge. surface(is)%activation_time) then
                         if (current_time+tiny(current_time).ge.params%er_start.and.current_time.lt.params%er_end) then    
                            call erosion (surface(is),olsf,is,params)
                         endif
    
                      else
                         if (iproc.eq.0) write(8,*) 'Surface ',is,' is attached to Surface0'
                         surface(is)%z=surface(1)%z   
                      endif
    
                   elseif (material0.eq.0.and.params%sedimentation) then
                      call int_to_char(ic,2,is)
                      call show_time (total,step,inc,1,'Apply sediment to surface '//ic(1:2)//'$')
                      if (iproc.eq.0) write(*,*) 'current time: ',current_time
                      if (iproc.eq.0) write(*,*) 'sed_start: ',params%sed_start
                      if (iproc.eq.0) write(*,*) 'sed_end: ',params%sed_end
                      if (iproc.eq.0) write(*,*) 'activation time: ',surface(is)%activation_time
                      if (current_time+tiny(current_time).ge.surface(is)%activation_time) then
                         if (iproc.eq.0) write(*,*) 'current time: ',current_time
                         if (iproc.eq.0) write(*,*) 'sed_start: ',params%sed_start
                         if (iproc.eq.0) write(*,*) 'sed_end: ',params%sed_end
                         if (current_time+tiny(current_time).ge.params%sed_start.and.current_time.lt.params%sed_end) then    
                            if (iproc.eq.0) write(*,*) 'Calling sedimentation with surface ',is
                            call sedimentation (surface(is),olsf,is,params,current_time, params%dt/2.d0)
                         endif
                      else
                         if (iproc.eq.0) write(8,*) 'Surface ',is,' is attached to Surface0'
                         surface(is)%z=surface(1)%z   
                      endif   
    
             !--------------------------------------------------------------------------------------
             !--------------------------------------------------------------------------------------
             !     compute isostasy and move surfaces again
             !--------------------------------------------------------------------------------------
             !--------------------------------------------------------------------------------------
             if (params%isostasy) then
    
                call show_time (total,step,inc,1,'Compute isostasy and adjust vertical velocity$')
    
    
                if (all_surf_fixed_spinup .and. params%in_spinup) then
    
                   if (iproc.eq.0 .and. params%debug.ge.1) write (*,'(a)') shift//'All surfaces fixed during spinup, skipping isostasy calculation'
    
                elseif (all_surf_fixed .and. .not.params%in_spinup) then
    
                   if (iproc.eq.0 .and. params%debug.ge.1) write (*,'(a)') shift//'All surfaces fixed during this step, skipping isostasy calculation'
    
                   if (surf_fixed_spinup .and. params%in_spinup) then
    
                      if (iproc.eq.0) write (*,'(a)') shift//'WARNING: Isostasy being used with some fixed position surfaces!'
    
                   elseif (surf_fixed .and. .not.params%in_spinup) then
    
                      if (iproc.eq.0) write (*,'(a)') shift//'WARNING: Isostasy being used with some fixed position surfaces!'
    
                   endif
    
                   !allocate(ov%wpreiso(ov%nnode),stat=err) ; if (err.ne.0) call stop_run ('Error alloc ov%wpreiso in main$')
    
                   call isostasy (params,weightel,ov,surface,mat,1,bcdef,istep)
    
    
                   call show_time (total,step,inc,1,'Apply isostasy to surfaces$')
                   do is=1,params%ns
    
                      if (surface(is)%fixed_surf_spinup .and. params%in_spinup) then
    
                         if (iproc.eq.0 .and. params%debug.ge.1) write (*,'(a,i2,a)') shift//'Surface ',is,' will not be moved during spinup phase'
    
                      elseif (surface(is)%fixed_surf .and. .not.params%in_spinup) then
    
                         if (iproc.eq.0 .and. params%debug.ge.1) write (*,'(a,i2,a)') shift//'Surface ',is,' will not be moved this step'
    
                      else
                         if (current_time+tiny(current_time).ge. surface(is)%activation_time) then
                            call move_surface (surface(is),surface0(is),1,1,ov,params%dt/2.d0,params,istep,is)
                         else
                            surface(is)%x=surface(1)%x
                            surface(is)%y=surface(1)%y
                            surface(is)%z=surface(1)%z
                            surface(is)%xn=surface(1)%xn
                            surface(is)%yn=surface(1)%yn
                            surface(is)%zn=surface(1)%zn
                            surface(is)%r=surface(1)%r
                            surface(is)%s=surface(1)%s
                         endif
                      endif
                   enddo
                endif
    
             if (params%in_spinup .and. params%fixed_cloud_spinup) then
               if (iproc.eq.0 .and. params%debug.ge.1) write (*,'(a)') shift//     &
                  'Cloud position fixed during spinup, skipping cloud advection'
             else
               if (params%move_cloud_at_midpoint) then
                 call show_time (total,step,inc,1,'Advect the cloud at midpoint$')
    
                 call move_cloud (params,cl,ov,params%dt/2.d0)
    
             ! SEPARATE SUBROUTINE???
             ! Loop over all cloud particles, find associated element and store mat num
    
             call show_time (total,step,inc,1,'Store prev elem mat num on cloud$')
    
             call store_ematnump_on_cloud(cl,osolve)
    
    
             ! MOVED DOWN FROM MASSIVE DEALLOCATION ABOVE IN ORDER TO RECORD ELEMENTAL
             ! MATERIAL NUMBER ON THE CLOUD
             if (params%debug.gt.1) call heap (threadinfo,'osolve%octree','main',size(osolve%octree),'int',-1)
             deallocate (osolve%octree)
             if (params%debug.gt.1) call heap (threadinfo,'osolve%matnum','main',size(osolve%matnum),'int',-1)
             deallocate (osolve%matnum)
    
    
    
    
             if (params%debug.gt.1) call heap (threadinfo,'olsf%x','main',size(olsf%x),'dp',-1)
             deallocate (olsf%x)
             if (params%debug.gt.1) call heap (threadinfo,'olsf%y','main',size(olsf%y),'dp',-1)
             deallocate (olsf%y)
             if (params%debug.gt.1) call heap (threadinfo,'olsf%z','main',size(olsf%z),'dp',-1)
             deallocate (olsf%z)
             if (params%debug.gt.1) call heap (threadinfo,'olsf%lsf','main',size(olsf%lsf),'dp',-1)
             deallocate (olsf%lsf)
             if (params%debug.gt.1) call heap (threadinfo,'olsf%icon','main',size(olsf%icon),'int',-1)
             deallocate (olsf%icon)
             if (params%debug.gt.1) call heap (threadinfo,'olsf%octree','main',size(olsf%octree),'int',-1)
             deallocate (olsf%octree)
    
    Dave Whipp's avatar
    Dave Whipp committed
          endif
    
            if (params%debug.gt.1) call heap (threadinfo,'weightel','main',size(weightel),'dp',-1)
    
    Dave Whipp's avatar
    Dave Whipp committed
            deallocate(weightel)
    
          endif
    
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
          ! deallocate void
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
          ! note that vo will be needed in the temperature calculations
          ! so if this is the last iteration (converge is true), we will not deallocate vo
    
          if (.not.converge) then
    
             if (params%debug.gt.1) call heap (threadinfo,'vo%node','main',size(vo%node),'int',-1)
             deallocate (vo%node)
             if (params%debug.gt.1) call heap (threadinfo,'vo%leaf','main',size(vo%leaf),'int',-1)
             deallocate (vo%leaf)
             if (params%debug.gt.1) call heap (threadinfo,'vo%face','main',size(vo%face),'int',-1)
             deallocate (vo%face)
             if (params%debug.gt.1) call heap (threadinfo,'vo%rtf','main',size(vo%rtf),'int',-1)
             deallocate (vo%rtf)
             if (params%debug.gt.1) call heap (threadinfo,'vo%ftr','main',size(vo%ftr),'int',-1)
             deallocate (vo%ftr)
             if (params%debug.gt.1) call heap (threadinfo,'vo%influid','main',size(vo%influid),'bool',-1)
             deallocate (vo%influid)
    
          end if
          if (converge) then
             do is=1,params%ns
    
                if (params%debug.gt.1) call heap (threadinfo,'surface0(is)%r','main',size(surface0(is)%r),'dp',-1)
                deallocate (surface0(is)%r)
                if (params%debug.gt.1) call heap (threadinfo,'surface0(is)%s','main',size(surface0(is)%s),'dp',-1)
                deallocate (surface0(is)%s)
                if (params%debug.gt.1) call heap (threadinfo,'surface0(is)%x','main',size(surface0(is)%x),'dp',-1)
                deallocate (surface0(is)%x)
                if (params%debug.gt.1) call heap (threadinfo,'surface0(is)%y','main',size(surface0(is)%y),'dp',-1)
                deallocate (surface0(is)%y)
                if (params%debug.gt.1) call heap (threadinfo,'surface0(is)%z','main',size(surface0(is)%z),'dp',-1)
                deallocate (surface0(is)%z)
                if (params%debug.gt.1) call heap (threadinfo,'surface0(is)%xn','main',size(surface0(is)%xn),'dp',-1)
                deallocate (surface0(is)%xn)
                if (params%debug.gt.1) call heap (threadinfo,'surface0(is)%yn','main',size(surface0(is)%yn),'dp',-1)
                deallocate (surface0(is)%yn)
                if (params%debug.gt.1) call heap (threadinfo,'surface0(is)%zn','main',size(surface0(is)%zn),'dp',-1)
                deallocate (surface0(is)%zn)
    
       if (params%debug.gt.1) call heap_hop2_f (threadinfo)
    
    
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
       !     end of grid iterations
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
    
       ! we update current_time and can only do it now because this is where the time step is known
       current_time=current_time+params%dt
       if (iproc.eq.0) write(8,*) 'current time =', current_time
    
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
       !     solve for temperature
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
    
       if (iproc.eq.0) then
          write(*,*)  '-----------------------------------------------------------------------'
          write(8,*)  '-----------------------------------------------------------------------'
          call show_time (total,step,inc,1,'Temperature calculations $')
          write (8,*) 'Start of temperature calculations'
          write(*,*)  '-----------------------------------------------------------------------'
          write(8,*)  '-----------------------------------------------------------------------'
       end if
    
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
       ! transfers velocity and temperature solution from ov to osolve
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
    
       do i=1,ov%nnode
          osolve%u(i)=ov%unode(i)
          osolve%v(i)=ov%vnode(i)
          osolve%w(i)=ov%wnode(i)
    
       enddo
    
       if (params%calculate_temp) then
    
          !------------------------------------------------------------------------|
          !------------------------------------------------------------------------|
          ! build matrix arrays, allocate memory for wsmp
          !------------------------------------------------------------------------|
          !------------------------------------------------------------------------|
    
          call show_time (total,step,inc,1,'wsmp setup1$')
    
          n = vo%nnode * ndoft
         
          !---[topology]----- 
          allocate (tpl(n)) 
          tpl%nheightmax=27*ndoft
          do i=1,n
             allocate (tpl(i)%icol(tpl(i)%nheightmax),stat=err) 
          enddo
    
          if (params%debug.gt.1) call heap (threadinfo,'tpl(:)%icol(:)','main',n*tpl(1)%nheightmax,'int',+1)
    
          !---[topology]----- 
    
          call wsmp_setup1 (n,n_iproc_st,n_iproc_end,n_iproc,nz_loc,ldb,ndoft,vo,osolve,tpl,params,threadinfo,istep,iter)
    
    
          allocate(iproc_col(n),stat=threadinfo%err)
          if (params%debug.gt.1) call heap (threadinfo,'iproc_col','main',size(iproc_col),'bool',+1)
          allocate(ja(nz_loc),stat=threadinfo%err)
          if (params%debug.gt.1) call heap (threadinfo,'ja','main',size(ja),'int',+1)
          allocate(ia(n_iproc+1),stat=threadinfo%err)
          if (params%debug.gt.1) call heap (threadinfo,'ia','main',size(ia),'int',+1)
          allocate(avals(nz_loc),stat=threadinfo%err)
          if (params%debug.gt.1) call heap (threadinfo,'avals','main',size(avals),'dp',+1)
          allocate(b(ldb,nrhs),stat=threadinfo%err)
          if (params%debug.gt.1) call heap (threadinfo,'b','main',size(b),'dp',+1)
          !allocate(weightel(osolve%nleaves),stat=threadinfo%err)
          !if (params%debug.gt.1) call heap (threadinfo,'weightel','main',size(weightel),'dp',+1)
    
    
          call show_time (total,step,inc,1,'wsmp setup2$')
    
          call wsmp_setup2 (n,n_iproc,n_iproc_st,n_iproc_end,nz_loc,iproc_col,     &
                            ia,ja,ndoft,vo,osolve,tpl,params,threadinfo,istep,iter)
    
          !---[topology]----- 
    
          if (params%debug.gt.1) call heap (threadinfo,'tpl(:)%icol(:)','main',n*tpl(1)%nheightmax,'int',-1)
    
          do i=1,n
             deallocate (tpl(i)%icol)
          enddo
          deallocate (tpl)
          !---[topology]----- 
    
          !----------------------------------------------------------------------------
          !----------------------------------------------------------------------------
          ! building the FEM matrix and rhs 
          !----------------------------------------------------------------------------
          !----------------------------------------------------------------------------
    
          call show_time (total,step,inc,1,'build system$')
    
    
          call build_system_wsmp (n,n_iproc,n_iproc_st,nz_loc,iproc_col,ia,ja,ldb, &
    
                                  nrhs,avals,b,params,osolve,ndoft,mat,vo,         &
                                  threadinfo,weightel)
    
    
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
          ! solve system with wsmp solver 
          !--------------------------------------------------------------------------------------
          !--------------------------------------------------------------------------------------
    
          call solve_with_pwgsmp (n,nz_loc,n_iproc,n_iproc_st,n_iproc_end,ia,ja,ldb,&
                                  nrhs,avals,b,params,osolve,ov,vo,threadinfo,ndoft,&
                                  istep,iter,iter_nl)
    
          !-------------------------------------------------------------------------!
          !-------------------------------------------------------------------------!
          ! deallocate memory used by the solver and terminates the solver's job
          !-------------------------------------------------------------------------!
          !-------------------------------------------------------------------------!
          call show_time (total,step,inc,1,'wsmp_cleanup$')
    
    
          if (params%debug.gt.1) call heap (threadinfo,'ia','main',size(ia),'int',-1)
          deallocate(ia)
          if (params%debug.gt.1) call heap (threadinfo,'ja','main',size(ja),'int',-1)
          deallocate(ja)
          if (params%debug.gt.1) call heap (threadinfo,'iproc_col','main',size(iproc_col),'bool',-1)
          deallocate(iproc_col)
          if (params%debug.gt.1) call heap (threadinfo,'avals','main',size(avals),'dp',-1)
          deallocate(avals) 
          if (params%debug.gt.1) call heap (threadinfo,'b','main',size(b),'dp',-1)
          deallocate(b)
          !if (params%debug.gt.1) call heap (threadinfo,'weightel','main',size(weightel),'dp',-1)
          !deallocate(weightel)
    
    
       else
    
          if(iproc.eq.0) then
             write(*,'(a,f15.7,a)') shift//'================================='
             write(*,'(a)')         shift//'skip temperature calculation'
             write(*,'(a,f15.7,a)') shift//'================================='
          end if
    
       end if
    
       !-------------------------------------------------------------------------!
       !-------------------------------------------------------------------------!
    
       call DoRuRe_temp_stats(params%doDoRuRe,istep,ov%nnode,ov%temp)
    
       olsf%nnode=ov%nnode
       olsf%nleaves=ov%nleaves
       olsf%noctree=ov%noctree
       
    
       allocate (olsf%octree(olsf%noctree),stat=threadinfo%err)
       if (params%debug.gt.1) call heap (threadinfo,'olsf%octree','main',size(olsf%octree),'int',+1)
       allocate (olsf%x(olsf%nnode),stat=threadinfo%err)
       if (params%debug.gt.1) call heap (threadinfo,'olsf%x','main',size(olsf%x),'dp',+1)
       allocate (olsf%y(olsf%nnode),stat=threadinfo%err)
       if (params%debug.gt.1) call heap (threadinfo,'olsf%y','main',size(olsf%y),'dp',+1)
       allocate (olsf%z(olsf%nnode),stat=threadinfo%err)
       if (params%debug.gt.1) call heap (threadinfo,'olsf%z','main',size(olsf%z),'dp',+1)
       allocate (olsf%lsf(olsf%nnode),stat=threadinfo%err)
       if (params%debug.gt.1) call heap (threadinfo,'olsf%lsf','main',size(olsf%lsf),'dp',+1)
    
       allocate (olsf%icon(params%mpe,olsf%nleaves),stat=threadinfo%err)    
    
       if (params%debug.gt.1) call heap (threadinfo,'olsf%icon','main',size(olsf%icon),'int',+1)
    
    
       olsf%octree(1:olsf%noctree)=ov%octree(1:ov%noctree)
       olsf%x(1:olsf%nnode)=ov%x(1:ov%nnode)
       olsf%y(1:olsf%nnode)=ov%y(1:ov%nnode)
       olsf%z(1:olsf%nnode)=ov%z(1:ov%nnode)
       olsf%icon(:,1:olsf%nleaves)=ov%icon(:,1:ov%nleaves)
    
       ! write time step to Log file
       if (iproc.eq.0) then
          write (8,*) 'Current time step ',params%dt
          write (8,*) 'Courant time step ',dtcourant
       end if
    
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
       !     move surfaces and apply erosion
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
       call show_time (total,step,inc,1,'Advect the surfaces$')
    
       do is=1,params%ns
    
          if (surface(is)%fixed_surf_spinup .and. params%in_spinup) then
    
             if (iproc.eq.0 .and. params%debug.ge.1) write (*,'(a,i2,a)') shift//'Surface ',is,' will not be moved during spinup phase'
    
          elseif (surface(is)%fixed_surf .and. .not.params%in_spinup) then
    
             if (iproc.eq.0 .and. params%debug.ge.1) write (*,'(a,i2,a)') shift//'Surface ',is,' will not be moved this step'
    
             write (ic(1:2),'(i2)') is
             call show_time (total,step,inc,1,'Advect surface '//ic(1:2)//'$')
             if (current_time+tiny(current_time).ge. surface(is)%activation_time) then
                call move_surface (surface(is),surface0(is),0,0,ov,params%dt,params,istep,is)
    
                surface(is)%x=surface(1)%x
                surface(is)%y=surface(1)%y
                surface(is)%z=surface(1)%z
                surface(is)%xn=surface(1)%xn
                surface(is)%yn=surface(1)%yn
                surface(is)%zn=surface(1)%zn
                surface(is)%r=surface(1)%r
                surface(is)%s=surface(1)%s
    
             ! erosion added by Jean on Dec 12 2007
    
             if (material0.eq.0.and.params%erosion) then
                call show_time (total,step,inc,1,'Erode surface '//ic(1:2)//'$')
    
                if (current_time+tiny(current_time).ge. surface(is)%activation_time) then
                   if (current_time+tiny(current_time).ge.params%er_start.and.current_time.lt.params%er_end) then    
                      call erosion (surface(is),olsf,is,params)
                   endif
    
                else
                   if (iproc.eq.0) write(8,*) 'Surface ',is,' is attached to Surface0'
                   surface(is)%z=surface(1)%z   
                endif
    
             elseif (material0.eq.0.and.params%sedimentation) then
                call show_time (total,step,inc,1,'Apply sediment to surface '//ic(1:2)//'$')
                if (current_time+tiny(current_time).ge.surface(is)%activation_time) then
                   if (iproc.eq.0) write(*,*) 'current time: ',current_time
                   if (iproc.eq.0) write(*,*) 'sed_start: ',params%sed_start
                   if (iproc.eq.0) write(*,*) 'sed_end: ',params%sed_end
                   if (current_time+tiny(current_time).ge.params%sed_start.and.current_time.lt.params%sed_end) then    
                      call sedimentation (surface(is),olsf,is,params,current_time, params%dt/2.d0)
                   endif
                else
                   if (iproc.eq.0) write(8,*) 'Surface ',is,' is attached to Surface0'
                   surface(is)%z=surface(1)%z   
                endif   
    
          if (iproc.eq.0) write (8,*) 'Min-Max z surf ',is,':',minval(surface(is)%z),maxval(surface(is)%z)
    
          allocate(surface(is)%u(surface(is)%nsurface))
          allocate(surface(is)%v(surface(is)%nsurface))
          allocate(surface(is)%w(surface(is)%nsurface))
    
       enddo
    
    
       !call interpolate_velocity_on_surface(params,surface,ov)
    
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
    
       !     compute isostasy, move surfaces again, update Moho displacement
    
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
    
          call show_time (total,step,inc,1,'Compute isostasy and adjust vertical velocity$')
    
          if (all_surf_fixed_spinup .and. params%in_spinup) then
    
             if (iproc.eq.0 .and. params%debug.ge.1) write (*,'(a)') shift//'All surfaces fixed during spinup, skipping isostasy calculation'
    
          elseif (all_surf_fixed .and. .not.params%in_spinup) then
    
             if (iproc.eq.0 .and. params%debug.ge.1) write (*,'(a)') shift//'All surfaces fixed during this step, skipping isostasy calculation'
    
             if (surf_fixed_spinup .and. params%in_spinup) then
    
                if (iproc.eq.0) write (*,'(a)') shift//'WARNING: Isostasy being used with some fixed position surfaces!'
    
             elseif (surf_fixed .and. .not.params%in_spinup) then
    
                if (iproc.eq.0) write (*,'(a)') shift//'WARNING: Isostasy being used with some fixed position surfaces!'
    
             endif
    
             !allocate(ov%wpreiso(ov%nnode),stat=err) ; if (err.ne.0) call stop_run ('Error alloc ov%wpreiso in main$')
    
             call isostasy (params,weightel,ov,surface,mat,0,bcdef,istep)
    
             if (params%isobc) bcdef%zisodisp=bcdef%zisodisp-bcdef%zisoinc
    
             do is=1,params%ns
    
                if (surface(is)%fixed_surf_spinup .and. params%in_spinup) then
    
                   if (iproc.eq.0 .and. params%debug.ge.1) write (*,'(a,i2,a)') shift//'Surface ',is,' will not be moved during spinup phase'
    
                elseif (surface(is)%fixed_surf .and. .not.params%in_spinup) then
    
                   if (iproc.eq.0 .and. params%debug.ge.1) write (*,'(a,i2,a)') shift//'Surface ',is,' will not be moved this step'
    
                else
                   if (current_time+tiny(current_time).ge. surface(is)%activation_time) then
                      call move_surface (surface(is),surface0(is),0,1,ov,params%dt,params,istep,is)
                   else
                      surface(is)%x=surface(1)%x
                      surface(is)%y=surface(1)%y
                      surface(is)%z=surface(1)%z
                      surface(is)%xn=surface(1)%xn
                      surface(is)%yn=surface(1)%yn
                      surface(is)%zn=surface(1)%zn
                      surface(is)%r=surface(1)%r
                      surface(is)%s=surface(1)%s
                   endif
                endif
             enddo
          endif
    
    Dave Whipp's avatar
    Dave Whipp committed
       ! Done with isostasy, deallocate weightel
    
       if (params%debug.gt.1) call heap (threadinfo,'weightel','main',size(weightel),'dp',-1)
       deallocate(weightel)
    
    Dave Whipp's avatar
    Dave Whipp committed
    
    
       call interpolate_velocity_on_surface(params,surface,ov)
    
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
    
    Dave Whipp's avatar
    Dave Whipp committed
       !     update strain, pressure, temperature on 3D cloud
    
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
       call show_time (total,step,inc,1,'Update cloud fields$')
       call update_cloud_fields (cl,ov,osolve,vo,params)
    
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
       !     advect cloud
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
    
    
       if (params%in_spinup .and. params%fixed_cloud_spinup) then
         if (iproc.eq.0 .and. params%debug.ge.1) write (*,'(a)') shift//'Cloud position fixed during spinup, skipping cloud advection'
       else
         call show_time (total,step,inc,1,'Advect the cloud$')
    
         call move_cloud (params,cl,ov,params%dt)
    
    
       ! Loop over all cloud particles, find associated element and store mat num
    
       call show_time (total,step,inc,1,'Store prev elem mat num on cloud$')
    
       if (params%debug.gt.1) call heap (threadinfo,'olsf%x','main',size(olsf%x),'dp',-1)
       deallocate (olsf%x) 
       if (params%debug.gt.1) call heap (threadinfo,'olsf%y','main',size(olsf%y),'dp',-1)
       deallocate (olsf%y) 
       if (params%debug.gt.1) call heap (threadinfo,'olsf%z','main',size(olsf%z),'dp',-1)
       deallocate (olsf%z)
       if (params%debug.gt.1) call heap (threadinfo,'olsf%lsf','main',size(olsf%lsf),'dp',-1)
       deallocate (olsf%lsf)
       if (params%debug.gt.1) call heap (threadinfo,'olsf%icon','main',size(olsf%icon),'int',-1)
       deallocate (olsf%icon)
       if (params%debug.gt.1) call heap (threadinfo,'olsf%octree','main',size(olsf%octree),'int',-1)
       deallocate (olsf%octree)
    
    
       osolve%u=ov%unode
       osolve%v=ov%vnode
       osolve%w=ov%wnode
    
       osolve%temp=ov%temp
    
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
       !     write global output before deallocating arrays
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
       call show_time (total,step,inc,1,'Write output$')
    
       call write_global_output (params,istep,iter-1,current_time,osolve,ov,vo,surface,cl,bcdef,nest,'final')
    
       call mpi_barrier (mpi_comm_world,ierr)
    
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
       ! deallocate osolve and vo
       !--------------------------------------------------------------------------------------
       !--------------------------------------------------------------------------------------
       do is=1,params%ns
          deallocate(surface(is)%u)
          deallocate(surface(is)%v)
          deallocate(surface(is)%w)
       end do
      
    
       if (params%debug.gt.1) call heap (threadinfo,'osolve%octree','main',size(osolve%octree),'int',-1)
       deallocate (osolve%octree)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%icon','main',size(osolve%icon),'int',-1)
       deallocate (osolve%icon)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%x','main',size(osolve%x),'dp',-1)
       deallocate (osolve%x)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%y','main',size(osolve%y),'dp',-1)
       deallocate (osolve%y)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%z','main',size(osolve%z),'dp',-1)
       deallocate (osolve%z)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%lsf','main',size(osolve%lsf),'dp',-1)
       deallocate (osolve%lsf)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%kfix','main',size(osolve%kfix),'int',-1)
       deallocate (osolve%kfix)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%iface','main',size(osolve%iface),'int',-1)
       deallocate (osolve%iface)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%pressure','main',size(osolve%pressure),'dp',-1)
       deallocate (osolve%pressure)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%spressure','main',size(osolve%spressure),'dp',-1)
       deallocate (osolve%spressure)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%strain','main',size(osolve%strain),'dp',-1)
       deallocate (osolve%strain)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%kfixt','main',size(osolve%kfixt),'int',-1)
       deallocate (osolve%kfixt)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%u','main',size(osolve%u),'dp',-1)
       deallocate (osolve%u)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%v','main',size(osolve%v),'dp',-1)
       deallocate (osolve%v)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%w','main',size(osolve%w),'dp',-1)
       deallocate (osolve%w)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%wiso','main',size(osolve%wiso),'dp',-1)
       deallocate (osolve%wiso)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%temp','main',size(osolve%temp),'dp',-1)
       deallocate (osolve%temp)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%crit','main',size(osolve%crit),'dp',-1)
       deallocate (osolve%crit)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%e2d','main',size(osolve%e2d),'dp',-1)
       deallocate (osolve%e2d)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%e3d','main',size(osolve%e3d),'dp',-1)
       deallocate (osolve%e3d)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%lode','main',size(osolve%lode),'dp',-1)
       deallocate (osolve%lode)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%eviscosity','main',size(osolve%eviscosity),'dp',-1)
       deallocate (osolve%eviscosity)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%is_plastic','main',size(osolve%is_plastic),'bool',-1)
       deallocate (osolve%is_plastic)
       if (params%debug.gt.1) call heap (threadinfo,'osolve%dilatr','main',size(osolve%dilatr),'dp',-1)
       deallocate (osolve%dilatr)
    
       if (params%debug.gt.1) call heap (threadinfo,'osolve%matnum','main',size(osolve%matnum),'int',-1)
       deallocate (osolve%matnum)
    
       if (params%debug.gt.1) call heap (threadinfo,'osolve%yield_ratio','main',size(osolve%yield_ratio),'dp',-1)
       deallocate (osolve%yield_ratio)
    
       if (params%debug.gt.1) call heap (threadinfo,'osolve%frict_angle','main',size(osolve%frict_angle),'dp',-1)
       deallocate (osolve%frict_angle)
    
       if (params%debug.gt.1) call heap (threadinfo,'vo%node','main',size(vo%node),'int',-1)
       deallocate (vo%node)
       if (params%debug.gt.1) call heap (threadinfo,'vo%leaf','main',size(vo%leaf),'int',-1)
       deallocate (vo%leaf)
       if (params%debug.gt.1) call heap (threadinfo,'vo%face','main',size(vo%face),'int',-1)
       deallocate (vo%face)
       if (params%debug.gt.1) call heap (threadinfo,'vo%rtf','main',size(vo%rtf),'int',-1)
       deallocate (vo%rtf)
       if (params%debug.gt.1) call heap (threadinfo,'vo%ftr','main',size(vo%ftr),'int',-1)
       deallocate (vo%ftr)
       if (params%debug.gt.1) call heap (threadinfo,'vo%influid','main',size(vo%influid),'bool',-1)
       deallocate (vo%influid)
       !if (params%debug.gt.1) call heap (threadinfo,'ov%wpreiso','main',size(ov%wpreiso),'dp',-1)
       !deallocate (ov%wpreiso)
    
       if (params%debug.gt.1) call heap (threadinfo,'osolve%e2dp','main',size(osolve%e2dp),'dp',-1)
       deallocate (osolve%e2dp)
    
    
       call show_time (total,step,inc,1,'End of time step$')
    
       ! end of big time loop
    
       istep=istep+1
    
    
    enddo
    !--------------------------------------------------------------------------------------
    !--------------------------------------------------------------------------------------
    !     end of time stepping
    !--------------------------------------------------------------------------------------
    !--------------------------------------------------------------------------------------
    
    if (params%debug.gt.1) call heap_hop1_f (threadinfo)
    
    
    call show_time (total,step,inc,1,'End of run$')
    
    call io_DoRuRe2 (params,'close')
       
    deallocate (cl%x)
    deallocate (cl%y)
    deallocate (cl%z)
    deallocate (cl%x0)
    deallocate (cl%y0)
    deallocate (cl%z0)
    deallocate (cl%strain)
    deallocate (cl%lsf0)
    deallocate (cl%temp)
    deallocate (cl%press)
    
    deallocate (cl%tag)
    
    deallocate (cl%matnum)
    
    if (params%debug.gt.1) call heap (threadinfo,'ov%octree','main',size(ov%octree),'int',-1)
    deallocate (ov%octree)
    if (params%debug.gt.1) call heap (threadinfo,'ov%x','main',size(ov%x),'dp',-1)
    deallocate (ov%x)
    if (params%debug.gt.1) call heap (threadinfo,'ov%y','main',size(ov%y),'dp',-1)
    deallocate (ov%y)
    if (params%debug.gt.1) call heap (threadinfo,'ov%z','main',size(ov%z),'dp',-1)
    deallocate (ov%z)
    if (params%debug.gt.1) call heap (threadinfo,'ov%unode','main',size(ov%unode),'dp',-1)
    deallocate (ov%unode)
    if (params%debug.gt.1) call heap (threadinfo,'ov%vnode','main',size(ov%vnode),'dp',-1)
    deallocate (ov%vnode)
    if (params%debug.gt.1) call heap (threadinfo,'ov%wnode','main',size(ov%wnode),'dp',-1)
    deallocate (ov%wnode)
    if (params%debug.gt.1) call heap (threadinfo,'ov%wnodeiso','main',size(ov%wnodeiso),'dp',-1)
    deallocate (ov%wnodeiso)
    if (params%debug.gt.1) call heap (threadinfo,'ov%icon','main',size(ov%icon),'int',-1)
    deallocate (ov%icon)
    if (params%debug.gt.1) call heap (threadinfo,'ov%temp','main',size(ov%temp),'dp',-1)
    deallocate (ov%temp)
    if (params%debug.gt.1) call heap (threadinfo,'ov%temporary_nodal...','main',size(ov%temporary_nodal_pressure),'dp',-1) 
    deallocate (ov%temporary_nodal_pressure)
    if (params%debug.gt.1) call heap (threadinfo,'ov%whole_leaf...','main',size(ov%whole_leaf_in_fluid),'bool',-1)         
    deallocate (ov%whole_leaf_in_fluid)