Skip to content

Commit

Permalink
Runs, but outputs garbage
Browse files Browse the repository at this point in the history
  • Loading branch information
Austin Michael Blevins committed Dec 5, 2022
1 parent 03f9fc7 commit 7b5e644
Show file tree
Hide file tree
Showing 4 changed files with 48 additions and 32 deletions.
4 changes: 2 additions & 2 deletions src/Makefile.am
Original file line number Diff line number Diff line change
Expand Up @@ -7,11 +7,11 @@ OPTREPORT = -qopt-report=5
IPRODUCTION = -g -traceback -no-wrap-margin -assume byterecl -O3 -qopt-prefetch=0 -sox $(PAR) $(SIMDVEC) $(HEAPARR)
#IDEBUG = -O0 -g -traceback -debug all -nogen-interfaces -assume byterecl -m64 -heap-arrays -FR -no-pie -no-ftz -fpe-all=0 -mp1 -fp-model strict -fpe0 -align all -pad -ip -prec-div -prec-sqrt -assume protect-parens -CB -no-wrap-margin -init=snan,arrays
IDEBUG = -O0 -g -traceback -debug all -nogen-interfaces -assume byterecl -m64 -heap-arrays -FR -no-pie -no-ftz -fpe-all=0 -mp1 -fp-model strict -fpe0 -align all -pad -ip -prec-sqrt -assume protect-parens -CB -no-wrap-margin -init=snan,arrays
#AM_FCFLAGS = $(IPRODUCTION)
AM_FCFLAGS = $(IDEBUG)
#ifort debug flags

#gfortran optimized flags
AM_FCFLAGS = -O3 -fopenmp -ffree-form -g -fbounds-check -fbacktrace
#AM_FCFLAGS = -O3 -fopenmp -ffree-form -g -fbounds-check -fbacktrace
#gfortran debug flags
#AM_FCFLAGS = -O0 -g -fopenmp -fbounds-check -Wall -Warray-bounds -Warray-temporaries -Wimplicit-interface -ffree-form -fsanitize-address-use-after-scope -fstack-check -fsanitize=bounds-strict -fsanitize=undefined -fsanitize=signed-integer-overflow -fsanitize=object-size -fstack-protector-all

Expand Down
7 changes: 5 additions & 2 deletions src/io/io_write_regotrack.f90
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,9 @@ subroutine io_write_regotrack(user,surf)
do j=1,user%gridsize
do i=1,user%gridsize
!current => surf(i,j)%regolayer
current = surf(i,j)%regolayer(1)
allocate(current,source=surf(i,j)%regolayer)
stacks_num(i,j) = size(current)
deallocate(current)
! do
! if (.not. associated(current)) exit ! We've reached the bottom of the linked list
! stacks_num(i,j) = stacks_num(i,j) + 1
Expand All @@ -70,8 +72,8 @@ subroutine io_write_regotrack(user,surf)
!current => surf(i,j)%regolayer
N = stacks_num(i,j)
allocate(meltfrac(N),thickness(N),comp(N),age(MAXAGEBINS,N))
allocate(current,source=surf(i,j)%regolayer)
do k=1,N
current = surf(i,j)%regolayer(k)
! meltfrac(k) = current%regodata%meltfrac
! thickness(k) = current%regodata%thickness
! comp(k) = current%regodata%comp
Expand All @@ -83,6 +85,7 @@ subroutine io_write_regotrack(user,surf)
age(:,k) = current(k)%age(:)

end do
deallocate(current)
write(FMELT) meltfrac(:)
write(FREGO) thickness(:)
write(FCOMP) comp(:)
Expand Down
18 changes: 8 additions & 10 deletions src/regolith/regolith_mix.f90
Original file line number Diff line number Diff line change
Expand Up @@ -29,13 +29,13 @@ subroutine regolith_mix(surfi,mixing_depth)
! Internal variables
type(regodatatype) :: newlayer
!type(regolisttype),pointer :: poppedlist,poppedlist_top
type(regodatatype),dimension(:),allocatable :: poppedarray, poppedarray_top
integer(I4B) :: N
type(regodatatype),dimension(:),allocatable :: poppedarray
integer(I4B) :: i, N

!===============================================
! Add up all layers' info until a desired depth
!===============================================
call util_traverse_pop_array(surfi%regolayer,mixing_depth,poppedarray_top)
call util_traverse_pop_array(surfi%regolayer,mixing_depth,poppedarray)

