Skip to content

Commit

Permalink
remove 3d fields
Browse files Browse the repository at this point in the history
  • Loading branch information
swensosc committed Mar 15, 2023
1 parent 4cfb548 commit cf3716e
Show file tree
Hide file tree
Showing 3 changed files with 41 additions and 70 deletions.
2 changes: 1 addition & 1 deletion src/biogeophys/IrrigationMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -133,7 +133,7 @@ module IrrigationMod
real(r8), pointer :: relsat_target_col(:,:) ! relative saturation at which smp is at the irrigation target [col, nlevsoi]

! Private data members; time-varying:
real(r8), pointer, public :: irrig_rate_patch (:) ! current irrigation rate [mm/s]
real(r8), pointer :: irrig_rate_patch (:) ! current irrigation rate [mm/s]
real(r8), pointer :: irrig_rate_demand_patch (:) ! current irrigation rate, neglecting surface water source limitation [mm/s]
integer , pointer :: n_irrig_steps_left_patch (:) ! number of time steps for which we still need to irrigate today (if 0, ignore)
real(r8), pointer :: qflx_irrig_demand_patch (:) ! irrigation flux neglecting surface water source limitation [mm/s]
Expand Down
106 changes: 40 additions & 66 deletions src/biogeophys/IrrigationStreamMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ module IrrigationStreamMod
use clm_varctl , only : iulog, use_irrigation_streams
use clm_varcon , only : grlnd
use controlMod , only : NLFilename
use decompMod , only : gsMap_lnd2Dsoi_gdc2glo
use decompMod , only : gsmap_lnd_gdc2glo
use domainMod , only : ldomain
use fileutils , only : getavu, relavu
use GridcellType , only : grc
Expand All @@ -44,7 +44,6 @@ module IrrigationStreamMod
type(shr_strdata_type) :: sdat_irrig ! irrigation input data stream
integer :: ism ! irrigation stream index
integer :: nfields ! number of fields in irrigation stream
integer, parameter :: nirrig = 2 ! number of crops on streams file
character(SHR_KIND_CXX), allocatable :: fldNames(:)
integer, allocatable :: g_to_ig(:) ! Array matching gridcell index to data index
logical :: irrig_ignore_data_if_missing ! If should ignore overridding a point with irrigation data
Expand Down Expand Up @@ -163,9 +162,7 @@ subroutine PrescribedIrrigationInit(bounds)

endif

!scs
call clm_domain_mct (bounds, dom_clm, nlevels=nirrig)
!call clm_domain_mct (bounds, dom_clm)
call clm_domain_mct (bounds, dom_clm)

!
! create the field list for these fields...use in shr_strdata_create
Expand All @@ -182,9 +179,8 @@ subroutine PrescribedIrrigationInit(bounds)
pio_subsystem=pio_subsystem, &
pio_iotype=shr_pio_getiotype(inst_name), &
mpicom=mpicom, compid=comp_id, &
gsmap=gsMap_lnd2Dsoi_gdc2glo, ggrid=dom_clm, &
gsmap=gsmap_lnd_gdc2glo, ggrid=dom_clm, &
nxg=ldomain%ni, nyg=ldomain%nj, &
nzg=nirrig, &
yearFirst=stream_year_first_irrig, &
yearLast=stream_year_last_irrig, &
yearAlign=model_year_align_irrig, &
Expand All @@ -194,15 +190,14 @@ subroutine PrescribedIrrigationInit(bounds)
domTvarName='time', &
domXvarName='lon' , &
domYvarName='lat' , &
domZvarName='numcft' , &
domAreaName='area', &
domMaskName='mask', &
filePath='', &
filename=(/stream_fldFileName_irrig/), &
fldListFile=fldList, &
fldListModel=fldList, &
fillalgo='none', &
mapalgo='none', &
mapalgo='nn', &
tintalgo=irrig_tintalgo, &
calendar=get_calendar(), &
! dtlimit = 15._r8, &
Expand Down Expand Up @@ -243,17 +238,8 @@ subroutine PrescribedIrrigationAdvance( bounds )
call get_curr_date(year, mon, day, sec)
mcdate = year*10000 + mon*100 + day

! stream_var_name = 'H2OSOI'

! Determine variable index
! ism = mct_aVect_indexRA(sdat_irrig%avs(1),trim(stream_var_name))

call shr_strdata_advance(sdat_irrig, mcdate, sec, mpicom, 'irrigation')

