Skip to content

Commit

Permalink
Merge pull request #250 from nmizukami/cesm-coupling
Browse files Browse the repository at this point in the history
small corrections
  • Loading branch information
nmizukami authored Jan 15, 2022
2 parents cfc1813 + d0c5771 commit e9065c2
Show file tree
Hide file tree
Showing 4 changed files with 20 additions and 19 deletions.
10 changes: 5 additions & 5 deletions route/build/src/domain_decomposition.f90
Original file line number Diff line number Diff line change
Expand Up @@ -18,11 +18,11 @@ MODULE domain_decomposition

implicit none

logical(lgt) :: domain_debug = .false. ! print out reach info with node assignment for debugging
logical(lgt) :: domain_debug = .false. ! print out reach info with node assignment for debugging purpose

! common parameters within this module
integer(i4b), parameter :: maxDomainOMP=50000 ! maximum omp domains
integer(i4b), parameter :: maxDomainMPI=100000 ! maximum mpi domains
integer(i4b), parameter :: maxDomainMPI=150000 ! maximum mpi domains
integer(i4b), parameter :: tributary=1
integer(i4b), parameter :: mainstem=2
integer(i4b), parameter :: endorheic=3
Expand Down Expand Up @@ -666,7 +666,7 @@ SUBROUTINE decomposeDomain(structNTOPO, & ! input:
nDomains = nDomains + 1

allocate(domains_out(nDomains)%segIndex(nUpSegs), stat=ierr, errmsg=cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage)//' [domains_out(nDomains)%segIndex]'; return; endif
if(ierr/=0)then; message=trim(message)//trim(cmessage)//' [1. domains_out(nDomains)%segIndex]'; return; endif

domains_out(nDomains)%basinType = tributary
domains_out(nDomains)%segIndex = structNTOPO(ixOutlets(iOut))%var(ixNTOPO%allUpSegIndices)%dat
Expand All @@ -684,7 +684,7 @@ SUBROUTINE decomposeDomain(structNTOPO, & ! input:
! 1. populate domains data structure
nDomains = nDomains + 1
allocate(domains_out(nDomains)%segIndex(nMainstem), stat=ierr, errmsg=cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage)//' [domains_out(nDomains)%segIndex]'; return; endif
if(ierr/=0)then; message=trim(message)//trim(cmessage)//' [2. domains_out(nDomains)%segIndex]'; return; endif
domains_out(nDomains)%basinType = mainstem
domains_out(nDomains)%segIndex = segIndex(ixSubset)

Expand Down Expand Up @@ -722,7 +722,7 @@ SUBROUTINE decomposeDomain(structNTOPO, & ! input:
nDomains = nDomains + 1

allocate(domains_out(nDomains)%segIndex(nUpSegs), stat=ierr, errmsg=cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage)//' [domains_out(nDomain)%segIndex]'; return; endif
if(ierr/=0)then; message=trim(message)//trim(cmessage)//' [3. domains_out(nDomain)%segIndex]'; return; endif

domains_out(nDomains)%basinType = tributary
domains_out(nDomains)%segIndex = structNTOPO(ixTribOutlet(iTrib))%var(ixNTOPO%allUpSegIndices)%dat
Expand Down
3 changes: 2 additions & 1 deletion route/build/src/kwe_route.f90
Original file line number Diff line number Diff line change
Expand Up @@ -189,7 +189,8 @@ SUBROUTINE kw_rch(iEns, segIndex, & ! input: index of runoff ensemble to be proc
write(iulog,'(A)') 'CHECK Kinematic wave routing'
if (nUps>0) then
do iUps = 1,nUps
write(iulog,'(A,X,I12,X,G15.4)') ' UREACHK, uprflux=',NETOPO_in(segIndex)%UREACHK(iUps),RCHFLX_out(iens, NETOPO_in(segIndex)%UREACHK(iUps))%REACH_Q
iRch_ups = NETOPO_in(segIndex)%UREACHI(iUps) ! index of upstream of segIndex-th reach
write(iulog,'(A,X,I12,X,G15.4)') ' UREACHK, uprflux=',NETOPO_in(segIndex)%UREACHK(iUps),RCHFLX_out(iens, iRch_ups)%REACH_Q
enddo
end if
write(iulog,'(A,X,G15.4)') ' RCHFLX_out(iEns,segIndex)%BASIN_QR(1)=',RCHFLX_out(iEns,segIndex)%BASIN_QR(1)
Expand Down
6 changes: 3 additions & 3 deletions route/build/src/popMetadat.f90
Original file line number Diff line number Diff line change
Expand Up @@ -213,9 +213,9 @@ subroutine popMetadat(err,message)
! ---------- populate segment fluxes/state metadata structures -------------------------------------------------------------------------------------------------------------------
! Reach Flux varName varDesc unit, varType, varDim, writeOut
call meta_rflx(ixRFLX%basRunoff )%init('basRunoff' , 'basin runoff' , 'm/s' , pio_real, [ixQdims%hru,ixQdims%time], .true.)
call meta_rflx(ixRFLX%instRunoff )%init('instRunoff' , 'instantaneous runoff in each reach' , 'm3/s', pio_real, [ixQdims%seg,ixQdims%time], .true.)
call meta_rflx(ixRFLX%dlayRunoff )%init('dlayRunoff' , 'delayed runoff in each reach' , 'm3/s', pio_real, [ixQdims%seg,ixQdims%time], .true.)
call meta_rflx(ixRFLX%sumUpstreamRunoff)%init('sumUpstreamRunoff', 'sum of upstream runoff in each reach' , 'm3/s', pio_real, [ixQdims%seg,ixQdims%time], .true.)
call meta_rflx(ixRFLX%instRunoff )%init('instRunoff' , 'instantaneous runoff in each reach' , 'm3/s', pio_real, [ixQdims%seg,ixQdims%time], .false.)
call meta_rflx(ixRFLX%dlayRunoff )%init('dlayRunoff' , 'delayed runoff in each reach' , 'm3/s', pio_real, [ixQdims%seg,ixQdims%time], .false.)
call meta_rflx(ixRFLX%sumUpstreamRunoff)%init('sumUpstreamRunoff', 'sum of upstream runoff in each reach' , 'm3/s', pio_real, [ixQdims%seg,ixQdims%time], .false.)
call meta_rflx(ixRFLX%IRFroutedRunoff )%init('IRFroutedRunoff' , 'routed runoff in each reach-impulse response function', 'm3/s', pio_real, [ixQdims%seg,ixQdims%time], .true.)
call meta_rflx(ixRFLX%KWTroutedRunoff )%init('KWTroutedRunoff' , 'routed runoff in each reach-lagrangian kinematic wave', 'm3/s', pio_real, [ixQdims%seg,ixQdims%time], .true.)
call meta_rflx(ixRFLX%KWroutedRunoff )%init('KWroutedRunoff' , 'routed runoff in each reach-kinematic wave' , 'm3/s', pio_real, [ixQdims%seg,ixQdims%time], .true.)
Expand Down
20 changes: 10 additions & 10 deletions route/build/src/read_control.f90
Original file line number Diff line number Diff line change
Expand Up @@ -182,16 +182,16 @@ SUBROUTINE read_control(ctl_fname, err, message)
case('<maxPfafLen>'); read(cData,*,iostat=io_error) maxPfafLen ! maximum digit of pfafstetter code (default 32)
case('<pfafMissing>'); pfafMissing = trim(cData) ! missing pfafcode (e.g., reach without any upstream area)
! OUTPUT OPTIONS
case('<basRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%basRunoff )%varFile
case('<instRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%instRunoff )%varFile
case('<dlayRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%dlayRunoff )%varFile
case('<sumUpstreamRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%sumUpstreamRunoff)%varFile
case('<KWTroutedRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%KWTroutedRunoff )%varFile
case('<IRFroutedRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%IRFroutedRunoff )%varFile
case('<KWroutedRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%KWroutedRunoff )%varFile
case('<DWroutedRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%DWroutedRunoff )%varFile
case('<MCroutedRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%MCroutedRunoff )%varFile
case('<volume>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%volume )%varFile
case('<basRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%basRunoff )%varFile ! default: true
case('<instRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%instRunoff )%varFile ! default: false
case('<dlayRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%dlayRunoff )%varFile ! default: false
case('<sumUpstreamRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%sumUpstreamRunoff)%varFile ! default: false
case('<KWTroutedRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%KWTroutedRunoff )%varFile ! default: true (turned off if inactive)
case('<IRFroutedRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%IRFroutedRunoff )%varFile ! default: true (turned off if inactive)
case('<KWroutedRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%KWroutedRunoff )%varFile ! default: true (turned off if inactive)
case('<DWroutedRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%DWroutedRunoff )%varFile ! default: true (turned off if inactive)
case('<MCroutedRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%MCroutedRunoff )%varFile ! default: true (turned off if inactive)
case('<volume>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%volume )%varFile ! default: true

! VARIABLE NAMES for data (overwrite default name in popMeta.f90)
! HRU structure
Expand Down

0 comments on commit e9065c2

Please sign in to comment.