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

Last change on this file since 1661 was 1621, checked in by emillour, 8 years ago

Further work on full dynamics/physics separation.

LMDZ.COMMON:

  • added phy_common/vertical_layers_mod.F90 to store information on vertical grid. This is where routines in the physics should get the information.
  • The contents of vertical_layers_mod intialized via dynphy_lonlat/inigeomphy_mod.F90.

LMDZ.MARS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • created an "ini_tracer_mod" routine in module "tracer_mod" for a cleaner initialization of the later.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.GENERIC:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added nqtot to tracer_h.F90.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.VENUS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics. Initialized via iniphysiq. IMPORTANT: there are some hard-coded constants! These should match what is in cpdet_mod.F90 in the dynamics.
  • got rid of references to moyzon_mod module within the physics. The required variables (tmoy, plevmoy) are passed to the physics as arguments to physiq.

LMDZ.TITAN:

  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics.
  • Extra work required to completely decouple physics and dynamics: moyzon_mod should be cleaned up and information passed from dynamics to physics as as arguments. Likewise moyzon_ch and moyzon_mu should not be queried from logic_mod (which is in the dynamics).

EM

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