source: trunk/LMDZ.TITAN.old/libf/phytitan/phyetat0.F90 @ 3303

Last change on this file since 3303 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: 10.3 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: latitude_deg,longitude_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      chimpas      = tab_cntrl(3)
58      lsinit       = tab_cntrl(17)
59
60      itau_phy = tab_cntrl(15)
61
62! Attention si raz_date est active :
63! il faut remettre a zero itau_phy apres phyetat0 !
64! et verifier que lsinit est proche de 0.
65      IF (raz_date.eq.1) THEN
66        itau_phy=0
67        if ((lsinit.gt.3.).and.(lsinit.lt.357.)) then
68          PRINT*, 'phyetat0: raz_date=1 and ls different from 0.'
69          PRINT*, 'When raz_date=1, we reset the initial date'
70          PRINT*, 'to spring equinox, Ls=0., so the start files'
71          PRINT*, 'should be within a couple of degrees from Ls=0.'
72          PRINT*, 'or the circulation will be too far from equilibrium'
73          CALL abort
74        endif
75      ENDIF
76
77! read latitudes and make a sanity check (because already known from dyn)
78call get_field("latitude",lat_startphy,found)
79IF (.not.found) THEN
80  PRINT*, 'phyetat0: Le champ <latitude> est absent'
81  CALL abort
82ENDIF
83DO i=1,klon
84  IF (ABS(lat_startphy(i)-latitude_deg(i))>=0.01) THEN
85    WRITE(*,*) "phyetat0: Warning! Latitude discrepancy wrt startphy file:",&
86               " i=",i," lat_startphy(i)=",lat_startphy(i),&
87               " latitude_deg(i)=",latitude_deg(i)
88    CALL abort
89  ENDIF
90ENDDO
91
92! read longitudes and make a sanity check (because already known from dyn)
93call get_field("longitude",lon_startphy,found)
94IF (.not.found) THEN
95  PRINT*, 'phyetat0: Le champ <longitude> est absent'
96  CALL abort
97ENDIF
98DO i=1,klon
99  IF (ABS(lon_startphy(i)-longitude_deg(i))>=0.01) THEN
100    WRITE(*,*) "phyetat0: Warning! Longitude discrepancy wrt startphy file:",&
101               " i=",i," lon_startphy(i)=",lon_startphy(i),&
102               " longitude_deg(i)=",longitude_deg(i)
103    CALL abort
104  ENDIF
105ENDDO
106
107! read in other variables here ...
108
109! Lecture des temperatures du sol:
110
111       CALL get_field("TS",ftsol(:),found)
112      IF (.not.found) THEN
113         PRINT*, 'phyetat0: Le champ <TS> est absent'
114         PRINT*, "phyetat0: Lecture echouee pour <TS>"
115         CALL abort
116      ELSE
117         PRINT*, 'phyetat0: Le champ <TS> est present'
118         xmin = 1.0E+20
119         xmax = -1.0E+20
120         DO i = 1, klon
121            xmin = MIN(ftsol(i),xmin)
122            xmax = MAX(ftsol(i),xmax)
123         ENDDO
124         PRINT*,'Temperature du sol <TS>', xmin, xmax
125      ENDIF
126
127
128! Lecture des temperatures du sol profond:
129
130      DO isoil=1, nsoilmx
131      IF (isoil.GT.99) THEN
132         PRINT*, "Trop de couches"
133         CALL abort
134      ENDIF
135      WRITE(str2,'(i2.2)') isoil
136      CALL get_field('Tsoil'//str2,ftsoil(:,isoil),found)
137      IF (.not.found) THEN
138         PRINT*, "phyetat0: Le champ <Tsoil"//str2//"> est absent"
139         PRINT*, "          Il prend donc la valeur de surface"
140         DO i=1, klon
141             ftsoil(i,isoil)=ftsol(i)
142         ENDDO
143      ENDIF
144      ENDDO
145
146! Lecture de albedo au sol:
147
148      CALL get_field("ALBE", falbe,found)
149      IF (.not.found) THEN
150         PRINT*, 'phyetat0: Le champ <ALBE> est absent'
151         PRINT*, "phyetat0: Lecture echouee pour <ALBE>"
152         CALL abort
153      ELSE
154         xmin = 1.0E+20
155         xmax = -1.0E+20
156         DO i = 1, klon
157            xmin = MIN(falbe(i),xmin)
158            xmax = MAX(falbe(i),xmax)
159         ENDDO
160         PRINT*,'Albedo du sol <ALBE>', xmin, xmax
161      ENDIF
162
163! Lecture rayonnement solaire au sol:
164
165      CALL get_field("solsw",solsw,found)
166      IF (.not.found) THEN
167         PRINT*, 'phyetat0: Le champ <solsw> est absent'
168         PRINT*, 'mis a zero'
169         solsw = 0.
170      ENDIF
171      xmin = 1.0E+20
172      xmax = -1.0E+20
173      DO i = 1, klon
174         xmin = MIN(solsw(i),xmin)
175         xmax = MAX(solsw(i),xmax)
176      ENDDO
177      PRINT*,'Rayonnement solaire au sol solsw:', xmin, xmax
178
179! Lecture rayonnement IF au sol:
180
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
187      xmin = 1.0E+20
188      xmax = -1.0E+20
189      DO i = 1, klon
190         xmin = MIN(sollw(i),xmin)
191         xmax = MAX(sollw(i),xmax)
192      ENDDO
193      PRINT*,'Rayonnement IF au sol sollw:', xmin, xmax
194
195! Lecture derive des flux:
196
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
203      xmin = 1.0E+20
204      xmax = -1.0E+20
205      DO i = 1, klon
206         xmin = MIN(fder(i),xmin)
207         xmax = MAX(fder(i),xmax)
208      ENDDO
209      PRINT*,'Derive des flux fder:', xmin, xmax
210
211! Lecture du rayonnement net au sol:
212
213      CALL get_field("RADS",radsol,found)
214      IF (.not.found) THEN
215         PRINT*, 'phyetat0: Le champ <RADS> est absent'
216         CALL abort
217      ENDIF
218      xmin = 1.0E+20
219      xmax = -1.0E+20
220      DO i = 1, klon
221         xmin = MIN(radsol(i),xmin)
222         xmax = MAX(radsol(i),xmax)
223      ENDDO
224      PRINT*,'Rayonnement net au sol radsol:', xmin, xmax
225
226! Lecture de l'orographie sous-maille si ok_orodr:
227
228      if(ok_orodr) then
229     
230      CALL get_field("ZMEA",zmea,found)
231      IF (.not.found) THEN
232         PRINT*, 'phyetat0: Le champ <ZMEA> est absent'
233         CALL abort
234      ENDIF
235      xmin = 1.0E+20
236      xmax = -1.0E+20
237      DO i = 1, klon
238         xmin = MIN(zmea(i),xmin)
239         xmax = MAX(zmea(i),xmax)
240      ENDDO
241      PRINT*,'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
242
243      CALL get_field("ZSTD",zstd,found)
244      IF (.not.found) THEN
245         PRINT*, 'phyetat0: Le champ <ZSTD> est absent'
246         CALL abort
247      ENDIF
248      xmin = 1.0E+20
249      xmax = -1.0E+20
250      DO i = 1, klon
251         xmin = MIN(zstd(i),xmin)
252         xmax = MAX(zstd(i),xmax)
253      ENDDO
254      PRINT*,'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
255
256      CALL get_field("ZSIG",zsig,found)
257      IF (.not.found) THEN
258         PRINT*, 'phyetat0: Le champ <ZSIG> est absent'
259         CALL abort
260      ENDIF
261      xmin = 1.0E+20
262      xmax = -1.0E+20
263      DO i = 1, klon
264         xmin = MIN(zsig(i),xmin)
265         xmax = MAX(zsig(i),xmax)
266      ENDDO
267      PRINT*,'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
268
269      CALL get_field("ZGAM",zgam,found)
270      IF (.not.found) THEN
271         PRINT*, 'phyetat0: Le champ <ZGAM> est absent'
272         CALL abort
273      ENDIF
274      xmin = 1.0E+20
275      xmax = -1.0E+20
276      DO i = 1, klon
277         xmin = MIN(zgam(i),xmin)
278         xmax = MAX(zgam(i),xmax)
279      ENDDO
280      PRINT*,'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
281
282      CALL get_field("ZTHE",zthe,found)
283      IF (.not.found) THEN
284         PRINT*, 'phyetat0: Le champ <ZTHE> est absent'
285         CALL abort
286      ENDIF
287      xmin = 1.0E+20
288      xmax = -1.0E+20
289      DO i = 1, klon
290         xmin = MIN(zthe(i),xmin)
291         xmax = MAX(zthe(i),xmax)
292      ENDDO
293      PRINT*,'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
294
295      CALL get_field("ZPIC",zpic,found)
296      IF (.not.found) THEN
297         PRINT*, 'phyetat0: Le champ <ZPIC> est absent'
298         CALL abort
299      ENDIF
300      xmin = 1.0E+20
301      xmax = -1.0E+20
302      DO i = 1, klon
303         xmin = MIN(zpic(i),xmin)
304         xmax = MAX(zpic(i),xmax)
305      ENDDO
306      PRINT*,'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
307
308      CALL get_field("ZVAL",zval,found)
309      IF (.not.found) THEN
310         PRINT*, 'phyetat0: Le champ <ZVAL> est absent'
311         CALL abort
312      ENDIF
313      xmin = 1.0E+20
314      xmax = -1.0E+20
315      DO i = 1, klon
316         xmin = MIN(zval(i),xmin)
317         xmax = MAX(zval(i),xmax)
318      ENDDO
319      PRINT*,'OROGRAPHIE SOUS-MAILLE zval:', xmin, xmax
320
321      else
322         zmea = 0.
323         zstd = 0.
324         zsig = 0.
325         zgam = 0.
326         zthe = 0.
327         zpic = 0.
328         zval = 0.
329
330      endif   ! fin test sur ok_orodr
331
332!     Par defaut on cree 2 bandes de methane au pole Nord et au pole Sud
333!     (entre 75 et 85 degres de latitude) de 2 metres.
334!     Les poles sont sec !
335      resch4(1) = 0.    ! pole nord = 1 point
336      DO i=2,klon
337          if ((latitude_deg(i).ge.75..and.latitude_deg(i).le.85.).or.  &
338              (latitude_deg(i).ge.-85.and.latitude_deg(i).le.-75.)) then
339            resch4(i) = 2.
340          else
341            resch4(i) = 0.
342          endif
343      ENDDO
344      resch4(klon) = 0.   ! pole sud = 1 point
345
346      CALL get_field("RESCH4",resch4,found)
347      IF (.not.found) THEN
348         PRINT*, "phyetat0: Le champ <RESCH4> est absent"
349         PRINT*, "Pas de reservoir de methane mais je continue..."
350         PRINT*, "Pour info, je met 2 metres de methane sur 2 bandes"
351         PRINT*, "comprises entre 75 et 85 degres de latitude dans  "
352         PRINT*, "chaque hemisphere."         
353      ENDIF
354
355! Lecture de TANCIEN:
356
357      ancien_ok = .TRUE.
358
359      CALL get_field("TANCIEN",t_ancien,found)
360      IF (.not.found) THEN
361         PRINT*, "phyetat0: Le champ <TANCIEN> est absent"
362         PRINT*, "Depart legerement fausse. Mais je continue"
363         ancien_ok = .FALSE.
364      ENDIF
365
366! close file
367call close_startphy
368
369! do some more initializations
370call init_iophy_new(latitude_deg,longitude_deg)
371
372end subroutine phyetat0
Note: See TracBrowser for help on using the repository browser.