source: LMDZ6/branches/IPSLCM6.0.15/libf/phymar/PHY_Atm_AT_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.0 KB
Line 
1      subroutine PHY_Atm_AT_INI(FlagAT_TKE,TypeAT)
2
3!------------------------------------------------------------------------------+
4!                                                         Sat 29-Jun-2013  MAR |
5!   MAR          PHY_Atm_AT_INI                                                |
6!     subroutine PHY_Atm_AT_INI intializes Turbulent Vertical Diffusion Scheme |
7!                                                                              |
8!     version 3.p.4.1 created by H. Gallee,               Tue 12-Mar-2013      |
9!           Last Modification by H. Gallee,               Sat 29-Jun-2013      |
10!                                                                              |
11!------------------------------------------------------------------------------+
12
13      use Mod_Real
14      use Mod_PHY____dat
15      use Mod_PHY____grd
16      use Mod_PHY_AT_ctr
17      use Mod_PHY_AT_grd
18      use Mod_PHY_AT_kkl
19
20
21
22      IMPLICIT NONE
23
24
25
26
27! Arguments
28! =========
29
30      logical                                    ::  FlagAT_TKE         !  Flag         (Turbulent Transfer, TKE-e Model: ON / OFF)
31      character(len=1)                           ::  TypeAT             !  Type         (Turbulent Transfer        Model: Choice  )
32
33
34
35
36! Local Variables
37! ===============
38
39      integer    ::    k
40!     integer    ::    i     ,j     ,ikl
41
42
43
44
45! Initialization of Mod_PHY_AT_ctr  (Atm_AT Switches
46! ================================        & Time/Space control Variables)
47
48! Atm_AT Switch
49! -------------
50
51      AT_TKE = FlagAT_TKE
52
53
54
55! E-e and K-l models parameters
56! -----------------------------
57
58        Ee_Duynkerke = .FALSE.                                          ! Dunkerke           (1988) E-epsilon model of turbulence
59        Ee_Kitada    = .FALSE.                                          ! Kitada             (1987) E-epsilon model of turbulence
60        Ee_HuangRamn = .FALSE.                                          ! Huang and Raman    (1991) E-epsilon model of turbulence
61        Kl_TherryLac = .FALSE.                                          ! Therry & Lacarrere (1983) K-l       model of turbulence
62
63      IF      (TypeAT.EQ.'e')                                       THEN!
64        Ee_Duynkerke =  .TRUE.                                          ! Dunkerke           (1988) E-epsilon model of turbulence
65      ELSE IF (TypeAT.EQ.'K')                                       THEN!
66        Ee_Kitada    =  .TRUE.                                          ! Kitada             (1987) E-epsilon model of turbulence
67      ELSE IF (TypeAT.EQ.'H')                                       THEN!
68        Ee_HuangRamn =  .TRUE.                                          ! Huang and Raman    (1991) E-epsilon model of turbulence
69      ELSE IF (TypeAT.EQ.'L')                                       THEN!
70        Kl_TherryLac =  .TRUE.                                          ! Therry & Lacarrere (1983) K-l       model of turbulence
71      ELSE
72            write(6,*)
73            write(6,*) ' TypeAT = ',TypeAT,' is inadequate'
74            write(6,*) ' Please Choose e (Duynkerke)  ,    K (Kitada)                           '
75            write(6,*) '               H (Huang Raman), OR L (Therry-Lacarrere) Turbulence Model'
76            write(6,*) '                                                    '
77
78!                **************
79            call MAR________BUG
80!                **************
81
82      END IF
83
84
85
86
87! Initialisation of the TKE Scheme
88! ================================
89
90!                **************
91          CALL   PHY_genTKE_INI
92!                **************
93
94
95
96
97! Initialisation of the Tri-Diagonal Matrix
98! =========================================
99
100        alphAT    =   0.25
101        betaAT    =   1.00 - alphAT
102        a_b_AT    =          alphAT / betaAT
103
104        Ac0_AT(mzp) = - dt__AT *Grav_F *Grav_F *betaAT    /(dsigmi(mzp) * dsigma(mzp))
105      DO k=    mzp-1,1,-1
106        Ac0_AT(k)   = - dt__AT *Grav_F *Grav_F *betaAT    /(dsigmi(k)   * dsigma(k))
107        Cc0_AT(k+1) =   Ac0_AT(k)                          *dsigmi(k)   / dsigmi(k+1)
108      ENDDO
109
110
111
112      end subroutine PHY_Atm_AT_INI
Note: See TracBrowser for help on using the repository browser.