source: LMDZ4/trunk/libf/phylmd/cv3_inip.F @ 961

Last change on this file since 961 was 879, checked in by Laurent Fairhead, 16 years ago

Suite de la bascule vers une physique avec thermiques, nouvelle convection, poche froide ...
LF

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 3.6 KB
Line 
1        SUBROUTINE cv3_inip(iflag_mix)
2***************************************************************
3*                                                             *
4* CV3_INIP Lecture des choix de lois de probabilité de mélange*
5*          et calcul de leurs coefficients normalisés.        *
6*                                                             *
7* written by   : Jean-Yves Grandpeix, 06/06/2006, 19.39.27    *
8* modified by :                                               *
9***************************************************************
10*
11#include "YOMCST2.h"
12c
13      INTEGER iflag_mix
14c
15c --   Mixing probability distribution functions
16c
17      real Qcoef1,Qcoef2,QFF,QFFF,Qmix,Rmix,Qmix1,Rmix1,Qmix2,Rmix2,F
18      Qcoef1(F) = tanh(F/gammas)
19      Qcoef2(F) = ( tanh(F/gammas) + gammas *
20     $            log(cosh((1.- F)/gammas)/cosh(F/gammas)))
21      QFF(F) = Max(Min(F,1.),0.)
22      QFFF(F) = Min(QFF(F),scut)
23      Qmix1(F) = ( tanh((QFF(F) - Fmax)/gammas)+Qcoef1max )/
24     $           Qcoef2max
25      Rmix1(F) = ( gammas*log(cosh((QFF(F)-Fmax)/gammas))
26     1             +QFF(F)*Qcoef1max ) / Qcoef2max
27      Qmix2(F) = -Log(1.-QFFF(F))/scut
28      Rmix2(F) = (QFFF(F)+(1.-QFF(F))*Log(1.-QFFF(F)))/scut
29      Qmix(F) = qqa1*Qmix1(F) + qqa2*Qmix2(F)
30      Rmix(F) = qqa1*Rmix1(F) + qqa2*Rmix2(F)
31C
32ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
33c
34C
35C===========================================================================
36C       READ IN PARAMETERS FOR THE MIXING DISTRIBUTION
37C       AND PASS THESE THROUGH A COMMON BLOCK TO SUBROUTINE CONVECT etc.
38C       (Written by V.T.J. Phillips, 20-30/Jan/99)
39C===========================================================================
40C
41C   line 1:  a flag (0 or 1) to decide whether P(F) = 1 or the general P(F) is to be
42C         used, followed by SCUT, which is the cut-off value of F in CONVECT
43C   line 2:  blank
44C   line 3:  the coefficients for the linear combination of P(F)s to
45C                 make the general P(F)
46C   line 4:  blank
47C   line 5:  gammas, Fmax for the cosh^2 component of P(F)
48C   line 6:  blank
49C   line 7:  alphas for the 1st irrational P(F)
50C   line 8:  blank
51C   line 9:  betas  for the 2nd irrational P(F)
52C
53
54        open(57,file='parameter_mix.data')
55
56        read(57,*) iflag_mix, scut
57        read(57,*)
58        if(iflag_mix .gt. 0) then
59              read(57,*) qqa1, qqa2
60              read(57,*)
61              read(57,*) gammas, Fmax
62              read(57,*)
63              read(57,*) alphas
64         endif
65         close(57)
66c
67      if(iflag_mix .gt. 0) then
68c
69c--      Normalize Pdf weights
70c
71        sumcoef=qqa1+qqa2
72        qqa1=qqa1/sumcoef
73        qqa2=qqa2/sumcoef
74c
75        Qcoef1max = Qcoef1(Fmax)
76        Qcoef2max = Qcoef2(Fmax)
77c
78        sigma = 0.
79        aire=0.0
80        pdf=0.0
81        mu=0.0
82        df = 0.0001
83c
84c        do ff = 0.0 + df, 1.0 - 2.*df, df
85         ff=df
86         dowhile ( ff .le. 1.0 - 2.*df )
87              pdf = (Qmix(ff+df) -  Qmix(ff)) * (1.-ff) / df
88              aire=aire+(Qmix(ff+df) - Qmix(ff)) * (1.-ff)
89              mu = mu + pdf * ff * df
90              write(*,*) pdf,  Qmix(ff), aire, ff
91         ff=ff+df
92         enddo
93c
94c         do ff=0.0+df,1.0 - 2.*df,df
95          ff=df
96          dowhile ( ff .le. 1.0 - 2.*df )
97              pdf = (Qmix(ff+df)- Qmix(ff)) * (1.-ff) / df
98              sigma = sigma+pdf*(ff - mu)*(ff - mu)*df
99         ff=ff+df
100         enddo
101         sigma = sqrt(sigma)
102c
103        if (abs(aire-1.0) .gt. 0.02) then
104            print *,'WARNING:: AREA OF MIXING PDF IS::', aire
105            stop
106        else
107            print *,'Area, mean & std deviation are ::', aire,mu,sigma
108        endif
109      endif     !  (iflag_mix .gt. 0)
110
111      RETURN
112      END
Note: See TracBrowser for help on using the repository browser.