source: LMDZ5/trunk/libf/phylmd/cv3_inicp.F @ 1907

Last change on this file since 1907 was 1907, checked in by lguez, 10 years ago

Added a copyright property to every file of the distribution, except
for the fcm files (which have their own copyright). Use svn propget on
a file to see the copyright. For instance:

$ svn propget copyright libf/phylmd/physiq.F90
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

Also added the files defining the CeCILL version 2 license, in French
and English, at the top of the LMDZ tree.

  • 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.8 KB
Line 
1        SUBROUTINE 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"
13c
14      INTEGER iflag_clos
15      CHARACTER (LEN=20) :: modname='cv3_inicp'
16      CHARACTER (LEN=80) :: abort_message
17c
18c --   Mixing probability distribution functions
19c
20      real Qcoef1,Qcoef2,QFF,QFFF,Qmix,Rmix,Qmix1,Rmix1,Qmix2,Rmix2,F
21      Qcoef1(F) = tanh(F/gammas)
22      Qcoef2(F) = ( tanh(F/gammas) + gammas *
23     $            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 )/
27     $           Qcoef2max
28      Rmix1(F) = ( gammas*log(cosh((QFF(F)-Fmax)/gammas))
29     1             +QFF(F)*Qcoef1max ) / Qcoef2max
30      Qmix2(F) = -Log(1.-QFFF(F))/scut
31      Rmix2(F) = (QFFF(F)+(1.-QFF(F))*Log(1.-QFFF(F)))/scut
32      Qmix(F) = qqa1*Qmix1(F) + qqa2*Qmix2(F)
33      Rmix(F) = qqa1*Rmix1(F) + qqa2*Rmix2(F)
34C
35ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
36c
37C
38C===========================================================================
39C       READ IN PARAMETERS FOR THE MIXING DISTRIBUTION
40C       AND PASS THESE THROUGH A COMMON BLOCK TO SUBROUTINE CONVECT etc.
41C       (Written by V.T.J. Phillips, 20-30/Jan/99)
42C===========================================================================
43C
44C   line 1:  a flag (0 or 1) to decide whether P(F) = 1 or the general P(F) is to be
45C         used, followed by SCUT, which is the cut-off value of F in CONVECT
46C   line 2:  blank
47C   line 3:  the coefficients for the linear combination of P(F)s to
48C                 make the general P(F)
49C   line 4:  blank
50C   line 5:  gammas, Fmax for the cosh^2 component of P(F)
51C   line 6:  blank
52C   line 7:  alphas for the 1st irrational P(F)
53C   line 8:  blank
54C   line 9:  betas  for the 2nd irrational P(F)
55C
56
57c        open(57,file='parameter_mix.data')
58
59c        read(57,*) iflag_clos
60c        read(57,*) iflag_mix, scut
61c        read(57,*)
62c        if(iflag_mix .gt. 0) then
63c             read(57,*) qqa1, qqa2
64c              read(57,*)
65c              read(57,*) gammas, Fmax
66c              read(57,*)
67c              read(57,*) alphas
68c         endif
69c        close(57)
70c
71      if(iflag_mix .gt. 0) then
72c
73c--      Normalize Pdf weights
74c
75        sumcoef=qqa1+qqa2
76        qqa1=qqa1/sumcoef
77        qqa2=qqa2/sumcoef
78c
79        Qcoef1max = Qcoef1(Fmax)
80        Qcoef2max = Qcoef2(Fmax)
81c
82        sigma = 0.
83        aire=0.0
84        pdf=0.0
85        mu=0.0
86        df = 0.0001
87c
88c        do ff = 0.0 + df, 1.0 - 2.*df, df
89         ff=df
90         dowhile ( ff .le. 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
94cc              write(*,*) pdf,  Qmix(ff), aire, ff
95         ff=ff+df
96         enddo
97c
98c         do ff=0.0+df,1.0 - 2.*df,df
99         ff=df
100         dowhile ( ff .le. 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         enddo
105         sigma = sqrt(sigma)
106c
107        if (abs(aire-1.0) .gt. 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        endif
114      endif     !  (iflag_mix .gt. 0)
115
116      RETURN
117      END
Note: See TracBrowser for help on using the repository browser.