Ignore:
Timestamp:
Jul 31, 2024, 6:20:03 PM (3 months ago)
Author:
abarral
Message:

Revert FCTTRE to INCLUDE to assess impact of inlining

File:
1 copied

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/phylmd/FCTTRE.h

    r5144 r5153  
    1 MODULE 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 
    16 CONTAINS
    17 
    18   REAL FUNCTION foeew (ptarg, pdelarg)
    19     USE lmdz_yoethf, ONLY: r3ies, r3les, r4ies, r4les
    20     USE lmdz_yomcst, ONLY: 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     USE lmdz_yomcst, ONLY: rlvtt, rcpd
    45     REAL, INTENT(IN) :: ptarg, pqsarg
    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     USE lmdz_yomcst, ONLY: rlvtt, rcpd
    51     REAL, INTENT(IN) :: ptarg, pqsarg
    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 
    57 END MODULE lmdz_fcttre
     1!
     2! $Header$
     3!
     4!
     5!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
     6!                 veillez  n'utiliser que des ! pour les commentaires
     7!                 et  bien positionner les & des lignes de continuation
     8!                 (les placer en colonne 6 et en colonne 73)
     9!
     10!     ------------------------------------------------------------------
     11!     This COMDECK includes the Thermodynamical functions for the cy39
     12!       ECMWF Physics package.
     13!       Consistent with YOMCST Basic physics constants, assuming the
     14!       partial pressure of water vapour is given by a first order
     15!       Taylor expansion of Qs(T) w.r.t. to Temperature, using constants
     16!       in YOETHF
     17!     ------------------------------------------------------------------
     18      REAL PTARG, PDELARG, P5ARG, PQSARG, PCOARG
     19      REAL FOEEW, FOEDE, qsats, qsatl, dqsats, dqsatl
     20      LOGICAL thermcep
     21      PARAMETER (thermcep=.TRUE.)
     22!
     23      FOEEW ( PTARG,PDELARG ) = EXP (                                   &
     24     &          (R3LES*(1.-PDELARG)+R3IES*PDELARG) * (PTARG-RTT)        &
     25     & / (PTARG-(R4LES*(1.-PDELARG)+R4IES*PDELARG)) )
     26!
     27      FOEDE ( PTARG,PDELARG,P5ARG,PQSARG,PCOARG ) = PQSARG*PCOARG*P5ARG &
     28     & / (PTARG-(R4LES*(1.-PDELARG)+R4IES*PDELARG))**2
     29!
     30      qsats(ptarg) = 100.0 * 0.622 * 10.0                               &
     31     &           ** (2.07023 - 0.00320991 * ptarg                       &
     32     &           - 2484.896 / ptarg + 3.56654 * LOG10(ptarg))
     33      qsatl(ptarg) = 100.0 * 0.622 * 10.0                               &
     34     &           ** (23.8319 - 2948.964 / ptarg                         &
     35     &           - 5.028 * LOG10(ptarg)                                 &
     36     &           - 29810.16 * EXP( - 0.0699382 * ptarg)                 &
     37     &           + 25.21935 * EXP( - 2999.924 / ptarg))
     38!
     39      dqsats(ptarg,pqsarg) = RLVTT/RCPD*pqsarg * (3.56654/ptarg         &
     40     &                     +2484.896*LOG(10.)/ptarg**2                  &
     41     &                     -0.00320991*LOG(10.))
     42      dqsatl(ptarg,pqsarg) = RLVTT/RCPD*pqsarg*LOG(10.)*                &
     43     &                (2948.964/ptarg**2-5.028/LOG(10.)/ptarg           &
     44     &                +25.21935*2999.924/ptarg**2*EXP(-2999.924/ptarg)  &
     45     &                +29810.16*0.0699382*EXP(-0.0699382*ptarg))
Note: See TracChangeset for help on using the changeset viewer.