source: LMDZ6/branches/Amaury_dev/libf/phylmd/lmdz_FCTTRE.f90 @ 5143

Last change on this file since 5143 was 5143, checked in by abarral, 8 weeks ago

Put YOEGWD.h, FCTTRE.h into modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 2.3 KB
Line 
1MODULE lmdz_fcttre
2  !     ------------------------------------------------------------------
3  !     This COMDECK includes the Thermodynamical functions for the cy39
4  !       ECMWF Physics package.
5  !       Consistent with YOMCST Basic physics constants, assuming the
6  !       partial pressure of water vapour is given by a first order
7  !       Taylor expansion of Qs(T) w.r.t. to Temperature, using constants
8  !       in YOETHF
9  !     ------------------------------------------------------------------
10
11  IMPLICIT NONE; PRIVATE
12  PUBLIC foeew, foede, qsats, qsatl, dqsats, dqsatl, thermcep
13
14  LOGICAL, PARAMETER :: thermcep = .TRUE.
15
16CONTAINS
17
18  REAL FUNCTION foeew (ptarg, pdelarg)
19    USE lmdz_YOETHF, ONLY: r3ies, r3les, r4ies, r4les
20    INCLUDE "YOMCST.h"  ! rtt
21    REAL, INTENT(IN) :: ptarg, pdelarg
22    foeew = exp ((r3les * (1. - pdelarg) + r3ies * pdelarg) * (ptarg - rtt) &
23            / (ptarg - (r4les * (1. - pdelarg) + r4ies * pdelarg)))
24  END FUNCTION foeew
25
26  REAL FUNCTION foede (ptarg, pdelarg, p5arg, pqsarg, pcoarg)
27    USE lmdz_YOETHF, ONLY: r4ies, r4les
28    REAL, INTENT(IN) :: ptarg, pdelarg, p5arg, pqsarg, pcoarg
29    foede = pqsarg * pcoarg * p5arg / (ptarg - (r4les * (1. - pdelarg) + r4ies * pdelarg))**2
30  END FUNCTION foede
31
32  REAL FUNCTION qsats(ptarg)
33    REAL, INTENT(IN) :: ptarg
34    qsats = 100.0 * 0.622 * 10.0 ** (2.07023 - 0.00320991 * ptarg - 2484.896 / ptarg + 3.56654 * log10(ptarg))
35  END FUNCTION qsats
36
37  REAL FUNCTION qsatl(ptarg)
38    REAL, INTENT(IN) :: ptarg
39    qsatl = 100.0 * 0.622 * 10.0 ** (23.8319 - 2948.964 / ptarg - 5.028 * log10(ptarg) &
40            - 29810.16 * exp(- 0.0699382 * ptarg) + 25.21935 * exp(- 2999.924 / ptarg))
41  END FUNCTION qsatl
42
43  REAL FUNCTION dqsats(ptarg, pqsarg)
44    REAL, INTENT(IN) :: ptarg, pqsarg
45    INCLUDE "YOMCST.h"  ! rlvtt, rcpd
46    dqsats = rlvtt / rcpd * pqsarg * (3.56654 / ptarg + 2484.896 * log(10.) / ptarg**2 - 0.00320991 * log(10.))
47  END FUNCTION dqsats
48
49  REAL FUNCTION dqsatl(ptarg, pqsarg)
50    REAL, INTENT(IN) :: ptarg, pqsarg
51    INCLUDE "YOMCST.h"  ! rlvtt, rcpd
52    dqsatl = rlvtt / rcpd * pqsarg * log(10.) * (2948.964 / ptarg**2 - 5.028 / log(10.) / ptarg &
53            + 25.21935 * 2999.924 / ptarg**2 * exp(-2999.924 / ptarg) + &
54            29810.16 * 0.0699382 * exp(-0.0699382 * ptarg))
55  END FUNCTION dqsatl
56
57END MODULE lmdz_fcttre
Note: See TracBrowser for help on using the repository browser.