source: LMDZ6/branches/Amaury_dev/libf/phylmd/lmdz_cv3_inip.f90 @ 5159

Last change on this file since 5159 was 5158, checked in by abarral, 7 weeks ago

Add missing klon on strataer_emiss_mod.F90
Correct various missing explicit declarations
Replace tabs by spaces (tabs are not part of the fortran charset)
Continue cleaning modules
Removed unused arguments and variables

  • 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.2 KB
Line 
1MODULE lmdz_cv3_inip
2  IMPLICIT NONE; PRIVATE
3  PUBLIC cv3_inip
4CONTAINS
5  SUBROUTINE cv3_inip
6    ! *******************************************************************
7    ! *                                                                  *
8    ! CV3_INIP Input = choice of mixing probability laws                 *
9    !          Output = normalized coefficients of the probability laws. *
10    ! *                                                                  *
11    ! written by   : Jean-Yves Grandpeix, 06/06/2006, 19.39.27           *
12    ! modified by :                                                      *
13    ! *******************************************************************
14
15    USE lmdz_print_control, ONLY: prt_level, lunout
16    USE lmdz_abort_physic, ONLY: abort_physic
17    ! IN: iflag_mix, gammas , alphas, betas, Fmax, scut, INOUT: qqa1 qqa2, OUT: Qcoef1max, Qcoef1max
18    USE lmdz_yomcst2, ONLY: iflag_mix, gammas, alphas, betas, Fmax, scut, qqa1, qqa2, Qcoef1max, Qcoef2max
19
20    IMPLICIT NONE
21
22    !----------------------------------------------
23    ! Local variables :
24    CHARACTER (LEN = 20) :: modname = 'cv3_inip'
25    CHARACTER (LEN = 80) :: abort_message
26
27    REAL :: sumcoef
28    REAL :: sigma, aire, pdf, mu, df
29    REAL :: ff
30
31    ! --   Mixing probability distribution functions
32
33    REAL qcoef1, qcoef2, qff, qfff, qmix, rmix, qmix1, rmix1, qmix2, rmix2, f
34
35    qcoef1(f) = tanh(f / gammas)
36    qcoef2(f) = (tanh(f / gammas) + gammas * log(cosh((1. - f) / gammas) / cosh(f / gammas)))
37    qff(f) = max(min(f, 1.), 0.)
38    qfff(f) = min(qff(f), scut)
39    qmix1(f) = (tanh((qff(f) - fmax) / gammas) + qcoef1max) / qcoef2max
40    rmix1(f) = (gammas * log(cosh((qff(f) - fmax) / gammas)) + qff(f) * qcoef1max) / &
41            qcoef2max
42    qmix2(f) = -log(1. - qfff(f)) / scut
43    rmix2(f) = (qfff(f) + (1. - qff(f)) * log(1. - qfff(f))) / scut
44    qmix(f) = qqa1 * qmix1(f) + qqa2 * qmix2(f)
45    rmix(f) = qqa1 * rmix1(f) + qqa2 * rmix2(f)
46
47    IF (iflag_mix>0) THEN
48
49      ! --      Normalize Pdf weights
50      sumcoef = qqa1 + qqa2
51      qqa1 = qqa1 / sumcoef
52      qqa2 = qqa2 / sumcoef
53
54      qcoef1max = qcoef1(fmax)
55      qcoef2max = qcoef2(fmax)
56
57      sigma = 0.
58      aire = 0.0
59      pdf = 0.0
60      mu = 0.0
61      df = 0.0001
62
63      ! do ff = 0.0 + df, 1.0 - 2.*df, df
64      ff = df
65      DO WHILE (ff<=1.0 - 2. * df)
66        pdf = (qmix(ff + df) - qmix(ff)) * (1. - ff) / df
67        aire = aire + (qmix(ff + df) - qmix(ff)) * (1. - ff)
68        mu = mu + pdf * ff * df
69        IF (prt_level>9) WRITE (lunout, *) pdf, qmix(ff), aire, ff
70        ff = ff + df
71      END DO
72
73      ! do ff=0.0+df,1.0 - 2.*df,df
74      ff = df
75      DO WHILE (ff<=1.0 - 2. * df)
76        pdf = (qmix(ff + df) - qmix(ff)) * (1. - ff) / df
77        sigma = sigma + pdf * (ff - mu) * (ff - mu) * df
78        ff = ff + df
79      END DO
80      sigma = sqrt(sigma)
81
82      IF (abs(aire - 1.0)>0.02) THEN
83        WRITE (lunout, *) 'WARNING:: AREA OF MIXING PDF IS::', aire
84        abort_message = ''
85        CALL abort_physic(modname, abort_message, 1)
86      ELSE
87        PRINT *, 'Area, mean & std deviation are ::', aire, mu, sigma
88      END IF
89    END IF !  (iflag_mix .gt. 0)
90
91  END SUBROUTINE cv3_inip
92END MODULE lmdz_cv3_inip
Note: See TracBrowser for help on using the repository browser.