source: trunk/LMDZ.VENUS/libf/phyvenus/phyetat0.F90 @ 3461

Last change on this file since 3461 was 3451, checked in by emillour, 7 weeks ago

Venus PCM:
Add "Age of Air" scheme from Maureen Cohen.
Activated with flag "ok_aoa=y" and requires that there is also
an "aoa" tracer in traceur.def
MC

File size: 11.0 KB
Line 
1!
2! $Id $
3!
4subroutine phyetat0(fichnom)
5! Load initial state for the physics
6! and do some resulting initializations
7
8      USE dimphy
9      USE mod_grid_phy_lmdz
10      USE mod_phys_lmdz_para
11      USE iophy
12      USE phys_state_var_mod
13      USE iostart
14      use geometry_mod, only: longitude_deg, latitude_deg
15      USE time_phylmdz_mod, only: itau_phy, raz_date, pdtphys
16      USE ioipsl_getin_p_mod, only: getin_p
17  use nonoro_gwd_ran_mod, only: du_nonoro_gwd, dv_nonoro_gwd, &
18                                east_gwstress, west_gwstress
19
20implicit none
21!======================================================================
22! Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818
23! Objet: Lecture de l'etat initial pour la physique
24!======================================================================
25!include "netcdf.inc"
26include "dimsoil.h"
27include "clesphys.h"
28include "tabcontrol.h"
29!======================================================================
30
31character(len=*),intent(in) :: fichnom ! input file name
32LOGICAL :: found
33REAL    :: tab_cntrl(length)
34integer :: i,isoil
35CHARACTER(len=2) :: str2
36REAL :: lon_startphy(klon), lat_startphy(klon)
37REAL :: surface_albedo
38
39! les variables globales lues dans le fichier restart
40
41! open physics initial state file:
42if (startphy_file) then
43  call open_startphy(fichnom)
44endif
45
46!
47! Load control parameters:
48!
49IF (startphy_file) THEN
50  CALL get_var("controle",tab_cntrl,found)
51  IF (.not.found) THEN
52    PRINT*, 'phyetat0: Le champ <controle> est absent'
53    CALL abort
54  ENDIF
55       
56  DO i = 1, length
57    tabcntr0( i ) = tab_cntrl( i )
58  ENDDO
59
60  dtime        = tab_cntrl(1)
61  radpas       = tab_cntrl(2)
62
63  itau_phy = tab_cntrl(15)
64
65! Attention si raz_date est active :
66! il faut remettre a zero itau_phy apres phyetat0 !
67  IF (raz_date.eq.1) THEN
68    itau_phy=0
69  ENDIF
70
71ELSE
72  tabcntr0(:)=1 ! dummy initialization
73  ! Initialize parameter or get values from def files
74  dtime=pdtphys
75  radpas=1
76  itau_phy=0
77ENDIF ! of IF (startphy_file)
78
79IF (startphy_file) THEN
80  ! read latitudes and make a sanity check (because already known from dyn)
81  call get_field("latitude",lat_startphy,found)
82  IF (.not.found) THEN
83    PRINT*, 'phyetat0: Le champ <latitude> est absent'
84    CALL abort
85  ENDIF
86  DO i=1,klon
87    IF (ABS(lat_startphy(i)-latitude_deg(i))>=0.01) THEN
88      WRITE(*,*) "phyetat0: Warning! Latitude discrepancy wrt startphy file:",&
89                 " i=",i," lat_startphy(i)=",lat_startphy(i),&
90                 " latitude_deg(i)=",latitude_deg(i)
91      CALL abort
92    ENDIF
93  ENDDO
94
95  ! read longitudes and make a sanity check (because already known from dyn)
96  call get_field("longitude",lon_startphy,found)
97  IF (.not.found) THEN
98    PRINT*, 'phyetat0: Le champ <longitude> est absent'
99    CALL abort
100  ENDIF
101  DO i=1,klon
102    IF (ABS(lon_startphy(i)-longitude_deg(i))>=0.01) THEN
103      WRITE(*,*) "phyetat0: Warning! Longitude discrepancy wrt startphy file:",&
104                 " i=",i," lon_startphy(i)=",lon_startphy(i),&
105                 " longitude_deg(i)=",longitude_deg(i)
106      CALL abort
107    ENDIF
108  ENDDO
109ENDIF ! of IF (startphy_file)
110
111! read in other variables here ...
112
113IF (startphy_file) THEN
114  ! Load surface temperature:
115  CALL get_field("TS",ftsol(:),found)
116  IF (.not.found) THEN
117    PRINT*, 'phyetat0: Le champ <TS> est absent'
118    PRINT*, "phyetat0: Lecture echouee pour <TS>"
119    CALL abort
120  ELSE
121    PRINT*, 'phyetat0: Le champ <TS> est present'
122    PRINT*,'Temperature du sol <TS>', minval(ftsol), maxval(ftsol)
123  ENDIF
124ELSE
125  ! Dummy initialization, but in fact this is later handled in physiq
126  ftsol(:)=0
127ENDIF ! of IF (startphy_file)
128
129IF (startphy_file) THEN
130  ! Load sub-surface temperatures:
131  DO isoil=1, nsoilmx
132    IF (isoil.GT.99) THEN
133       PRINT*, "Trop de couches"
134       CALL abort
135    ENDIF
136    WRITE(str2,'(i2.2)') isoil
137    CALL get_field('Tsoil'//str2,ftsoil(:,isoil),found)
138    IF (.not.found) THEN
139      PRINT*, "phyetat0: Le champ <Tsoil"//str2//"> est absent"
140      PRINT*, "          Il prend donc la valeur de surface"
141      DO i=1, klon
142             ftsoil(i,isoil)=ftsol(i)
143      ENDDO
144    ENDIF
145  ENDDO
146ELSE
147  ! Dummy initialization, but in fact this is later handled in physiq
148  ftsoil(:,:)=0
149ENDIF ! of IF (startphy_file)
150
151IF (startphy_file) THEN
152  ! Load surface albedo:
153  CALL get_field("ALBE", falbe,found)
154  IF (.not.found) THEN
155    PRINT*, 'phyetat0: Le champ <ALBE> est absent'
156    PRINT*, "phyetat0: Lecture echouee pour <ALBE>"
157    CALL abort
158  ENDIF
159ELSE
160  ! Dummy initialization: read value from def file
161  surface_albedo=0.5 ! default
162  CALL getin_p("surface_albedo",surface_albedo)
163  falbe(:)=surface_albedo
164ENDIF ! of IF (startphy_file)
165PRINT*,'Albedo du sol <ALBE>', minval(falbe), maxval(falbe)
166
167IF (startphy_file) THEN
168  ! Lecture rayonnement solaire au sol:
169  CALL get_field("solsw",solsw,found)
170  IF (.not.found) THEN
171    PRINT*, 'phyetat0: Le champ <solsw> est absent'
172    PRINT*, 'mis a zero'
173    solsw = 0.
174  ENDIF
175ELSE
176  ! Dummy initialization
177  solsw(:)=0
178ENDIF ! of IF (startphy_file)
179PRINT*,'Rayonnement solaire au sol solsw:', minval(solsw), maxval(solsw)
180
181IF (startphy_file) THEN
182  ! Lecture rayonnement IR au sol:
183  CALL get_field("sollw",sollw,found)
184  IF (.not.found) THEN
185    PRINT*, 'phyetat0: Le champ <sollw> est absent'
186    PRINT*, 'mis a zero'
187    sollw = 0.
188  ENDIF
189ELSE
190  ! Dummy initialization
191  sollw(:)=0
192ENDIF ! of IF (startphy_file)
193PRINT*,'Rayonnement IR au sol sollw:', minval(sollw), maxval(solsw)
194
195IF (startphy_file) THEN
196  ! Lecture derive des flux:
197  CALL get_field("fder",fder,found)
198  IF (.not.found) THEN
199    PRINT*, 'phyetat0: Le champ <fder> est absent'
200    PRINT*, 'mis a zero'
201    fder = 0.
202  ENDIF
203ELSE
204  ! Dummy initialization
205  fder(:)=0
206ENDIF ! of IF (startphy_file)
207PRINT*,'Derive des flux fder:', minval(fder), maxval(fder)
208
209IF (startphy_file) THEN
210  ! Lecture derive flux IR:
211  CALL get_field("dlw",dlw,found)
212  IF (.not.found) THEN
213    PRINT*, 'phyetat0: Le champ <dlw> est absent'
214    PRINT*, 'mis a zero'
215    dlw = 0.
216  ENDIF
217ELSE
218  ! Dummy initialization
219  dlw(:)=0
220ENDIF ! of IF (startphy_file)
221PRINT*,'Derive flux IR dlw:', minval(dlw), maxval(dlw)
222
223IF (startphy_file) THEN
224  ! Lecture rayonnement IR vers le bas au sol:
225  CALL get_field("sollwdown",sollwdown,found)
226  IF (.not.found) THEN
227    PRINT*, 'phyetat0: Le champ <sollwdown> est absent'
228    PRINT*, 'mis a zero'
229    sollwdown = 0.
230  ENDIF
231ELSE
232  ! Dummy initialization
233  sollwdown(:)=0
234ENDIF ! of IF (startphy_file)
235PRINT*,'Flux IR vers le bas au sol sollwdown:', minval(sollwdown), maxval(sollwdown)
236
237IF (startphy_file) THEN
238  ! Lecture du rayonnement net au sol:
239  CALL get_field("RADS",radsol,found)
240  IF (.not.found) THEN
241    PRINT*, 'phyetat0: Le champ <RADS> est absent'
242    CALL abort
243  ENDIF
244ELSE
245  ! Dummy initialization
246  radsol(:)=0
247ENDIF ! of IF (startphy_file)
248PRINT*,'Rayonnement net au sol radsol:', minval(radsol), maxval(radsol)
249
250IF (startphy_file) THEN
251  ! Load sub-grid scale orography parameters:
252  CALL get_field("ZMEA",zmea,found)
253  IF (.not.found) THEN
254    PRINT*, 'phyetat0: Le champ <ZMEA> est absent'
255    PRINT*, 'mis a zero'
256    zmea=0.
257  ENDIF
258ELSE
259  zmea(:)=0
260ENDIF ! of IF (startphy_file)
261PRINT*,'OROGRAPHIE SOUS-MAILLE zmea:', minval(zmea), maxval(zmea)
262
263IF (startphy_file) THEN
264  ! Load sub-grid scale orography parameters:
265  CALL get_field("ZSTD",zstd,found)
266  IF (.not.found) THEN
267    PRINT*, 'phyetat0: Le champ <ZSTD> est absent'
268    PRINT*, 'mis a zero'
269    zstd=0.
270  ENDIF
271ELSE
272  zstd(:)=0
273ENDIF ! of IF (startphy_file)
274PRINT*,'OROGRAPHIE SOUS-MAILLE zstd:', minval(zstd), maxval(zstd)
275
276IF (startphy_file) THEN
277  ! Load sub-grid scale orography parameters:
278  CALL get_field("ZSIG",zsig,found)
279  IF (.not.found) THEN
280    PRINT*, 'phyetat0: Le champ <ZSIG> est absent'
281    PRINT*, 'mis a zero'
282    zsig=0.
283  ENDIF
284ELSE
285  zsig(:)=0
286ENDIF ! of IF (startphy_file)
287PRINT*,'OROGRAPHIE SOUS-MAILLE zsig:', minval(zsig), maxval(zsig)
288
289IF (startphy_file) THEN
290  ! Load sub-grid scale orography parameters:
291  CALL get_field("ZGAM",zgam,found)
292  IF (.not.found) THEN
293    PRINT*, 'phyetat0: Le champ <ZGAM> est absent'
294    PRINT*, 'mis a zero'
295    zgam=0.
296  ENDIF
297ELSE
298  zgam(:)=0
299ENDIF ! of IF (startphy_file)
300PRINT*,'OROGRAPHIE SOUS-MAILLE zgam:', minval(zgam), maxval(zgam)
301
302IF (startphy_file) THEN
303  ! Load sub-grid scale orography parameters:
304  CALL get_field("ZTHE",zthe,found)
305  IF (.not.found) THEN
306    PRINT*, 'phyetat0: Le champ <ZTHE> est absent'
307    PRINT*, 'mis a zero'
308    zthe=0.
309  ENDIF
310ELSE
311  zthe(:)=0
312ENDIF ! of IF (startphy_file)
313PRINT*,'OROGRAPHIE SOUS-MAILLE zthe:', minval(zthe), maxval(zthe)
314
315IF (startphy_file) THEN
316  ! Load sub-grid scale orography parameters:
317  CALL get_field("ZPIC",zpic,found)
318  IF (.not.found) THEN
319    PRINT*, 'phyetat0: Le champ <ZPIC> est absent'
320    PRINT*, 'mis a zero'
321    zpic=0.
322  ENDIF
323ELSE
324  zpic(:)=0
325ENDIF ! of IF (startphy_file)
326PRINT*,'OROGRAPHIE SOUS-MAILLE zpic:', minval(zpic), maxval(zpic)
327
328IF (startphy_file) THEN
329  ! Load sub-grid scale orography parameters:
330  CALL get_field("ZVAL",zval,found)
331  IF (.not.found) THEN
332    PRINT*, 'phyetat0: Le champ <ZVAL> est absent'
333    PRINT*, 'mis a zero'
334    zval=0.
335  ENDIF
336ELSE
337  zval(:)=0
338ENDIF ! of IF (startphy_file)
339PRINT*,'OROGRAPHIE SOUS-MAILLE zval:', minval(zval), maxval(zval)
340
341IF (startphy_file) THEN
342  ! Lecture de TANCIEN:
343  ancien_ok = .TRUE.
344
345  CALL get_field("TANCIEN",t_ancien,found)
346  IF (.not.found) THEN
347    PRINT*, "phyetat0: Le champ <TANCIEN> est absent"
348    PRINT*, "Depart legerement fausse. Mais je continue"
349    ancien_ok = .FALSE.
350  ENDIF
351ELSE
352  ancien_ok=.false.
353ENDIF
354
355IF (startphy_file) THEN
356  CALL get_field("age",age,found)
357  IF (.not.found) THEN
358    PRINT*, "phyetat0: Age of air is missing"
359    PRINT*, "Reinitialising age of air to 0"
360    age(:,:) = 0.
361  ENDIF
362ELSE
363  age(:,:) = 0.
364ENDIF
365
366IF (startphy_file) THEN
367  ! Load Q2 the TKE at interlayer:
368  CALL get_field("Q2",q2,found)
369  IF (.not.found) THEN
370    PRINT*, 'phyetat0: Le champ <Q2> est absent'
371    PRINT*, 'mis a zero'
372    q2(:,:)=0.
373  ENDIF
374ELSE
375  ! Dummy initialization
376  q2(:,:)=0
377ENDIF ! of IF (startphy_file)
378PRINT*,'Turbulent Kinetic Energy', minval(q2), maxval(q2)
379
380! Non-orographic gravity waves
381if (startphy_file) then
382   call get_field("du_nonoro_gwd",du_nonoro_gwd,found)
383   if (.not.found) then
384      write(*,*) "phyetat0: <du_nonoro_gwd> not in file"
385      du_nonoro_gwd(:,:)=0.
386   endif
387endif ! of if (startphy_file)
388if (startphy_file) then
389   call get_field("dv_nonoro_gwd",dv_nonoro_gwd,found)
390   if (.not.found) then
391      write(*,*) "phyetat0: <dv_nonoro_gwd> not in file"
392      dv_nonoro_gwd(:,:)=0.
393   endif
394endif ! of if (startphy_file)
395if (startphy_file) then
396   call get_field("east_gwstress",east_gwstress,found)
397   if (.not.found) then
398      write(*,*) "phyetat0: <east_gwstress> not in file"
399      east_gwstress(:,:)=0.
400   endif
401endif ! of if (startphy_file)
402if (startphy_file) then
403   call get_field("west_gwstress",west_gwstress,found)
404   if (.not.found) then
405      write(*,*) "phyetat0: <west_gwstress> not in file"
406      west_gwstress(:,:)=0.
407   endif
408endif ! of if (startphy_file)
409
410! close file
411IF (startphy_file) call close_startphy
412
413! do some more initializations
414call init_iophy_new(latitude_deg,longitude_deg)
415
416end subroutine phyetat0
Note: See TracBrowser for help on using the repository browser.