!!$ do g = 1, nfields
!!$ call shr_strdata_advance(sdat_irrig, mcdate, sec, mpicom, fldNames(g))
!!$ enddo

! Map gridcell to AV index
ier = 0
if ( .not. allocated(g_to_ig) )then
Expand Down Expand Up @@ -300,28 +286,26 @@ subroutine PrescribedIrrigationInterp(bounds, irrigation_inst)
integer :: mcdate ! current date
integer :: yr,mon,day,nbsec ! year,month,day,seconds components of a date
integer :: hours,minutes,secs ! hours,minutes,seconds of hh:mm:ss
real(r8), allocatable :: irrig_rate_prescribed (:,:) ! prescribed rate of irrigation
real(r8), allocatable :: irrig_rate_duration (:,:) ! prescribed duration of irrigation
real(r8), allocatable :: irrig_start_time (:,:)
real(r8), allocatable :: irrig_crop_type (:,:)
real(r8), allocatable :: irrig_lon (:,:)
real(r8), allocatable :: irrig_lat (:,:)
real(r8), allocatable :: irrig_rate_prescribed (:) ! prescribed rate of irrigation
real(r8), allocatable :: irrig_rate_duration (:) ! prescribed duration of irrigation
real(r8), allocatable :: irrig_start_time (:)
integer, allocatable :: irrig_crop_type (:)
real(r8), allocatable :: irrig_lon (:)
real(r8), allocatable :: irrig_lat (:)
real(r8), parameter :: eps = 1e-3_r8

character(*), parameter :: subName = "('PrescribedIrrigationInterp')"

!-----------------------------------------------------------------------

! SHR_ASSERT_FL( (lbound(sdat_irrig%avs(1)%rAttr,1) == ism ), sourcefile, __LINE__)
! SHR_ASSERT_FL( (ubound(sdat_irrig%avs(1)%rAttr,1) == ism ), sourcefile, __LINE__)
SHR_ASSERT_FL( (lbound(g_to_ig,1) <= bounds%begg ), sourcefile, __LINE__)
SHR_ASSERT_FL( (ubound(g_to_ig,1) >= bounds%endg ), sourcefile, __LINE__)

associate( &
irrig_rate_patch => irrigation_inst%irrig_rate_patch & ! Input: [real(r8) (:,:) ] current irrigation rate [mm/s]
qflx_irrig_patch => irrigation_inst%qflx_irrig_patch & ! Input: [real(r8) (:,:) ] patch irrigation flux (mm H2O/s)
)
SHR_ASSERT_FL( (lbound(irrig_rate_patch,1) <= bounds%begp ), sourcefile, __LINE__)
SHR_ASSERT_FL( (ubound(irrig_rate_patch,1) >= bounds%endp ), sourcefile, __LINE__)
SHR_ASSERT_FL( (lbound(qflx_irrig_patch,1) <= bounds%begp ), sourcefile, __LINE__)
SHR_ASSERT_FL( (ubound(qflx_irrig_patch,1) >= bounds%endp ), sourcefile, __LINE__)

!
! Set the prescribed irrigation read from the file everywhere
Expand All @@ -330,62 +314,52 @@ subroutine PrescribedIrrigationInterp(bounds, irrigation_inst)
call get_curr_time (mdcur, mscur)
call get_curr_date (yr, mon, day, mcsec)

allocate(irrig_rate_prescribed(bounds%begg:bounds%endg,nirrig))
allocate(irrig_rate_duration(bounds%begg:bounds%endg,nirrig))
allocate(irrig_start_time(bounds%begg:bounds%endg,nirrig))
allocate(irrig_crop_type(bounds%begg:bounds%endg,nirrig))
allocate(irrig_lon(bounds%begg:bounds%endg,nirrig))
allocate(irrig_lat(bounds%begg:bounds%endg,nirrig))
allocate(irrig_rate_prescribed(bounds%begg:bounds%endg))
allocate(irrig_rate_duration(bounds%begg:bounds%endg))
allocate(irrig_start_time(bounds%begg:bounds%endg))
allocate(irrig_crop_type(bounds%begg:bounds%endg))
allocate(irrig_lon(bounds%begg:bounds%endg))
allocate(irrig_lat(bounds%begg:bounds%endg))

! Read data from data streams
do g = bounds%begg, bounds%endg
ig = g_to_ig(g)

do j = 1, nirrig

!n = ig + (j-1)*size(g_to_ig)
n = ig + (j-1)*size(g_to_ig)

