source: LMDZ6/branches/PBLSURF_GPUPORT/libf/phylmd/qsat_seawater2.f90 @ 5876

Last change on this file since 5876 was 5876, checked in by yann meurdesoif, 8 days ago

GPU port of cdrag + call_atke + coef_diff_turb

YM

File size: 3.6 KB
Line 
1MODULE qsat_seawater2_mod
2
3
4CONTAINS
5
6REAL   FUNCTION QSAT_SEAWATER2(knon, klon, PT,PP,PSSS)
7!$gpum horizontal knon
8
9!     ######################################
10!
11!!****  *QSATW * - function to compute saturation vapor humidity from
12!!                 temperature
13!!
14!!    PURPOSE
15!!    -------
16!       The purpose of this function is to compute the saturation vapor
17!     pressure from temperature over saline seawater
18!     
19!
20!!**  METHOD
21!!    ------
22!!       Given temperature T (PT) and salinity S (PSSS), the saturation vapor
23!!    pressure es(T,S) (FOES(PT,PSSS)) is computed following Weiss and Price
24!!    (1980).
25!!
26!!      Then, the specific humidity at saturation is deduced.
27!! 
28!!
29!!    EXTERNAL
30!!    --------
31!!      NONE
32!!
33!!    IMPLICIT ARGUMENTS
34!!    ------------------
35!!      Module MODD_CST : contains physical constants
36!!     
37!!    REFERENCE
38!!    ---------
39!!      Weiss, R.F., and Price, B.A., 1980 : Nitrous oxide solubility in water
40!!      and seawater. Marine Chemistry, nb 8, pp 347-359.
41!!
42!!
43!!    AUTHOR
44!!    ------
45!!      S. Belamari     * Meteo France *
46!!
47!!    MODIFICATIONS
48!!    -------------
49!!      Original    19/03/2014
50!-------------------------------------------------------------------------------
51!
52!*       0.    DECLARATIONS
53!              ------------
54!
55USE MODD_CSTS, ONLY : XRD, XRV
56USE indice_sol_mod
57!
58IMPLICIT NONE
59!
60!*       0.1   Declarations of arguments and results
61!
62!
63INTEGER, INTENT(IN) :: knon  ! horizontal indice compressed
64INTEGER, INTENT(IN) :: klon  ! horizontal indice (fake can be 1)
65
66REAL, DIMENSION(klon), INTENT(IN)                :: PT     ! Temperature
67                                                        ! (Kelvin)
68REAL, DIMENSION(klon), INTENT(IN)                :: PP     ! Pressure
69                                                        ! (Pascal)
70REAL, DIMENSION(klon), INTENT(IN)                :: PSSS   ! Salinity
71                                                        ! (g/kg)
72REAL, DIMENSION(SIZE(PT))                   :: PQSATA  ! saturation vapor
73                                                        ! specific humidity
74                                                        ! with respect to
75                                                        ! water (kg/kg)
76!
77!*       0.2   Declarations of local variables
78!
79REAL, DIMENSION(SIZE(PT))                   :: ZFOES  ! saturation vapor
80                                                        ! pressure
81                                                        ! (Pascal)
82!
83REAL, DIMENSION(SIZE(PT))                   :: ZWORK1
84REAL                                        :: ZWORK2
85!REAL(KIND=JPRB) :: ZHOOK_HANDLE
86!-------------------------------------------------------------------------------
87!
88!IF (LHOOK) CALL DR_HOOK('MODE_THERMOS:QSATSEAW2_1D',0,ZHOOK_HANDLE)
89!
90!*       1.    COMPUTE SATURATION VAPOR PRESSURE
91!              ---------------------------------
92!
93ZFOES(:) = EXP( 24.4543 -67.4509*(100.0/PT(:)) -4.8489*LOG(PT(:)/100.0)   &
94                -5.44E-04*(PSSS(:)/1.00472) ) !see Sharqawy et al (2010) Eq32 p368
95ZFOES(:) = ZFOES(:)*1013.25E+02             !convert from atm to Pa
96!
97ZWORK1(:) = ZFOES(:)/PP(:)
98ZWORK2    = XRD/XRV
99!
100!*       2.    COMPUTE SATURATION SPECIFIC HUMIDITY
101!              ------------------------------------
102!
103PQSATA(:) = ZWORK2*ZWORK1(:) / (1.0+(ZWORK2-1.0)*ZWORK1(:))
104!
105!IF (LHOOK) CALL DR_HOOK('MODE_THERMOS:QSATSEAW2_1D',1,ZHOOK_HANDLE)
106!-------------------------------------------------------------------------------
107!
108END FUNCTION QSAT_SEAWATER2
109!
110!-------------------------------------------------------------------------------
111
112END MODULE qsat_seawater2_mod
Note: See TracBrowser for help on using the repository browser.