-
Kyle Klenk (kck540) authoredKyle Klenk (kck540) authored
snowLiqFlx.f90 11.79 KiB
! SUMMA - Structure for Unifying Multiple Modeling Alternatives
! Copyright (C) 2014-2020 NCAR/RAL; University of Saskatchewan; University of Washington
!
! This file is part of SUMMA
!
! For more information see: http://www.ral.ucar.edu/projects/summa
!
! This program is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! This program is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with this program. If not, see <http://www.gnu.org/licenses/>.
module snowLiqFlx_module
! access modules
USE nrtype ! numerical recipes data types
USE multiconst,only:iden_ice,iden_water ! intrinsic density of ice and water (kg m-3)
! access missing values
USE globalData,only:integerMissing ! missing integer
USE globalData,only:realMissing ! missing real number
! named variables
USE var_lookup,only:iLookINDEX ! named variables for structure elements
USE var_lookup,only:iLookPARAM ! named variables for structure elements
USE var_lookup,only:iLookPROG ! named variables for structure elements
USE var_lookup,only:iLookDIAG ! named variables for structure elements
! data types
USE data_types,only:var_d ! x%var(:) (dp)
USE data_types,only:var_dlength ! x%var(:)%dat (dp)
USE data_types,only:var_ilength ! x%var(:)%dat (i4b)
! privacy
implicit none
private
public::snowLiqFlx
contains
! ************************************************************************************************
! public subroutine snowLiqFlx: compute liquid water flux through the snowpack
! ************************************************************************************************
subroutine snowLiqFlx(&
! input: model control
nSnow, & ! intent(in): number of snow layers
firstFluxCall, & ! intent(in): the first flux call
scalarSolution, & ! intent(in): flag to indicate the scalar solution
! input: forcing for the snow domain
scalarThroughfallRain, & ! intent(in): rain that reaches the snow surface without ever touching vegetation (kg m-2 s-1)
scalarCanopyLiqDrainage, & ! intent(in): liquid drainage from the vegetation canopy (kg m-2 s-1)
! input: model state vector
mLayerVolFracLiqTrial, & ! intent(in): trial value of volumetric fraction of liquid water at the current iteration (-)
! input-output: data structures
indx_data, & ! intent(in): model indices
mpar_data, & ! intent(in): model parameters
prog_data, & ! intent(in): model prognostic variables for a local HRU
diag_data, & ! intent(inout): model diagnostic variables for a local HRU
! output: fluxes and derivatives
iLayerLiqFluxSnow, & ! intent(inout): vertical liquid water flux at layer interfaces (m s-1)
iLayerLiqFluxSnowDeriv, & ! intent(inout): derivative in vertical liquid water flux at layer interfaces (m s-1)
! output: error control