ip = mct_aVect_indexRA(sdat_irrig%avs(1),'irrig_rate')
irrig_rate_prescribed(g,j) = sdat_irrig%avs(1)%rAttr(ip,n)
ip = mct_aVect_indexRA(sdat_irrig%avs(1),'irrig_rate')
irrig_rate_prescribed(g) = sdat_irrig%avs(1)%rAttr(ip,ig)

ip = mct_aVect_indexRA(sdat_irrig%avs(1),'irrig_duration')
irrig_rate_duration(g,j) = sdat_irrig%avs(1)%rAttr(ip,n)
ip = mct_aVect_indexRA(sdat_irrig%avs(1),'irrig_duration')
irrig_rate_duration(g) = sdat_irrig%avs(1)%rAttr(ip,ig)

ip = mct_aVect_indexRA(sdat_irrig%avs(1),'irrig_start_time')
irrig_start_time(g,j) = sdat_irrig%avs(1)%rAttr(ip,n)
ip = mct_aVect_indexRA(sdat_irrig%avs(1),'irrig_start_time')
irrig_start_time(g) = sdat_irrig%avs(1)%rAttr(ip,ig)

ip = mct_aVect_indexRA(sdat_irrig%avs(1),'crop_type')
irrig_crop_type(g,j) = sdat_irrig%avs(1)%rAttr(ip,n)
ip = mct_aVect_indexRA(sdat_irrig%avs(1),'crop_type')
irrig_crop_type(g) = int(sdat_irrig%avs(1)%rAttr(ip,ig))

ip = mct_aVect_indexRA(sdat_irrig%avs(1),'irrig_longitude')
irrig_lon(g,j) = sdat_irrig%avs(1)%rAttr(ip,n)
ip = mct_aVect_indexRA(sdat_irrig%avs(1),'irrig_longitude')
irrig_lon(g) = sdat_irrig%avs(1)%rAttr(ip,ig)

ip = mct_aVect_indexRA(sdat_irrig%avs(1),'irrig_latitude')
irrig_lat(g,j) = sdat_irrig%avs(1)%rAttr(ip,n)

end do
ip = mct_aVect_indexRA(sdat_irrig%avs(1),'irrig_latitude')
irrig_lat(g) = sdat_irrig%avs(1)%rAttr(ip,ig)
end do


do p = bounds%begp, bounds%endp
if (lun%itype(patch%landunit(p)) == istcrop) then
g = patch%gridcell(p)
ivt = patch%itype(p)

g = patch%gridcell(p)
ivt = patch%itype(p)

do j = 1, nirrig

if((abs(irrig_lon(g,j) - grc%londeg(g)) < eps) .and. (abs(irrig_lat(g,j) - grc%latdeg(g)) < eps) .and. (ivt == irrig_crop_type(g,j))) then

! if((abs(irrig_lon(g) - grc%londeg(g)) < eps) .and. (abs(irrig_lat(g) - grc%latdeg(g)) < eps) .and. (ivt == irrig_crop_type(g))) then
if(ivt == int(irrig_crop_type(g))) then

if ((mscur >= irrig_start_time(g,j)) .and. (mscur <= (irrig_start_time(g,j)+irrig_rate_duration(g,j)))) then
if ((mscur >= irrig_start_time(g)) .and. (mscur <= (irrig_start_time(g)+irrig_rate_duration(g)))) then

irrig_rate_patch(p) = irrig_rate_prescribed(g,j)
qflx_irrig_patch(p) = irrig_rate_prescribed(g)
else
irrig_rate_patch(p) = 0._r8
qflx_irrig_patch(p) = 0._r8
endif
endif
enddo
endif
enddo

deallocate(irrig_rate_prescribed,irrig_rate_duration,irrig_start_time,irrig_crop_type,irrig_lon,irrig_lat)
Expand Down
3 changes: 0 additions & 3 deletions src/main/clm_initializeMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -127,9 +127,6 @@ subroutine initialize1( )

if(use_soil_moisture_streams) call decompInit_lnd3D(ni, nj, nlevsoi)

!scs: this is hardcoded right now so it needs to match stream file
if(use_irrigation_streams) call decompInit_lnd3D(ni, nj, 2)

! *** Get JUST gridcell processor bounds ***
! Remaining bounds (landunits, columns, patches) will be determined
! after the call to decompInit_glcp - so get_proc_bounds is called
Expand Down

0 comments on commit cf3716e

Please sign in to comment.