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

Last change on this file since 1524 was 1524, checked in by emillour, 9 years ago

All GCMS:
More updates to enforce dynamics/physics separation:

get rid of references to "temps_mod" from physics packages;
make a "time_phylmdz_mod.F90" module to store that
information and fill it via "iniphysiq".

EM

File size: 9.6 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 infotrac
15      USE comgeomphy,  only: rlatd,rlond
16      USE control_mod, only: raz_date
17      USE time_phylmdz_mod, only: itau_phy
18
19implicit none
20!======================================================================
21! Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818
22! Objet: Lecture de l'etat initial pour la physique
23!======================================================================
24#include "dimensions.h"
25#include "netcdf.inc"
26#include "dimsoil.h"
27#include "clesphys.h"
28#include "tabcontrol.h"
29!======================================================================
30
31character(len=*),intent(in) :: fichnom ! input file name
32REAL    :: xmin, xmax
33LOGICAL :: found
34REAL    :: tab_cntrl(length)
35integer :: i,isoil
36CHARACTER(len=2) :: str2
37
38! les variables globales lues dans le fichier restart
39
40! open physics initial state file:
41call open_startphy(fichnom)
42
43!
44! Lecture des parametres de controle:
45!
46      CALL get_var("controle",tab_cntrl,found)
47      IF (.not.found) THEN
48         PRINT*, 'phyetat0: Le champ <controle> est absent'
49         CALL abort
50      ENDIF
51       
52      DO i = 1, length
53           tabcntr0( i ) = tab_cntrl( i )
54      ENDDO
55
56
57      dtime        = tab_cntrl(1)
58      radpas       = tab_cntrl(2)
59      chimpas      = tab_cntrl(3)
60      lsinit       = tab_cntrl(17)
61
62      itau_phy = tab_cntrl(15)
63
64! Attention si raz_date est active :
65! il faut remettre a zero itau_phy apres phyetat0 !
66! et verifier que lsinit est proche de 0.
67      IF (raz_date.eq.1) THEN
68        itau_phy=0
69        if ((lsinit.gt.3.).and.(lsinit.lt.357.)) then
70          PRINT*, 'phyetat0: raz_date=1 and ls different from 0.'
71          PRINT*, 'When raz_date=1, we reset the initial date'
72          PRINT*, 'to spring equinox, Ls=0., so the start files'
73          PRINT*, 'should be within a couple of degrees from Ls=0.'
74          PRINT*, 'or the circulation will be too far from equilibrium'
75          CALL abort
76        endif
77      ENDIF
78
79! read latitudes
80call get_field("latitude",rlatd,found)
81      IF (.not.found) THEN
82         PRINT*, 'phyetat0: Le champ <latitude> est absent'
83         CALL abort
84      ENDIF
85
86! read longitudes
87call get_field("longitude",rlond,found)
88      IF (.not.found) THEN
89         PRINT*, 'phyetat0: Le champ <longitude> est absent'
90         CALL abort
91      ENDIF
92
93! read in other variables here ...
94
95! Lecture des temperatures du sol:
96
97       CALL get_field("TS",ftsol(:),found)
98      IF (.not.found) THEN
99         PRINT*, 'phyetat0: Le champ <TS> est absent'
100         PRINT*, "phyetat0: Lecture echouee pour <TS>"
101         CALL abort
102      ELSE
103         PRINT*, 'phyetat0: Le champ <TS> est present'
104         xmin = 1.0E+20
105         xmax = -1.0E+20
106         DO i = 1, klon
107            xmin = MIN(ftsol(i),xmin)
108            xmax = MAX(ftsol(i),xmax)
109         ENDDO
110         PRINT*,'Temperature du sol <TS>', xmin, xmax
111      ENDIF
112
113
114! Lecture des temperatures du sol profond:
115
116      DO isoil=1, nsoilmx
117      IF (isoil.GT.99) THEN
118         PRINT*, "Trop de couches"
119         CALL abort
120      ENDIF
121      WRITE(str2,'(i2.2)') isoil
122      CALL get_field('Tsoil'//str2,ftsoil(:,isoil),found)
123      IF (.not.found) THEN
124         PRINT*, "phyetat0: Le champ <Tsoil"//str2//"> est absent"
125         PRINT*, "          Il prend donc la valeur de surface"
126         DO i=1, klon
127             ftsoil(i,isoil)=ftsol(i)
128         ENDDO
129      ENDIF
130      ENDDO
131
132! Lecture de albedo au sol:
133
134      CALL get_field("ALBE", falbe,found)
135      IF (.not.found) THEN
136         PRINT*, 'phyetat0: Le champ <ALBE> est absent'
137         PRINT*, "phyetat0: Lecture echouee pour <ALBE>"
138         CALL abort
139      ELSE
140         xmin = 1.0E+20
141         xmax = -1.0E+20
142         DO i = 1, klon
143            xmin = MIN(falbe(i),xmin)
144            xmax = MAX(falbe(i),xmax)
145         ENDDO
146         PRINT*,'Albedo du sol <ALBE>', xmin, xmax
147      ENDIF
148
149! Lecture rayonnement solaire au sol:
150
151      CALL get_field("solsw",solsw,found)
152      IF (.not.found) THEN
153         PRINT*, 'phyetat0: Le champ <solsw> est absent'
154         PRINT*, 'mis a zero'
155         solsw = 0.
156      ENDIF
157      xmin = 1.0E+20
158      xmax = -1.0E+20
159      DO i = 1, klon
160         xmin = MIN(solsw(i),xmin)
161         xmax = MAX(solsw(i),xmax)
162      ENDDO
163      PRINT*,'Rayonnement solaire au sol solsw:', xmin, xmax
164
165! Lecture rayonnement IF au sol:
166
167      CALL get_field("sollw",sollw,found)
168      IF (.not.found) THEN
169         PRINT*, 'phyetat0: Le champ <sollw> est absent'
170         PRINT*, 'mis a zero'
171         sollw = 0.
172      ENDIF
173      xmin = 1.0E+20
174      xmax = -1.0E+20
175      DO i = 1, klon
176         xmin = MIN(sollw(i),xmin)
177         xmax = MAX(sollw(i),xmax)
178      ENDDO
179      PRINT*,'Rayonnement IF au sol sollw:', xmin, xmax
180
181! Lecture derive des flux:
182
183      CALL get_field("fder",fder,found)
184      IF (.not.found) THEN
185         PRINT*, 'phyetat0: Le champ <fder> est absent'
186         PRINT*, 'mis a zero'
187         fder = 0.
188      ENDIF
189      xmin = 1.0E+20
190      xmax = -1.0E+20
191      DO i = 1, klon
192         xmin = MIN(fder(i),xmin)
193         xmax = MAX(fder(i),xmax)
194      ENDDO
195      PRINT*,'Derive des flux fder:', xmin, xmax
196
197! Lecture du rayonnement net au sol:
198
199      CALL get_field("RADS",radsol,found)
200      IF (.not.found) THEN
201         PRINT*, 'phyetat0: Le champ <RADS> est absent'
202         CALL abort
203      ENDIF
204      xmin = 1.0E+20
205      xmax = -1.0E+20
206      DO i = 1, klon
207         xmin = MIN(radsol(i),xmin)
208         xmax = MAX(radsol(i),xmax)
209      ENDDO
210      PRINT*,'Rayonnement net au sol radsol:', xmin, xmax
211
212! Lecture de l'orographie sous-maille si ok_orodr:
213
214      if(ok_orodr) then
215     
216      CALL get_field("ZMEA",zmea,found)
217      IF (.not.found) THEN
218         PRINT*, 'phyetat0: Le champ <ZMEA> est absent'
219         CALL abort
220      ENDIF
221      xmin = 1.0E+20
222      xmax = -1.0E+20
223      DO i = 1, klon
224         xmin = MIN(zmea(i),xmin)
225         xmax = MAX(zmea(i),xmax)
226      ENDDO
227      PRINT*,'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
228
229      CALL get_field("ZSTD",zstd,found)
230      IF (.not.found) THEN
231         PRINT*, 'phyetat0: Le champ <ZSTD> est absent'
232         CALL abort
233      ENDIF
234      xmin = 1.0E+20
235      xmax = -1.0E+20
236      DO i = 1, klon
237         xmin = MIN(zstd(i),xmin)
238         xmax = MAX(zstd(i),xmax)
239      ENDDO
240      PRINT*,'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
241
242      CALL get_field("ZSIG",zsig,found)
243      IF (.not.found) THEN
244         PRINT*, 'phyetat0: Le champ <ZSIG> est absent'
245         CALL abort
246      ENDIF
247      xmin = 1.0E+20
248      xmax = -1.0E+20
249      DO i = 1, klon
250         xmin = MIN(zsig(i),xmin)
251         xmax = MAX(zsig(i),xmax)
252      ENDDO
253      PRINT*,'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
254
255      CALL get_field("ZGAM",zgam,found)
256      IF (.not.found) THEN
257         PRINT*, 'phyetat0: Le champ <ZGAM> est absent'
258         CALL abort
259      ENDIF
260      xmin = 1.0E+20
261      xmax = -1.0E+20
262      DO i = 1, klon
263         xmin = MIN(zgam(i),xmin)
264         xmax = MAX(zgam(i),xmax)
265      ENDDO
266      PRINT*,'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
267
268      CALL get_field("ZTHE",zthe,found)
269      IF (.not.found) THEN
270         PRINT*, 'phyetat0: Le champ <ZTHE> est absent'
271         CALL abort
272      ENDIF
273      xmin = 1.0E+20
274      xmax = -1.0E+20
275      DO i = 1, klon
276         xmin = MIN(zthe(i),xmin)
277         xmax = MAX(zthe(i),xmax)
278      ENDDO
279      PRINT*,'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
280
281      CALL get_field("ZPIC",zpic,found)
282      IF (.not.found) THEN
283         PRINT*, 'phyetat0: Le champ <ZPIC> est absent'
284         CALL abort
285      ENDIF
286      xmin = 1.0E+20
287      xmax = -1.0E+20
288      DO i = 1, klon
289         xmin = MIN(zpic(i),xmin)
290         xmax = MAX(zpic(i),xmax)
291      ENDDO
292      PRINT*,'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
293
294      CALL get_field("ZVAL",zval,found)
295      IF (.not.found) THEN
296         PRINT*, 'phyetat0: Le champ <ZVAL> est absent'
297         CALL abort
298      ENDIF
299      xmin = 1.0E+20
300      xmax = -1.0E+20
301      DO i = 1, klon
302         xmin = MIN(zval(i),xmin)
303         xmax = MAX(zval(i),xmax)
304      ENDDO
305      PRINT*,'OROGRAPHIE SOUS-MAILLE zval:', xmin, xmax
306
307      else
308         zmea = 0.
309         zstd = 0.
310         zsig = 0.
311         zgam = 0.
312         zthe = 0.
313         zpic = 0.
314         zval = 0.
315
316      endif   ! fin test sur ok_orodr
317
318!     Par defaut on cree 2 bandes de methane au pole Nord et au pole Sud
319!     (entre 75 et 85 degres de latitude) de 2 metres.
320!     Les poles sont sec !
321      resch4(1) = 0.    ! pole nord = 1 point
322      DO i=2,klon
323          if ((rlatd(i).ge.75..and.rlatd(i).le.85.).or.  &
324              (rlatd(i).ge.-85.and.rlatd(i).le.-75.)) then
325            resch4(i) = 2.
326          else
327            resch4(i) = 0.
328          endif
329      ENDDO
330      resch4(klon) = 0.   ! pole sud = 1 point
331
332      CALL get_field("RESCH4",resch4,found)
333      IF (.not.found) THEN
334         PRINT*, "phyetat0: Le champ <RESCH4> est absent"
335         PRINT*, "Pas de reservoir de methane mais je continue..."
336         PRINT*, "Pour info, je met 2 metres de methane sur 2 bandes"
337         PRINT*, "comprises entre 75 et 85 degres de latitude dans  "
338         PRINT*, "chaque hemisphere."         
339      ENDIF
340
341! Lecture de TANCIEN:
342
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
351
352! close file
353call close_startphy
354
355! do some more initializations
356call init_iophy_new(rlatd,rlond)
357
358end subroutine phyetat0
Note: See TracBrowser for help on using the repository browser.