Skip to content

Commit

Permalink
Restructured the regolith stacks so that there is no longer a buffer …
Browse files Browse the repository at this point in the history
…layer. Layer 1 is now a bedrock layer down to the centerl starts from bedrock now.
  • Loading branch information
daminton committed Sep 5, 2023
1 parent 2b3dd3e commit 8675eca
Show file tree
Hide file tree
Showing 5 changed files with 7 additions and 50 deletions.
2 changes: 1 addition & 1 deletion src/Makefile.am
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ AM_FCFLAGS = $(IPRODUCTION)
#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
3 changes: 0 additions & 3 deletions src/globals/module_globals.f90
Original file line number Diff line number Diff line change
Expand Up @@ -67,9 +67,6 @@ module module_globals
real(SP),dimension(MAXAGEBINS) :: age
real(DP) :: thickness
real(DP) :: comp
real(DP) :: porosity ! Porosity: Maximum 1, Minium 0.
real(DP) :: damage ! Damage : Maximum 1, Minium 0.
real(DP) :: depth ! Absolute location with respect to the initial surface.
real(DP) :: meltvolume
real(DP) :: totvolume
real(DP) :: ejm !ejected melt
Expand Down
29 changes: 3 additions & 26 deletions src/init/init_regolith_stack.f90
Original file line number Diff line number Diff line change
Expand Up @@ -28,41 +28,18 @@ subroutine init_regolith_stack(user,surf,domain)
type(usertype),intent(in) :: user
type(surftype),dimension(:,:),intent(inout) :: surf
type(domaintype),intent(in) :: domain
type(regodatatype) :: bedrock
integer(I4B) :: xp,yp,k
integer(I4B) :: xp,yp

! Internal variables
logical :: initstat

! Temporary variable setup for initialize a pre-exising structure
type(regodatatype) :: test_stratig

!call init_regolith_parab(user,surf)
!=======================================
! Initialize the grid space
!=======================================
bedrock%thickness = user%trad
bedrock%comp = 0._DP
bedrock%age(:) = 0.0_SP
allocate(bedrock%distvol(1+domain%rcnum))
bedrock%distvol(:) = 0.0_SP
bedrock%meltvolume = 0.0_DP
bedrock%totvolume = bedrock%thickness * user%pix * user%pix
bedrock%ejm = 0.0_DP

do yp = 1, user%gridsize
do xp = 1, user%gridsize

!call util_init_list(surf(xp,yp)%regolayer,initstat)
call util_init_array(user,surf(xp,yp)%regolayer,domain,initstat)

if (initstat) then
call util_push_array(surf(xp,yp)%regolayer,bedrock)
else
write(*,*) 'init_regolith_stack: Initialization of regolayer failed.'
end if

end do
do concurrent(xp=1:user%gridsize,yp=1:user%gridsize)
call util_init_array(user,surf(xp,yp)%regolayer,domain,initstat)
end do

return
Expand Down
2 changes: 1 addition & 1 deletion src/util/module_util.f90
Original file line number Diff line number Diff line change
Expand Up @@ -111,7 +111,7 @@ end subroutine util_destroy_list
! end interface

interface
subroutine util_init_array(user,regolayer,domain,initstat)
pure subroutine util_init_array(user,regolayer,domain,initstat)
use module_globals
implicit none
type(usertype),intent(in) :: user
Expand Down
21 changes: 2 additions & 19 deletions src/util/util_init_array.f90
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@
! Notes :
!
!**********************************************************************************************************************************
subroutine util_init_array(user,regolayer,domain,initstat)
pure subroutine util_init_array(user,regolayer,domain,initstat)
use module_globals
use module_util, EXCEPT_THIS_ONE => util_init_array
implicit none
Expand All @@ -35,36 +35,19 @@ subroutine util_init_array(user,regolayer,domain,initstat)

! Executable code
initstat = .false.
! if (.not. associated(regolayer)) then
! allocate(regolayer, STAT=allocstat)
! if (allocstat == 0) then
! initstat = .true.
! nullify(regolayer%next)
! regolayer%regodata%thickness = sqrt(VBIG) ! This generates a buffer layer that the model should never reach if the run is structured properly
! regolayer%regodata%comp = 0.0_DP
! regolayer%regodata%meltfrac = 0.0_DP
! regolayer%regodata%porosity = 0.0_DP
! regolayer%regodata%age(:) = 0.0_SP
if (allocated(regolayer)) deallocate(regolayer)
allocate(regolayer(1),stat=allocstat)
if (allocstat == 0) then
initstat = .true.
regolayer(1)%thickness = sqrt(VBIG) ! This generates a buffer layer that the model should never reach if the run is structured properly
regolayer(1)%thickness = user%trad ! This generates a buffer layer that the model should never reach if the run is structured properly
regolayer(1)%comp = 0.0_DP
regolayer(1)%porosity = 0.0_DP
regolayer(1)%age(:) = 0.0_SP
regolayer(1)%ejm = 0.0_DP
allocate(regolayer(1)%distvol(1+domain%rcnum))
regolayer(1)%distvol(:) = 0.0_SP
regolayer(1)%meltvolume = 0.0_DP
regolayer(1)%totvolume = regolayer(1)%thickness * user%pix * user%pix
end if
! else
! write(*,*) 'util_init_list: Initialization failed. Exhausted memory.'
! end if
! else
! write(*,*) 'util_init_list: Initialization failed. Regolayer already associated.'
! end if

return
end subroutine util_init_array

0 comments on commit 8675eca

Please sign in to comment.