source: trunk/LMDZ.MARS/libf/phymars/watersat_mod.F90 @ 3493

Last change on this file since 3493 was 3212, checked in by llange, 11 months ago

Mars PCM
Small mistake in the previous commit, I forgot to do the "svn add".
Note that watersat has been transposed from .F to .F90
LL

File size: 2.2 KB
Line 
1 MODULE watersat_mod
2 
3!======================================================================================================================!
4! Subject:
5!---------
6!   Module used to compute the saturation water vapor pressure and qsat
7!----------------------------------------------------------------------------------------------------------------------!
8! Reference:
9!-----------
10!  Laurent Li Parameterization documentation. Checked again Murphy and Koop 2005 (QJRMS)
11!
12!======================================================================================================================!
13
14
15IMPLICIT NONE
16
17CONTAINS
18     
19      SUBROUTINE watersat(gridsize,T,P,qsat)
20     
21      IMPLICIT NONE
22
23!=======================================================================
24!
25!  Water mass mixing ratio at saturation (kg/kg) for a given pressure (Pa)
26!  and Temperature (K) array of dimension gridsize
27!
28!  Moved in module by Deborah BARDET 02/07/18
29!  Adapted in F90 by LL 09/02/2024
30!=======================================================================
31
32!   declarations:
33!   -------------
34!   arguments:
35!   ----------
36
37!   INPUT
38      INTEGER, INTENT(in) :: gridsize              ! Dimension of the array
39      REAL, INTENT(in) :: T(gridsize)    ! Temperature [K]
40      REAL, INTENT(in) :: p(gridsize)              ! Pressure [Pa]
41     
42!   OUTPUT
43      real, INTENT(out) :: qsat(gridsize)          ! qsat for water vapor [kg/kg]
44     
45!   local:
46!   ------
47      INTEGER :: i                                 ! Loop index
48      REAL :: psat                                 ! Saturation water vapor over ice [Pa]
49      REAL :: epsi                                 ! Rapport of water molar mass over CO2 molar mass [1] 
50         
51!    Code:
52!    --------
53      epsi = 18./44. !~0.41, as in other version. Perhaps should be recomputed properly is mu_dry changes ?
54      do i=1,gridsize
55          psat = 100.0 * 10**(2.07023 - 0.00320991*T(i) - 2484.896 / T(i) + 3.56654 * log10(T(i)))
56          if(psat.gt.P(i)) then
57              qsat(i) = 1.
58          else
59              qsat(i) = epsi*psat/(P(i)-(1.-epsi)*psat)
60              qsat(i) = max(qsat(i), 1.e-30) ! in case of tiny value
61          endif
62      enddo
63
64      END SUBROUTINE watersat
65     
66      END MODULE watersat_mod       
Note: See TracBrowser for help on using the repository browser.