-
Kyle Klenk (kck540) authoredKyle Klenk (kck540) authored
tempAdjust.f90 13.75 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 tempAdjust_module
! data types
USE nrtype
! derived types to define the data structures
USE data_types,only:&
var_d, & ! data vector (dp)
var_dlength ! data vector with variable length dimension (dp)
! named variables defining elements in the data structures
USE var_lookup,only:iLookPARAM,iLookPROG,iLookDIAG ! named variables for structure elements
! physical constants
USE multiconst,only:Tfreeze ! freezing point of pure water (K)
USE multiconst,only:LH_fus ! latent heat of fusion (J kg-1)
USE multiconst,only:Cp_ice ! specific heat of ice (J kg-1 K-1)
USE multiconst,only:Cp_water ! specific heat of liquid water (J kg-1 K-1)
USE multiconst,only:iden_water ! intrinsic density of water (kg m-3)
! privacy
implicit none
private
public::tempAdjust
contains
! ************************************************************************************************
! public subroutine tempAdjust: compute change in snow stored on the vegetation canopy
! ************************************************************************************************
subroutine tempAdjust(&
! input: derived parameters
canopyDepth, & ! intent(in): canopy depth (m)
! input/output: data structures
mpar_data, & ! intent(in): model parameters
prog_data, & ! intent(inout): model prognostic variables for a local HRU
diag_data, & ! intent(out): model diagnostic variables for a local HRU
! output: error control
err,message) ! intent(out): error control
! ------------------------------------------------------------------------------------------------
! utility routines
USE snow_utils_module,only:fracliquid ! compute fraction of liquid water
USE snow_utils_module,only:dFracLiq_dTk ! differentiate the freezing curve w.r.t. temperature (snow)
implicit none
! ------------------------------------------------------------------------------------------------
! input: derived parameters
real(dp),intent(in) :: canopyDepth ! depth of the vegetation canopy (m)
! input/output: data structures
type(var_dlength),intent(in) :: mpar_data ! model parameters