newlayer%thickness = 0.0_DP
newlayer%comp = 0.0_DP
Expand All @@ -45,13 +45,12 @@ subroutine regolith_mix(surfi,mixing_depth)
!poppedlist => poppedlist_top
!do while(associated(poppedlist%next))
N = size(poppedarray)
do
newlayer%thickness = newlayer%thickness + poppedarray(N)%thickness
newlayer%comp = newlayer%comp + poppedarray(N)%thickness * poppedarray(N)%comp
newlayer%meltfrac = newlayer%meltfrac + poppedarray(N)%thickness * poppedarray(N)%meltfrac
newlayer%age(:) = newlayer%age(:) + poppedarray(N)%age(:)
do i = N,1,-1
newlayer%thickness = newlayer%thickness + poppedarray(i)%thickness
newlayer%comp = newlayer%comp + poppedarray(i)%thickness * poppedarray(i)%comp
newlayer%meltfrac = newlayer%meltfrac + poppedarray(i)%thickness * poppedarray(i)%meltfrac
newlayer%age(:) = newlayer%age(:) + poppedarray(i)%age(:)
!poppedlist => poppedlist%next
N = N - 1
end do

! Get average values of composition and melt fraction
Expand All @@ -60,7 +59,6 @@ subroutine regolith_mix(surfi,mixing_depth)

call util_push_array(surfi%regolayer, newlayer)
!call util_destroy_list(poppedlist_top)
deallocate(poppedarray_top)

return
end subroutine regolith_mix
51 changes: 33 additions & 18 deletions src/util/util_traverse_pop_array.f90
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ subroutine util_traverse_pop_array(regolayer,traverse_depth,poppedarray)

! Internal variables
real(DP) :: z,depth,dz
type(regodatatype) :: oldregodata
type(regodatatype),dimension(:),allocatable :: oldregodata
logical :: initstat
real(DP) :: recyratio
integer(I4B) :: i, N, maxi
Expand All @@ -42,16 +42,9 @@ subroutine util_traverse_pop_array(regolayer,traverse_depth,poppedarray)
dz = 0._DP
z = traverse_depth



! Initialize popped array
call util_init_array(poppedarray,initstat)


!if (initstat) then
i = N
do
depth = depth + regolayer(i)%depth
depth = depth + regolayer(i)%thickness
if (depth > traverse_depth) then
maxi = i
exit
Expand All @@ -61,20 +54,42 @@ subroutine util_traverse_pop_array(regolayer,traverse_depth,poppedarray)
end do


!allocate(poppedarray,source=regolayer(maxi:N))
allocate(poppedarray,source=regolayer(maxi:N))


!depth = regolayer(maxi)%thickness

depth = 0
do i=1+maxi,N ! is this correct? NO- must check
depth = depth + regolayer(i)%thickness
end do

!for #1 element of poppedarray, shrink thickness by whatever was lefr over. In corresponding maxi of regolayer, also need to change that.

depth = regolayer(maxi)%depth
poppedarray(1)%thickness = z - depth
regolayer(maxi)%thickness = regolayer(maxi)%thickness - z

! copy regolayer from 1 to maxi to temp variable, then deallocate regolayer, then movealloc templayer onto regolayer <--may need temp array
allocate(oldregodata,source=regolayer(1:maxi))
deallocate(regolayer)
call move_alloc(oldregodata,regolayer) ! right intents?

! if (z <= depth) then
! dz = depth - z
oldregodata = regolayer(maxi)
oldregodata%thickness = z
oldregodata%age(:) = z / regolayer(maxi)%thickness * regolayer(maxi)%age(:)
recyratio = dz / regolayer(maxi)%thickness
regolayer(maxi)%age(:) = recyratio * regolayer(maxi)%age(:)
regolayer(maxi)%thickness = dz
call util_push_array(poppedarray,oldregodata)

!*****the following lines may still be needed, especially if they deal with thickness:*****

! oldregodata = regolayer(maxi)
! oldregodata%thickness = z
! oldregodata%age(:) = z / regolayer(maxi)%thickness * regolayer(maxi)%age(:)
! recyratio = dz / regolayer(maxi)%thickness
! regolayer(maxi)%age(:) = recyratio * regolayer(maxi)%age(:)
! regolayer(maxi)%thickness = dz

!********************


!call util_push_array(poppedarray,oldregodata) <--not needed; just editing in place
! else
! z = z - regolayer%thickness
! call util_pop_array(regolayer,oldregodata)
Expand Down

0 comments on commit 7b5e644

Please sign in to comment.