Ignore:
Timestamp:
Jun 9, 2020, 3:29:47 PM (4 years ago)
Author:
aslmd
Message:

Cancelled commits 2350 2351 2352. Very weird behaviour of git svn dcommit where username argument does not seem to work.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/co2sat.F

    r2350 r2353  
     1      SUBROUTINE co2sat(naersize,t,p,psat)
     2c       SUBROUTINE co2sat(naersize,t,p,qsat) JA
     3      IMPLICIT NONE
     4
    15c=======================================================================
    2 c     SUBROUTINE co2sat
    3 c-----------------------------------------------------------------------
    4 c     Aim:
    5 c     ----
    6 c     Compute saturated steam pressure (from James et al, 1992)
     6c
     7c
     8c  now:  straight psat of CO2 (or qsat of CO2 but need of mmean)
     9c
    710c=======================================================================
    8       subroutine co2sat(naersize, t, psat)
    9      
    10       implicit none
    11 c-----------------------------------------------------------------------
    12 c     VARIABLES
    13 c-----------------------------------------------------------------------
    14 c     Inputs:
    15 c     -------
    16       integer, intent(in) ::
    17      &   naersize ! dimension of tables t and psat
    18      
    19       real, intent(in) ::
    20      &   t(naersize) ! temperature table
    2111
    22 c     Output:
    23 c     -------
    24       real, intent(out) ::
    25      &   psat(naersize) ! Saturated steam pressure (Pa)
     12c   declarations:
     13c   -------------
     14c   arguments:
     15c   ----------
    2616
    27 c     Local:
    28 c     ------
    29       integer ::
    30      &   i ! loop on naersize
    31 c=======================================================================
    32 c===== BEGIN
    33 c=======================================================================
    34       do i = 1, naersize
    35         psat(i) = 1.382 * 1e12 * exp(-3182.48/t(i))
    36       end do
    37 c=======================================================================
    38 c===== END
    39 c=======================================================================
     17c   INPUT
     18      integer naersize
     19      real t(naersize) , p(naersize)
     20c   OUTPUT
     21c      real qsat(naersize) JA
     22      real psat(naersize)
     23
     24c   local:
     25c   ------
     26      INTEGER i
     27      REAL r2,r3,r4 , To, es
     28      SAVE r2,r3,r4
     29      DATA r2,r3,r4/611.14,21.875,7.66/
     30      SAVE To
     31      DATA To/273.16/
     32         
     33      do i=1,naersize
     34
     35
     36c        pression de vapeur saturante (James et al. 1992):
     37
     38          psat(i)  = 1.382 * 1e12 * exp(-3182.48/t(i)) !; (Pa)
     39
     40c         OR:
     41
     42c         qsat(i) = psat/p(i)*44.01/mmean ! Need of updated information on mmean
     43c         qsat(i) = max(qsat(i), 1.e-30)
     44
     45
     46      enddo
     47c      qsat=psat JA
     48         
     49
    4050      RETURN
    4151      END
Note: See TracChangeset for help on using the changeset viewer.