Ignore:
Timestamp:
Apr 17, 2020 4:14:16 PM (4 years ago)
Author:
schwenkel
Message:

Implementation of ice microphysics

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/basic_constants_and_equations_mod.f90

    r4400 r4502  
    2525! -----------------
    2626! $Id$
     27! Implementation of ice microphysics
     28!
     29! 4400 2020-02-10 20:32:41Z suehring
    2730! Move routine to transform coordinates from netcdf_interface_mod to
    2831! basic_constants_and_equations_mod
     
    9295    REAL(wp), PARAMETER ::  g_d_cp  = g   / c_p   !< precomputed g / c_p
    9396    REAL(wp), PARAMETER ::  lv_d_cp = l_v / c_p   !< precomputed l_v / c_p
     97    REAL(wp), PARAMETER ::  ls_d_cp = l_s / c_p   !< precomputed l_s / c_p
    9498    REAL(wp), PARAMETER ::  lv_d_rd = l_v / r_d   !< precomputed l_v / r_d
    9599    REAL(wp), PARAMETER ::  rd_d_rv = r_d / r_v   !< precomputed r_d / r_v
     
    106110    PRIVATE magnus_0d, &
    107111            magnus_1d, &
     112            magnus_tl_0d, &
     113            magnus_tl_1d, &
     114            magnus_0d_ice, &
     115            magnus_1d_ice, &
    108116            ideal_gas_law_rho_0d, &
    109117            ideal_gas_law_rho_1d, &
     
    126134       MODULE PROCEDURE magnus_1d
    127135    END INTERFACE magnus
     136
     137    INTERFACE magnus_tl
     138       MODULE PROCEDURE magnus_tl_0d
     139       MODULE PROCEDURE magnus_tl_1d
     140    END INTERFACE magnus_tl
     141
     142    INTERFACE magnus_ice
     143       MODULE PROCEDURE magnus_0d_ice
     144       MODULE PROCEDURE magnus_1d_ice
     145    END INTERFACE magnus_ice
    128146
    129147    INTERFACE ideal_gas_law_rho
     
    337355! Description:
    338356! ------------
     357!> This function computes the magnus formula (Press et al., 1992) using the
     358!> (ice-) liquid water potential temperature.
     359!> The magnus formula is needed to calculate the saturation vapor pressure over
     360!> a plane liquid water surface
     361!------------------------------------------------------------------------------!
     362    FUNCTION magnus_tl_0d( t_l )
     363
     364       IMPLICIT NONE
     365
     366       REAL(wp), INTENT(IN) ::  t_l  !< liquid water temperature (K)
     367
     368       REAL(wp) ::  magnus_tl_0d
     369!
     370!--    Saturation vapor pressure for a specific temperature:
     371       magnus_tl_0d =  610.78_wp * EXP( 17.269_wp * ( t_l - 273.16_wp ) /             &
     372                                                    ( t_l - 35.86_wp  ) )
     373
     374    END FUNCTION magnus_tl_0d
     375
     376!------------------------------------------------------------------------------!
     377! Description:
     378! ------------
     379!> This function computes the magnus formula (Press et al., 1992) using the
     380!> (ice-) liquid water potential temperature.
     381!> The magnus formula is needed to calculate the saturation vapor pressure over
     382!> a plane liquid water surface
     383!------------------------------------------------------------------------------!
     384    FUNCTION magnus_tl_1d( t_l )
     385
     386       IMPLICIT NONE
     387
     388       REAL(wp), INTENT(IN), DIMENSION(:) ::  t_l  !< liquid water temperature (K)
     389
     390       REAL(wp), DIMENSION(size(t_l)) ::  magnus_tl_1d
     391!
     392!--    Saturation vapor pressure for a specific temperature:
     393       magnus_tl_1d =  610.78_wp * EXP( 17.269_wp * ( t_l - 273.16_wp ) /      &
     394                                                    ( t_l - 35.86_wp  ) )
     395
     396    END FUNCTION magnus_tl_1d
     397
     398!------------------------------------------------------------------------------!
     399! Description:
     400! ------------
     401!> This function computes the magnus formula (Press et al., 1992).
     402!> The magnus formula is needed to calculate the saturation vapor pressure over
     403!> a plane ice surface
     404!------------------------------------------------------------------------------!
     405    FUNCTION magnus_0d_ice( t )
     406
     407       IMPLICIT NONE
     408
     409       REAL(wp), INTENT(IN) ::  t  !< temperature (K)
     410
     411       REAL(wp) ::  magnus_0d_ice
     412!
     413!--    Saturation vapor pressure for a specific temperature:
     414       magnus_0d_ice =  611.2_wp * EXP( 22.46_wp * ( t - degc_to_k ) /         &
     415                                                   ( t - 0.53_wp  ) )
     416
     417    END FUNCTION magnus_0d_ice
     418
     419!------------------------------------------------------------------------------!
     420! Description:
     421! ------------
     422!> This function computes the magnus formula (Press et al., 1992).
     423!> The magnus formula is needed to calculate the saturation vapor pressure over
     424!> a plane ice surface
     425!------------------------------------------------------------------------------!
     426    FUNCTION magnus_1d_ice( t )
     427
     428       IMPLICIT NONE
     429
     430       REAL(wp), INTENT(IN), DIMENSION(:) ::  t  !< temperature (K)
     431
     432       REAL(wp), DIMENSION(size(t)) ::  magnus_1d_ice
     433!
     434!--    Saturation vapor pressure for a specific temperature:
     435       magnus_1d_ice =  611.2_wp * EXP( 22.46_wp * ( t - degc_to_k ) /          &
     436                                                   ( t - 0.53_wp  ) )
     437
     438    END FUNCTION magnus_1d_ice
     439
     440!------------------------------------------------------------------------------!
     441! Description:
     442! ------------
    339443!> Compute the ideal gas law for scalar arguments.
    340444!------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.