Newer
Older
Dave Whipp
committed
allocate (osolve%yield_ratio(osolve%nleaves),stat=threadinfo%err)
if (params%debug.gt.1) call heap (threadinfo,'osolve%yield_ratio','main',size(osolve%yield_ratio),'dp',+1)
allocate (osolve%frict_angle(osolve%nleaves),stat=threadinfo%err)
if (params%debug.gt.1) call heap (threadinfo,'osolve%frict_angle','main',size(osolve%frict_angle),'dp',+1)
1007
1008
1009
1010
1011
1012
1013
1014
1015
1016
1017
1018
1019
1020
1021
1022
1023
1024
1025
1026
1027
1028
1029
1030
1031
1032
1033
1034
1035
1036
1037
1038
1039
!---------------------------------------------------------------------------|
!---------------------------------------------------------------------------|
! Reconstruct elemental densities from density strings
!---------------------------------------------------------------------------|
!---------------------------------------------------------------------------|
!After regenerating the element grid, we reconstruct the elemental densities
!from density_str 'density' entries (this is current density, incorporating
!refinement from any previous grid iterations).
!Note: this might be better done in the non-linear iterations. Either way
!we'll need to make sure this assignment does not conflict with make_cut,
!and that compacted density is not overwritten.
!Apply only if params%compaction
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
! beginning of non linear iterations
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
do iter_nl=1,abs(params%nonlinear_iterations)
if (iter_nl==1 .and. params%first_iter .and. params%first_step) params%first_nliter=.true.
if (iproc.eq.0) then
write(*,*) '-----------------------------------'
write(8,*) '-----------------------------------'
call show_time(total,step,inc,-iter_nl,' start of non-linear iteration $')
write(8,*) 'Doing inner iteration ',iter_nl
write(*,*) '-----------------------------------'
write(8,*) '-----------------------------------'
end if
if (params%debug.gt.1) call heap_hop3(threadinfo,iter_nl)
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
! transfering previous solution from ov to osolve
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
if (iter_nl.gt.1) then
do i=1,ov%nnode
osolve%u(i)=ov%unode(i)
osolve%v(i)=ov%vnode(i)
osolve%w(i)=ov%wnode(i)
osolve%wiso(i)=ov%wnodeiso(i)
if (params%compaction) osolve%wcompact(i)=ov%wnodecompact(i)
enddo
end if
! call define_bc (params,osolve,vo)
!if (iproc.eq.0) then
!write(*,*) minval(osolve%u),maxval(osolve%u)
!write(*,*) minval(osolve%v),maxval(osolve%v)
!write(*,*) minval(osolve%w),maxval(osolve%w)
!end if
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
! building the FEM matrix and rhs
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
call show_time (total,step,inc,1,'build system$')
if (.not. params%first_nliter) params%init_e2d=.false.
call build_system_wsmp (n,n_iproc,n_iproc_st,nz_loc,iproc_col,ia,ja, &
ldb,nrhs,avals,b,params,osolve,ndof,mat,vo,cl, &
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
! if this is the first iteration of the first time step, write output file
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
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
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
1119
1120
1121
1122
1123
1124
1125
1126
1127
1128
1129
1130
1131
1132
1133
1134
1135
1136
1137
1138
1139
1140
1141
1142
1143
1144
1145
1146
1147
1148
1149
1150
1151
1152
1153
1154
1155
1156
1157
1158
1159
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)
! 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
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. !!++!!
params%first_nliter=.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$')
! 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)
Dave Whipp
committed
deallocate (osolve%strain)
1289
1290
1291
1292
1293
1294
1295
1296
1297
1298
1299
1300
1301
1302
1303
1304
1305
1306
1307
1308
1309
1310
1311
1312
1313
1314
1315
1316
1317
1318
1319
1320
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)
Dave Whipp
committed
if (params%debug.gt.1) call heap (threadinfo,'osolve%e2dp','main',size(osolve%e2dp),'dp',-1)
deallocate (osolve%e2dp)
Dave Whipp
committed
if (params%compaction) then
if (params%debug.gt.1) call heap (threadinfo,'osolve%wcompact','main',size(osolve%wcompact),'dp',-1)
deallocate (osolve%wcompact)
endif
1346
1347
1348
1349
1350
1351
1352
1353
1354
1355
1356
1357
1358
1359
1360
1361
1362
1363
1364
1365
1366
1367
1368
1369
1370
1371
1372
1373
1374
1375
1376
1377
1378
1379
1380
1381
1382
1383
1384
1385
1386
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
Dave Whipp
committed
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
Dave Whipp
committed
! reset cloud geometry to original geometry
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
Dave Whipp
committed
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
Dave Whipp
committed
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
! 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
1484
1485
1486
1487
1488
1489
1490
1491
1492
1493
1494
1495
1496
1497
1498
1499
1500
1501
1502
1503
1504
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
! Compute Compaction, move surfaces, add to cloud advection velocities
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
!Here we call the compaction subroutine, which updates density_str 'density' entries
!(current density), calculates compaction velocities based on the difference between
!current and past densities (density and densityp), where densityp is the density
!profiles from the start of the time step.
!Compaction velocities are used to move the surfaces.
!Compaction velocities are added to nodal velocity solution used to advect the cloud.
!Apply only if params%compaction
1505
1506
1507
1508
1509
1510
1511
1512
1513
1514
1515
1516
1517
1518
1519
1520
1521
1522
1523
1524
1525
1526
1527
1528
1529
1530
1531
1532
1533
1534
1535
1536
1537
1538
1539
1540
1541
1542
1543
1544
1545
1546
1547
if (params%compaction) then
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 compaction 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 compaction calculation'
else
if (surf_fixed_spinup .and. params%in_spinup) then
if (iproc.eq.0) write (*,'(a)') shift//'WARNING: Compaction being used with some fixed position surfaces!'
elseif (surf_fixed .and. .not.params%in_spinup) then
if (iproc.eq.0) write (*,'(a)') shift//'WARNING: Compaction being used with some fixed position surfaces!'
endif
call compaction(params,density_str,osolve,ov,mat,params%dt/2.d0)
call show_time (total,step,inc,1,'Apply compaction 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
endif
!See isostasy for check whether surfaces are active and not fixed,
!call move_surface with adjusted ov.
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
! 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
Dave Whipp
committed
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'
Dave Whipp
committed
elseif (params%fixed_cloud) then
if (iproc.eq.0 .and. params%debug.ge.1) write (*,'(a)') shift// &
'Cloud position fixed, skipping midpoint cloud advection'
Dave Whipp
committed
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)
Dave Whipp
committed
endif
endif
Dave Whipp
committed
! 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$')
Dave Whipp
committed
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,'osolve%matnump','main',size(osolve%matnump),'int',-1)
deallocate (osolve%matnump)
if (params%compaction) then
if (params%debug.gt.1) call heap (threadinfo,'osolve%compaction_density','main',size(osolve%compaction_density),'dp',-1)
deallocate (osolve%compaction_density)
endif
Dave Whipp
committed
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)
if (params%debug.gt.1) call heap (threadinfo,'weightel','main',size(weightel),'dp',-1)
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)
Dave Whipp
committed
if (converge) then
! DEALLOCATE CLOUD0 STUFF
endif
params%first_iter = .false.
Dave Whipp
committed
enddo
if (params%debug.gt.1) call heap_hop2_f (threadinfo)
1719
1720
1721
1722
1723
1724
1725
1726
1727
1728
1729
1730
1731
1732
1733
1734
1735
1736
1737
1738
1739
1740
1741
1742
1743
1744
1745
1746
1747
1748
1749
1750
1751
1752
1753
1754
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
! 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)
Dave Whipp
committed
!osolve%wpreiso(i)=ov%wnodepreiso(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]-----
Dave Whipp
committed
!-------------------------------------------------------------------------
!-------------------------------------------------------------------------
Dave Whipp
committed
!-------------------------------------------------------------------------
!-------------------------------------------------------------------------
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, &
Dave Whipp
committed
nrhs,avals,b,params,osolve,ndoft,mat,vo,cl, &
threadinfo,weightel)
Dave Whipp
committed
!-------------------------------------------------------------------------
!-------------------------------------------------------------------------
Dave Whipp
committed
!-------------------------------------------------------------------------
!-------------------------------------------------------------------------
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)
1880
1881
1882
1883
1884
1885
1886
1887
1888
1889
1890
1891
1892
1893
1894
1895
1896
1897
1898
1899
1900
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
Dave Whipp
committed
!call interpolate_velocity_on_surface(params,surface,ov)
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
! Compute Compaction, move surfaces, add to cloud advection velocities
!--------------------------------------------------------------------------------------
!--------------------------------------------------------------------------------------
1976
1977
1978
1979
1980
1981
1982
1983
1984
1985
1986
1987
1988
1989
1990
1991
1992
1993
1994
1995
1996
1997
1998
1999
2000
!Here we call the compaction subroutine, which updates density_str 'density' entries
!(current density), calculates compaction velocities based on the difference between
!current and past densities (density and densityp), where densityp is the density
!profiles from the start of the time step.
!Compaction velocities are used to move the surfaces.
!Compaction velocities are added to nodal velocity solution used to advect the cloud.
if (params%compaction) then
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 compaction 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 compaction calculation'
else
if (surf_fixed_spinup .and. params%in_spinup) then
if (iproc.eq.0) write (*,'(a)') shift//'WARNING: Compaction being used with some fixed position surfaces!'
elseif (surf_fixed .and. .not.params%in_spinup) then
if (iproc.eq.0) write (*,'(a)') shift//'WARNING: Compaction being used with some fixed position surfaces!'
endif
call compaction(params,density_str,osolve,ov,mat,params%dt)
call show_time (total,step,inc,1,'Apply compaction 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'