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

Last change on this file since 1723 was 1718, checked in by emillour, 7 years ago

Venus GCM:
Add possibility to start without a startphy.nc file by setting option "startphy_file=.false." in run.def (default is obviously startphy_file=.true.).
Note that a restartphy.nc file is always generated at the end of the run.
EM

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