source: LMDZ5/branches/LMDZ6_rc0/libf/phylmd/cv3_inicp.F90 @ 2283

Last change on this file since 2283 was 1999, checked in by Laurent Fairhead, 10 years ago

Merged trunk changes r1920:1997 into testing branch

  • 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: 3.4 KB
Line 
1SUBROUTINE cv3_inicp()
2
3  ! **************************************************************
4  ! *
5  ! CV3_INIP Lecture des choix de lois de probabilité de mélange*
6  ! et calcul de leurs coefficients normalisés.        *
7  ! *
8  ! written by   : Jean-Yves Grandpeix, 06/06/2006, 19.39.27    *
9  ! modified by :                                               *
10  ! **************************************************************
11
12  include "YOMCST2.h"
13
14  INTEGER iflag_clos
15  CHARACTER (LEN=20) :: modname = 'cv3_inicp'
16  CHARACTER (LEN=80) :: abort_message
17
18  ! --   Mixing probability distribution functions
19
20  REAL qcoef1, qcoef2, qff, qfff, qmix, rmix, qmix1, rmix1, qmix2, rmix2, f
21
22  qcoef1(f) = tanh(f/gammas)
23  qcoef2(f) = (tanh(f/gammas)+gammas*log(cosh((1.-f)/gammas)/cosh(f/gammas)))
24  qff(f) = max(min(f,1.), 0.)
25  qfff(f) = min(qff(f), scut)
26  qmix1(f) = (tanh((qff(f)-fmax)/gammas)+qcoef1max)/qcoef2max
27  rmix1(f) = (gammas*log(cosh((qff(f)-fmax)/gammas))+qff(f)*qcoef1max)/ &
28    qcoef2max
29  qmix2(f) = -log(1.-qfff(f))/scut
30  rmix2(f) = (qfff(f)+(1.-qff(f))*log(1.-qfff(f)))/scut
31  qmix(f) = qqa1*qmix1(f) + qqa2*qmix2(f)
32  rmix(f) = qqa1*rmix1(f) + qqa2*rmix2(f)
33
34  ! cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
35
36
37  ! ===========================================================================
38  ! READ IN PARAMETERS FOR THE MIXING DISTRIBUTION
39  ! AND PASS THESE THROUGH A COMMON BLOCK TO SUBROUTINE CONVECT etc.
40  ! (Written by V.T.J. Phillips, 20-30/Jan/99)
41  ! ===========================================================================
42
43  ! line 1:  a flag (0 or 1) to decide whether P(F) = 1 or the general P(F)
44  ! is to be
45  ! used, followed by SCUT, which is the cut-off value of F in CONVECT
46  ! line 2:  blank
47  ! line 3:  the coefficients for the linear combination of P(F)s to
48  ! make the general P(F)
49  ! line 4:  blank
50  ! line 5:  gammas, Fmax for the cosh^2 component of P(F)
51  ! line 6:  blank
52  ! line 7:  alphas for the 1st irrational P(F)
53  ! line 8:  blank
54  ! line 9:  betas  for the 2nd irrational P(F)
55
56
57  ! open(57,file='parameter_mix.data')
58
59  ! read(57,*) iflag_clos
60  ! read(57,*) iflag_mix, scut
61  ! read(57,*)
62  ! if(iflag_mix .gt. 0) then
63  ! read(57,*) qqa1, qqa2
64  ! read(57,*)
65  ! read(57,*) gammas, Fmax
66  ! read(57,*)
67  ! read(57,*) alphas
68  ! endif
69  ! close(57)
70
71  IF (iflag_mix>0) THEN
72
73    ! --      Normalize Pdf weights
74
75    sumcoef = qqa1 + qqa2
76    qqa1 = qqa1/sumcoef
77    qqa2 = qqa2/sumcoef
78
79    qcoef1max = qcoef1(fmax)
80    qcoef2max = qcoef2(fmax)
81
82    sigma = 0.
83    aire = 0.0
84    pdf = 0.0
85    mu = 0.0
86    df = 0.0001
87
88    ! do ff = 0.0 + df, 1.0 - 2.*df, df
89    ff = df
90    DO WHILE (ff<=1.0-2.*df)
91      pdf = (qmix(ff+df)-qmix(ff))*(1.-ff)/df
92      aire = aire + (qmix(ff+df)-qmix(ff))*(1.-ff)
93      mu = mu + pdf*ff*df
94      ! c              write(*,*) pdf,  Qmix(ff), aire, ff
95      ff = ff + df
96    END DO
97
98    ! do ff=0.0+df,1.0 - 2.*df,df
99    ff = df
100    DO WHILE (ff<=1.0-2.*df)
101      pdf = (qmix(ff+df)-qmix(ff))*(1.-ff)/df
102      sigma = sigma + pdf*(ff-mu)*(ff-mu)*df
103      ff = ff + df
104    END DO
105    sigma = sqrt(sigma)
106
107    IF (abs(aire-1.0)>0.02) THEN
108      PRINT *, 'WARNING:: AREA OF MIXING PDF IS::', aire
109      abort_message = ''
110      CALL abort_gcm(modname, abort_message, 1)
111    ELSE
112      PRINT *, 'Area, mean & std deviation are ::', aire, mu, sigma
113    END IF
114  END IF !  (iflag_mix .gt. 0)
115
116  RETURN
117END SUBROUTINE cv3_inicp
Note: See TracBrowser for help on using the repository browser.