source: LMDZ6/branches/Amaury_dev/libf/phylmd/lmdz_alpale.f90 @ 5157

Last change on this file since 5157 was 5144, checked in by abarral, 7 weeks ago

Put YOMCST.h into modules

File size: 8.0 KB
Line 
1! Contains the alpale subroutine, as well as the old content from alpale.h
2
3MODULE lmdz_alpale
4  IMPLICIT NONE; PRIVATE
5  PUBLIC alpale
6
7  !=====================================================================
8  ! Specifique de Ale/Alp :
9  !=====================================================================
10  PUBLIC iflag_trig_bl, iflag_clos_bl, tau_trig_shallow, tau_trig_deep, iflag_strig, &
11          alp_bl_k, s_trig, h_trig, iflag_coupl, iflag_clos, iflag_wake
12  ! dans alealp_th, thermcell_alp, physiq_mod, conf_phys
13  INTEGER :: iflag_trig_bl, iflag_clos_bl, iflag_strig
14  INTEGER :: tau_trig_shallow, tau_trig_deep
15  REAL :: s_trig, h_trig
16  ! thermcell_alp et convection ...
17  INTEGER :: iflag_coupl, iflag_clos, iflag_wake
18  ! thermcell_alp
19  REAL :: alp_bl_k
20  !$OMP THREADPRIVATE(iflag_trig_bl, iflag_clos_bl, tau_trig_shallow, tau_trig_deep, iflag_strig)
21  !$OMP THREADPRIVATE(alp_bl_k, s_trig, h_trig, iflag_coupl, iflag_clos, iflag_wake)
22
23CONTAINS
24
25  SUBROUTINE alpale(debut, itap, dtime, paprs, omega, t_seri, &
26          alp_offset, it_wape_prescr, wape_prescr, fip_prescr, &
27          ale_bl_prescr, alp_bl_prescr, &
28          wake_pe, wake_fip, &
29          Ale_bl, Ale_bl_trig, Alp_bl, &
30          Ale, Alp, Ale_wake, Alp_wake)
31
32    ! **************************************************************
33    ! *
34    ! ALPALE                                                       *
35    ! *
36    ! *
37    ! written by   : Jean-Yves Grandpeix, 12/05/2016              *
38    ! modified by :                                               *
39    ! **************************************************************
40
41    USE dimphy
42    USE lmdz_ioipsl_getin_p, ONLY: getin_p
43    USE lmdz_print_control, ONLY: mydebug => debug, lunout, prt_level
44    USE phys_local_var_mod, ONLY: zw2       ! Variables internes non sauvegardees de la physique
45    USE lmdz_abort_physic, ONLY: abort_physic
46    USE lmdz_yoethf
47    USE lmdz_yomcst
48
49    IMPLICIT NONE
50
51    !================================================================
52    ! Auteur(s)   : Jean-Yves Grandpeix, 12/05/2016
53    ! Objet : Sums up all contributions to Ale and Alp
54    !================================================================
55
56    ! Input arguments
57    !----------------
58    LOGICAL, INTENT(IN) :: debut
59    INTEGER, INTENT(IN) :: itap
60    REAL, INTENT(IN) :: dtime
61    INTEGER, INTENT(IN) :: it_wape_prescr
62    REAL, INTENT(IN) :: wape_prescr, fip_prescr
63    REAL, INTENT(IN) :: Ale_bl_prescr, Alp_bl_prescr
64    REAL, INTENT(IN) :: alp_offset
65    REAL, DIMENSION(klon, klev + 1), INTENT(IN) :: paprs
66    REAL, DIMENSION(klon, klev), INTENT(IN) :: t_seri
67    REAL, DIMENSION(klon, klev), INTENT(IN) :: omega
68    REAL, DIMENSION(klon), INTENT(IN) :: wake_pe, wake_fip
69    REAL, DIMENSION(klon), INTENT(IN) :: Ale_bl, Ale_bl_trig, Alp_bl
70
71
72    ! Output arguments
73    !----------------
74    REAL, DIMENSION(klon), INTENT(OUT) :: Ale, Alp
75    REAL, DIMENSION(klon), INTENT(OUT) :: Ale_wake, Alp_wake
76
77    ! Local variables
78    !----------------
79    INTEGER :: i, k
80    REAL, DIMENSION(klon) :: www
81    REAL, SAVE :: ale_max = 1000.
82    REAL, SAVE :: alp_max = 2.
83    CHARACTER*20 modname
84    CHARACTER*80 abort_message
85
86
87    !$OMP THREADPRIVATE(ale_max,alp_max)
88
89    ! Calcul de l'energie disponible ALE (J/kg) et de la puissance
90    ! disponible ALP (W/m2) pour le soulevement des particules dans
91    ! le modele convectif
92
93    do i = 1, klon
94      ALE(i) = 0.
95      ALP(i) = 0.
96    enddo
97
98    !calcul de ale_wake et alp_wake
99    IF (iflag_wake>=1) THEN
100      IF (itap <= it_wape_prescr) THEN
101        do i = 1, klon
102          ale_wake(i) = wape_prescr
103          alp_wake(i) = fip_prescr
104        enddo
105      else
106        do i = 1, klon
107          !jyg  ALE=WAPE au lieu de ALE = 1/2 Cstar**2
108          !cc           ale_wake(i) = 0.5*wake_cstar(i)**2
109          ale_wake(i) = wake_pe(i)
110          alp_wake(i) = wake_fip(i)
111        enddo
112      endif
113    else
114      do i = 1, klon
115        ale_wake(i) = 0.
116        alp_wake(i) = 0.
117      enddo
118    endif
119    !combinaison avec ale et alp de couche limite: constantes si pas
120    !de couplage, valeurs calculees dans le thermique sinon
121    IF (iflag_coupl==0) THEN
122      IF (debut.AND.prt_level>9) &
123              WRITE(lunout, *)'ALE et ALP imposes'
124      do i = 1, klon
125        !on ne couple que ale
126        !           ALE(i) = max(ale_wake(i),Ale_bl(i))
127        ALE(i) = max(ale_wake(i), ale_bl_prescr)
128        !on ne couple que alp
129        !           ALP(i) = alp_wake(i) + Alp_bl(i)
130        ALP(i) = alp_wake(i) + alp_bl_prescr
131      enddo
132    else
133      IF(prt_level>9)WRITE(lunout, *)'ALE et ALP couples au thermique'
134      !         do i = 1,klon
135      !             ALE(i) = max(ale_wake(i),Ale_bl(i))
136      ! avant        ALP(i) = alp_wake(i) + Alp_bl(i)
137      !             ALP(i) = alp_wake(i) + Alp_bl(i) + alp_offset ! modif sb
138      !         WRITE(20,*)'ALE',ALE(i),Ale_bl(i),ale_wake(i)
139      !         WRITE(21,*)'ALP',ALP(i),Alp_bl(i),alp_wake(i)
140      !         enddo
141
142      ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
143      ! Modif FH 2010/04/27. Sans doute temporaire.
144      ! Deux options pour le alp_offset : constant si >?? 0 ou
145      ! proportionnel ??a w si <0
146      ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
147      ! Estimation d'une vitesse verticale effective pour ALP
148      IF (1==0) THEN
149        www(1:klon) = 0.
150        do k = 2, klev - 1
151          do i = 1, klon
152            www(i) = max(www(i), -omega(i, k) * RD * t_seri(i, k) &
153                    / (RG * paprs(i, k)) * zw2(i, k) * zw2(i, k))
154            ! if (paprs(i,k)>pbase(i)) THEN
155            ! calcul approche de la vitesse verticale en m/s
156            !  www(i)=max(www(i),-omega(i,k)*RD*temp(i,k)/(RG*paprs(i,k))
157            !             endif
158            !   Le 0.1 est en gros H / ps = 1e4 / 1e5
159          enddo
160        enddo
161        do i = 1, klon
162          IF (www(i)>0. .AND. ale_bl(i)>0.) www(i) = www(i) / ale_bl(i)
163        enddo
164      ENDIF
165
166      do i = 1, klon
167        ALE(i) = max(ale_wake(i), Ale_bl(i))
168        !cc nrlmd le 10/04/2012----------Stochastic triggering------------
169        IF (iflag_trig_bl>=1) THEN
170          ALE(i) = max(ale_wake(i), Ale_bl_trig(i))
171        endif
172        !cc fin nrlmd le 10/04/2012
173        IF (alp_offset>=0.) THEN
174          ALP(i) = alp_wake(i) + Alp_bl(i) + alp_offset ! modif sb
175        else
176          abort_message = 'Ne pas passer la car www non calcule'
177          CALL abort_physic (modname, abort_message, 1)
178
179          ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
180          !                                _                  _
181          ! Ajout d'une composante 3 * A * w w'2 a w'3 avec
182          ! w=www : w max sous pbase ou A est la fraction
183          ! couverte par les ascendances w' on utilise le fait
184          ! que A * w'3 = ALP et donc A * w'2 ~ ALP / sqrt(ALE)
185          ! (on ajoute 0.1 pour les singularites)
186          ALP(i) = alp_wake(i) * (1. + 3. * www(i) / (sqrt(ale_wake(i)) + 0.1)) &
187                  + alp_bl(i) * (1. + 3. * www(i) / (sqrt(ale_bl(i)) + 0.1))
188          !    ALP(i)=alp_wake(i)+Alp_bl(i)+alp_offset*min(omega(i,6),0.)
189          !             if (alp(i)<0.) THEN
190          !                PRINT*,'ALP ',alp(i),alp_wake(i) &
191          !                     ,Alp_bl(i),alp_offset*min(omega(i,6),0.)
192          !             endif
193        endif
194      enddo
195      ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
196
197    endif
198    do i = 1, klon
199      IF (alp(i)>alp_max) THEN
200        IF(prt_level>9)WRITE(lunout, *)                             &
201                'WARNING SUPER ALP (seuil=', alp_max, &
202                '): i, alp, alp_wake,ale', i, alp(i), alp_wake(i), ale(i)
203        alp(i) = alp_max
204      endif
205      IF (ale(i)>ale_max) THEN
206        IF(prt_level>9)WRITE(lunout, *)                             &
207                'WARNING SUPER ALE (seuil=', ale_max, &
208                '): i, alp, alp_wake,ale', i, ale(i), ale_wake(i), alp(i)
209        ale(i) = ale_max
210      endif
211    enddo
212
213    !fin calcul ale et alp
214    !=======================================================================
215
216    RETURN
217  END
218
219END MODULE lmdz_alpale
Note: See TracBrowser for help on using the repository browser.