source: LMDZ6/branches/IPSLCM6.0.15/libf/phymar/PHY_Atm_CM_INI.f90 @ 3607

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

Inclusion de la physique de MAR


Integration of MAR physics

File size: 4.2 KB
Line 
1      subroutine PHY_Atm_CM_INI
2
3!------------------------------------------------------------------------------+
4!                                                         Sat 29-Jun-2013  MAR |
5!   MAR          PHY_Atm_CM_INI                                                |
6!     subroutine PHY_Atm_CM_INI initializes Cloud Microphysical Scheme CMiPhy  |
7!                                                                              |
8!     version 3.p.4.1 created by H. Gallee,               Thu 21-Mar-2013      |
9!           Last Modification by H. Gallee,               Sat 29-Jun-2013      |
10!                                                                              |
11!------------------------------------------------------------------------------+
12!                                                                              |
13!                                                                              |
14! # OPTIONS:                                                                   |
15! # ^^^^^^^                                                                    |
16! #          #kk  SCu  fraction  Limitation                                    |
17! #          #hb  Snow      particles distrib. parameter  n0___s is BSnow value|
18! #          #LA  Snow,Rain particles distrib. parameters n0___s,r        TUNED|
19! #          #rc  MAX  allowed Relative Humidity is a function of Grid Size    |
20!                                                                              |
21!------------------------------------------------------------------------------+
22
23      use Mod_Real
24      use Mod_PHY____grd
25      use Mod_PHY_CM_dat
26      use Mod_PHY_CM_kkl
27
28
29      IMPLICIT NONE
30
31      integer        ::  i     ,j     ,k     ,ikl
32
33
34
35!  DATA TUNING
36!  ===========
37
38! #kk SSImax = 900.0        ! Maximum        Sursaturation % ICE (900 ==> RH=1000%)       [%]
39! #LA n0___r = 3.0e06       ! intercept parameter / rain gamam distribution ! Tuning
40! #LA n0___s = 4.0e06       ! intercept parameter / snow gamma distribution ! Tuning
41! #hb n0___s = 0.1d18       ! intercept parameter / snow gamma distribution (Blown Snow only)
42                            ! DO NOT USE unless for specific sensivity experiments
43! #hb IF (it_EXP.eq.1) write(6,6000)
44! #hb 6000 format(/,' ****************************************************', &
45! #hb&            /,' * cnos  = 0.1d18 for PURE BLOWING SNOW EXPERIMENTS *', &
46! #hb&            /,' *             DO not USE  OTHERWISE                *', &
47! #hb&            /,' ****************************************************', &
48! #hb&            /)
49
50! _hl qisMAX = 0.0008       ! compromise when graupels are not included
51!                           ! Ref.: Emde & Kahlig 1989, Ann.Geoph.      7, p.408  (18)
52      qw_MAX = qw_MAXL      ! Cloud droplets MAX concentration before autoconversion
53                            ! Ref.: Lin et al.    1983, JCAM           22, p.1076 (50)
54!     qw_MAX = 0.0003       ! critical liquid water mixing ratio
55!                           ! Ref.: Sundqvist     1988, Physically-Based Modelling and Simulation of Climate and Climatic Change,
56!                           !                           M.E. Schlesinger, Ed., Reidel, 433-461.
57
58
59
60! Maximum Relative Humidity
61! =========================
62
63! #rc RH_MAX = 0.90+0.08*sqrt(max(0.,100.-dxHOST*0.001)/95.)
64
65
66
67
68! IOs
69! ===
70
71        DO  ipt_CM=1,npt_CM
72            ikl0CM(ipt_CM) = ikl_AP(i0__CM(ipt_CM),j0__CM(ipt_CM))
73        ENDDO
74
75
76
77
78! Cloud Microphysics Initialization
79! =================================
80
81      IF (it_EXP.LE.1)                                              THEN
82
83
84! Precipitation: Mod_PHY_CM_kkl:
85! -----------------------------
86
87          DO ikl=1,kcolp
88            rai0CM    (ikl)   = 0.
89            rainCM    (ikl)   = 0.
90            sno0CM    (ikl)   = 0.
91            snobCM    (ikl)   = 0.
92            snowCM    (ikl)   = 0.
93            Ice0CM    (ikl)   = 0.
94            Ice_CM    (ikl)   = 0.
95
96
97
98! Hyrometeores : Mod_PHY_CM_kkl:
99! -----------------------------
100
101          DO k=   1,mzp
102            CCNiCM    (ikl,k) = 0.
103            qw__CM    (ikl,k) = 0.
104            qi__CM    (ikl,k) = 0.
105            qs__CM    (ikl,k) = 0.
106! #qg       qg__CM    (ikl,k) = 0.
107            qr__CM    (ikl,k) = 0.
108          END DO
109          END DO
110
111      END IF
112
113      end subroutine PHY_Atm_CM_INI
Note: See TracBrowser for help on using the repository browser.