LMDZ
PHY________INI.f90
Go to the documentation of this file.
1  subroutine phy________ini
2 
3 !------------------------------------------------------------------------------+
4 ! Sun 30-Jun-2013 MAR |
5 ! MAR PHY________INI |
6 ! subroutine PHY________INI intializes MAR PHYsical parameterizations |
7 ! |
8 ! version 3.p.4.1 created by H. Gallee, Tue 12-Mar-2013 |
9 ! Last Modification by H. Gallee, Sun 30-Jun-2013 |
10 ! |
11 !------------------------------------------------------------------------------+
12 
13  use mod_real
14  use mod_phy____dat
15  use mod_phy____grd
16  use mod_phy_rt_grd
17  use mod_phy____kkl
18 
19 
20  IMPLICIT NONE
21 
22 
23  logical :: search_argexp = .false. ! Lapack used to compute MAX/MIN exponential arguments
24  integer :: i, j, ikl !
25 
26 
27 
28 
29 !=============================================================================================!
30 ! !
31 ! include 'MARphy.inc' ! MARthusalem constants
32 ! !
33 !=============================================================================================!
34 
35 
36 !=============================================================================================!
37 ! !
38 ! Modification of Mod_PHY____dat (needed if constants slighly differ in the HOST model) !
39 ! ================================ (Here the chosen HOST model is MAR) !
40 ! !
41 ! Initialization of Mod_PHY____dat from MARphy.inc (MARphy.inc contains MARthusalem constants)!
42 ! ------------------------------------------------ !
43 ! !
44 ! zer0 = 0.0 ! [-] !
45 ! half = 0.5 ! [-] !
46 ! un_1 = 1.0 ! [-] !
47  pinmbr = acos(-1.0) ! [-] !
48 ! eps6 = epsi ! [-] !
49 ! epsn = eps9 ! [-] !
50 ! A_MolV = 1.35e-5 ! Air Viscosity 1.35e-5 [m2/s] !
51 ! rhoIce = ro_Ice ! Ice Specific Mass 920.e0 [kg/m3] !
52 ! BSnoRo = blsno ! Blown Snow Specific Mass 2.55e+2 [kg/m3] !
53 ! LhfH2O = Lf_H2O !
54 ! LhvH2O = Lv_H2O ! Latent Heat Vaporisation, Water 2.5008e+6 [J/kg] !
55 ! LhsH2O = Ls_H2O !
56 ! CpdAir = Cp ! Air Heat Capacity (p=C) 1004.708845 [J/kg/K] !
57 ! R_DAir = RDryAi ! Dry Air Perfect Gas Law C 287.05967 [J/kg/K] !
58 ! RCp = cap ! RDryAi / Cp [-] !
59 ! p0_kap = pcap !
60 ! hC_Wat = C__Wat ! H2O Heat Capacity 4186.00e0 [J/kg/K] !
61 ! rhoWat = ro_Wat
62 ! Tf_Sno = TfSnow
63 ! Tf_Sea = tfrwat
64 ! StefBo = stefan ! Stefan-Bolstzman Constant 5.67e-8 [W/m2/K4] !
65 ! Grav_F = gravit ! Gravity Acceleration 9.81e0 [m/s2] !
66 ! vonKrm = vonkar ! von Karman Constant 0.40e0 [-] !
67 ! A_Stab = A_Turb ! 5.8 [-] !
68 ! AhStab = AhTurb
69 ! AsStab = AsTurb
70 ! r_Stab = r_Turb
71 ! !
72 !=============================================================================================!
73 
74 
75 
76 ! Initialization of Mod_PHY____dat (auxiliary Constants) !
77 ! ------------------------------------------------------ !
78 
79  grav_i = 1. / grav_f ! [s2/m] !
80  gravf2 = grav_f * grav_f ! [m2/s4] !
81  rcp = r_dair / cpdair ! Case Sensitive [-] !
82  lv_cpd = lhvh2o / cpdair
83  ls_cpd = lhsh2o / cpdair
84  lc_cpd = lhfh2o / cpdair
85  vonkrm = 0.35 ! von Karman Constant, Case Sensitive !
86 
87  IF (search_argexp) THEN
88 
89 ! ***************
90  call phy_cpu_numprec
91 ! ***************
92 
93  ELSE
94 
95  ea_min =-80.
96  ea_max = 80.
97 
98  END IF
99 
100 
101 
102 
103 ! Initialization of Mod_PHY____grd
104 ! ================================
105 
106 
107 ! Correspondance entre la grille 2D horizontale dynamique et
108 ! -------------------- la grille 2D horizontale physique utile mxp,myp,mzp
109 ! ---------------------------------------------------
110  mxp = mxpp-ixp1+1 !
111  myp = mypp-jyp1+1 !
112  !kcolp = mxp * myp ! Déja calculé en amont dans physiq.F90 Martin
113  mzp = mzpp-1
114  print*, 'mxpp=',mxpp
115  print*, 'mxp=',mxp
116  print*, 'ixp1=',ixp1
117  print*, 'mypp=',mypp
118  print*, 'jyp1=',jyp1
119  print*, 'myp=',myp
120 
121 
122 ! Horizontal Cartesian Grid
123 ! -------------------------
124 
125  write(6,*) ' '
126  write(6,*) 'i_x0 , j_y0 = ' &
127  & ,i_x0 , j_y0
128 
129 
130  ! dxHOST is Model Grid Size
131  dx2inv = 0.5/dxhost ! 1 / (2 dxHOST)
132  dy2inv = 0.5/dxhost ! 1 / (2 dxHOST)
133 
134 
135 
136 
137 ! ALLOCATION
138 ! ==========
139 
140 ! ****************
141  CALL phy________alloc
142 ! ****************
143 
144 
145 
146 
147 ! Initialization of Mod_PHY____grd
148 ! ================================
149 
150 ! Initialization of the Correspondance between 2-D cartesian and vector Grid
151 ! --------------------------------------------------------------------------
152 
153 ! Adapted for MAR/LMDZ coupling:
154 
155 ! ii__AP(1)=ixp1
156 ! jj__AP(1)=jyp1
157 ! PRINT*,'jyp1=',jyp1
158 ! PRINT*,'jj__AP(1)=',jj__AP(1)
159 ! ii__AP(kcolp)=ixp1
160 ! jj__AP(kcolp)=mypp
161 !
162 ! DO i=ixp1,mxpp
163 ! DO j=jyp1+1,mypp-1
164 !
165 ! ikl = (j-(jyp1+1)) *mxpp +1 + (i-ixp1+1) ! Tout est décalé de 1 à cause du point isolé au pole dans la grille physique LMD
166 ! ! ikl = (j-jyp1) *mxpp + i-ixp1+1
167 ! ! ikl = (j-jyp1) *(mxp-1) + i-ixp1+1
168 ! ii__AP(ikl) = i
169 ! jj__AP(ikl) = j
170 ! ikl_AP(i,j) = ikl
171 ! PRINT*,'ii__AP(',ikl,')=',ii__AP(ikl)
172 ! PRINT*,'jj__AP(',ikl,')=',jj__AP(ikl)
173 ! ENDDO
174 ! ENDDO
175 
176 ! Modification Gilles Delaygue 2014/07/14 !
177  ikl=1
178  ii__ap(ikl)=ixp1
179  jj__ap(ikl)=jyp1
180  ikl_ap(:,jyp1) = ikl
181 
182  DO j=jyp1+1,mypp-1
183  DO i=ixp1,mxpp
184  ikl=ikl+1
185  ii__ap(ikl) = i
186  jj__ap(ikl) = j
187  ikl_ap(i,j) = ikl
188  ENDDO
189  ENDDO
190 
191  ikl=ikl+1
192  ii__ap(ikl)=ixp1
193  jj__ap(ikl)=mypp
194  ikl_ap(:,mypp) = ikl
195 
196 
197 
198 
199 
200  print*,'Control dans PHY_INI:'
201  print*,'ii__AP(1)=',ii__ap(1)
202  print*,'ii__AP(kcolp)=',ii__ap(kcolp)
203  print*,'jj__AP(1)=',jj__ap(1)
204  print*,'jj__AP(kcolp)=',jj__ap(kcolp)
205 
206 ! Martin control tout sauf les poles:
207  WRITE(6,600)(ii__ap(ikl),ikl=2,kcolp-1)
208  600 FORMAT (48i2)
209  WRITE(6,601)(jj__ap(ikl),ikl=2,kcolp-1)
210  601 FORMAT (48i2)
211 
212 ! DO i=ixp1,mxpp
213 ! DO j=jyp1,mypp
214 !
215 ! ikl = (j-jyp1) *mxp + i-ixp1+1
216 ! ii__AP(ikl) = i
217 ! jj__AP(ikl) = j
218 ! ikl_AP(i,j) = ikl
219 !
220 ! ENDDO
221 ! ENDDO
222 
223  ikl0 = ikl_ap(i_x0,j_y0)
224 
225 
226 
227 
228 ! Allocation of radiative transfert Variables
229 ! ===========================================
230 
231 
232 ! Initialization of Mod_PHY_RT_grd
233 ! --------------------------------
234 
235  naero = 6
236 
237 
238 ! ****************
239  CALL phy_atm_rt_alloc
240 ! ****************
241 
242 
243 
244 
245 ! Allocation of microphysical Variables
246 ! ===========================================
247 
248 ! ****************
249  CALL phy_atm_cm_alloc
250 ! ****************
251 
252 
253 
254 
255 ! Allocation of Turbulence Variables
256 ! ===========================================
257 
258 ! ****************
259  CALL phy_atm_at_alloc
260 ! ****************
261 
262 
263 
264 
265 ! Allocation of Surface Variables
266 ! ===============================
267 
268 ! ****************
269  CALL phy_sisvat_alloc
270 ! ****************
271 
272 
273 
274 
275 ! OUTPUT
276 ! ======
277 
278  OPEN(unit=4,status='unknown',file='PHY___________.OUT')
279  rewind 4
280 
281 
282 
283  end subroutine phy________ini
real(kind=real8), save cpdair
real(kind=real8), save ea_min
real(kind=real8), save gravf2
real(kind=real8), save dy2inv
subroutine phy_atm_at_alloc
integer, dimension(:), allocatable, save ii__ap
integer, save mxpp
real(kind=real8), save dxhost
real(kind=real8), save lhfh2o
subroutine phy________alloc
real(kind=real8), save pinmbr
real(kind=real8), save lc_cpd
real(kind=real8), save grav_i
subroutine phy_cpu_numprec
real(kind=real8), save vonkrm
integer, save j_y0
integer, save kcolp
integer, save ikl0
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
Definition: calcul_STDlev.h:26
subroutine phy________ini
integer, save jyp1
real(kind=real8), save lhvh2o
real(kind=real8), save dx2inv
real(kind=real8), save r_dair
real(kind=real8), save grav_f
subroutine phy_sisvat_alloc
integer, save mzpp
subroutine phy_atm_cm_alloc
real(kind=real8), save rcp
integer, save i_x0
integer, save mzp
integer, save naero
integer, save ixp1
real(kind=real8), save lhsh2o
integer, save mxp
subroutine phy_atm_rt_alloc
integer, save myp
!$Header!integer nvarmx s s unit
Definition: gradsdef.h:20
real(kind=real8), save ls_cpd
integer, dimension(:), allocatable, save jj__ap
real(kind=real8), save ea_max
integer, save mypp
integer, dimension(:,:), allocatable, save ikl_ap
real(kind=real8), save lv_cpd