source: dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cv3_inip.F90 @ 3983

Last change on this file since 3983 was 3831, checked in by ymipsl, 10 years ago

module reorganisation for a cleaner dyn-phys interface
YM

File size: 4.3 KB
Line 
1SUBROUTINE cv3_inip()
2  ! *******************************************************************
3  ! *                                                                  *
4  ! CV3_INIP Input = choice of mixing probability laws                 *
5  !          Output = normalized coefficients of the probability laws. *
6  ! *                                                                  *
7  ! written by   : Jean-Yves Grandpeix, 06/06/2006, 19.39.27           *
8  ! modified by :                                                      *
9  ! *******************************************************************
10!
11!----------------------------------------------
12!  INPUT (from Common YOMCST2 in "YOMCST2.h") :
13! iflag_mix
14! gammas   
15! alphas
16! betas
17! Fmax
18! scut
19!
20!----------------------------------------------
21!  INPUT/OUTPUT (from and to Common YOMCST2 in "YOMCST2.h") :
22! qqa1
23! qqa2
24!
25!----------------------------------------------
26!  OUTPUT (to Common YOMCST2 in "YOMCST2.h") :
27! Qcoef1max
28! Qcoef2max
29!
30!----------------------------------------------
31  USE print_control_mod, ONLY: prt_level, lunout
32  IMPLICIT NONE
33
34  include "YOMCST2.h"
35
36!----------------------------------------------
37! Local variables :
38   CHARACTER (LEN=20) :: modname = 'cv3_inip'
39   CHARACTER (LEN=80) :: abort_message
40
41   REAL               :: sumcoef
42   REAL               :: sigma, aire, pdf, mu, df
43   REAL               :: ff
44
45
46  ! --   Mixing probability distribution functions
47
48  REAL qcoef1, qcoef2, qff, qfff, qmix, rmix, qmix1, rmix1, qmix2, rmix2, f
49
50  qcoef1(f) = tanh(f/gammas)
51  qcoef2(f) = (tanh(f/gammas)+gammas*log(cosh((1.-f)/gammas)/cosh(f/gammas)))
52  qff(f) = max(min(f,1.), 0.)
53  qfff(f) = min(qff(f), scut)
54  qmix1(f) = (tanh((qff(f)-fmax)/gammas)+qcoef1max)/qcoef2max
55  rmix1(f) = (gammas*log(cosh((qff(f)-fmax)/gammas))+qff(f)*qcoef1max)/ &
56    qcoef2max
57  qmix2(f) = -log(1.-qfff(f))/scut
58  rmix2(f) = (qfff(f)+(1.-qff(f))*log(1.-qfff(f)))/scut
59  qmix(f) = qqa1*qmix1(f) + qqa2*qmix2(f)
60  rmix(f) = qqa1*rmix1(f) + qqa2*rmix2(f)
61
62  ! cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
63
64
65  ! ===========================================================================
66  ! READ IN PARAMETERS FOR THE MIXING DISTRIBUTION
67  ! AND PASS THESE THROUGH A COMMON BLOCK TO SUBROUTINE CONVECT etc.
68  ! (Written by V.T.J. Phillips, 20-30/Jan/99)
69  ! ===========================================================================
70
71  ! line 1:  a flag (0 or 1) to decide whether P(F) = 1 or the general P(F)
72  ! is to be
73  ! used, followed by SCUT, which is the cut-off value of F in CONVECT
74  ! line 2:  blank
75  ! line 3:  the coefficients for the linear combination of P(F)s to
76  ! make the general P(F)
77  ! line 4:  blank
78  ! line 5:  gammas, Fmax for the cosh^2 component of P(F)
79  ! line 6:  blank
80  ! line 7:  alphas for the 1st irrational P(F)
81  ! line 8:  blank
82  ! line 9:  betas  for the 2nd irrational P(F)
83
84
85  ! c$$$        open(57,file='parameter_mix.data')
86  ! c$$$
87  ! c$$$        read(57,*) iflag_mix, scut
88  ! c$$$        read(57,*)
89  ! c$$$        if(iflag_mix .gt. 0) then
90  ! c$$$              read(57,*) qqa1, qqa2
91  ! c$$$              read(57,*)
92  ! c$$$              read(57,*) gammas, Fmax
93  ! c$$$              read(57,*)
94  ! c$$$              read(57,*) alphas
95  ! c$$$         endif
96  ! c$$$         close(57)
97
98
99  IF (iflag_mix>0) THEN
100
101    ! --      Normalize Pdf weights
102
103    sumcoef = qqa1 + qqa2
104    qqa1 = qqa1/sumcoef
105    qqa2 = qqa2/sumcoef
106
107    qcoef1max = qcoef1(fmax)
108    qcoef2max = qcoef2(fmax)
109
110    sigma = 0.
111    aire = 0.0
112    pdf = 0.0
113    mu = 0.0
114    df = 0.0001
115
116    ! do ff = 0.0 + df, 1.0 - 2.*df, df
117    ff = df
118    DO WHILE (ff<=1.0-2.*df)
119      pdf = (qmix(ff+df)-qmix(ff))*(1.-ff)/df
120      aire = aire + (qmix(ff+df)-qmix(ff))*(1.-ff)
121      mu = mu + pdf*ff*df
122      IF (prt_level>9) WRITE (lunout, *) pdf, qmix(ff), aire, ff
123      ff = ff + df
124    END DO
125
126    ! do ff=0.0+df,1.0 - 2.*df,df
127    ff = df
128    DO WHILE (ff<=1.0-2.*df)
129      pdf = (qmix(ff+df)-qmix(ff))*(1.-ff)/df
130      sigma = sigma + pdf*(ff-mu)*(ff-mu)*df
131      ff = ff + df
132    END DO
133    sigma = sqrt(sigma)
134
135    IF (abs(aire-1.0)>0.02) THEN
136      WRITE (lunout, *) 'WARNING:: AREA OF MIXING PDF IS::', aire
137      abort_message = ''
138      CALL abort_physic(modname, abort_message, 1)
139    ELSE
140      PRINT *, 'Area, mean & std deviation are ::', aire, mu, sigma
141    END IF
142  END IF !  (iflag_mix .gt. 0)
143
144  RETURN
145END SUBROUTINE cv3_inip
Note: See TracBrowser for help on using the repository browser.