source: trunk/LMDZ.GENERIC/libf/phystd/phyetat0.F90 @ 1295

Last change on this file since 1295 was 1252, checked in by aslmd, 11 years ago

LMDZ.GENERIC LMDZ.COMMON LMDZ.UNIVERSAL. Bye Bye LMDZ.UNIVERSAL. Go to LMDZ.COMMON!

File size: 9.1 KB
Line 
1subroutine phyetat0 (ngrid,fichnom,tab0,Lmodif,nsoil,nq, &
2                     day_ini,time,tsurf,tsoil, &
3                     emis,q2,qsurf,cloudfrac,totcloudfrac,hice)
4
5  USE infotrac, ONLY: tname
6  USE surfdat_h, only: phisfi, albedodat, zmea, zstd, zsig, zgam, zthe
7  use iostart, only: nid_start, open_startphy, close_startphy, &
8                     get_field, get_var, inquire_field, &
9                     inquire_dimension, inquire_dimension_length
10
11  implicit none
12
13!======================================================================
14! Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818
15!  Adaptation à Mars : Yann Wanherdrick
16! Objet: Lecture de l etat initial pour la physique
17!======================================================================
18#include "netcdf.inc"
19#include "dimensions.h"
20#include "dimphys.h"
21#include "planete.h"
22#include "comcstfi.h"
23
24!======================================================================
25!  INTEGER nbsrf !Mars nbsrf a 1 au lieu de 4
26!  PARAMETER (nbsrf=1) ! nombre de sous-fractions pour une maille
27!======================================================================
28!  Arguments:
29!  ---------
30!  inputs:
31  integer,intent(in) :: ngrid
32  character*(*),intent(in) :: fichnom ! "startfi.nc" file
33  integer,intent(in) :: tab0
34  integer,intent(in) :: Lmodif
35  integer,intent(in) :: nsoil ! # of soil layers
36  integer,intent(in) :: nq
37  integer,intent(in) :: day_ini
38  real,intent(in) :: time
39
40!  outputs:
41  real,intent(out) :: tsurf(ngrid) ! surface temperature
42  real,intent(out) :: tsoil(ngrid,nsoil) ! soil temperature
43  real,intent(out) :: emis(ngrid) ! surface emissivity
44  real,intent(out) :: q2(ngrid, llm+1) !
45  real,intent(out) :: qsurf(ngrid,nq) ! tracers on surface
46! real co2ice(ngrid) ! co2 ice cover
47  real,intent(out) :: cloudfrac(ngrid,nlayermx)
48  real,intent(out) :: hice(ngrid), totcloudfrac(ngrid)
49
50!======================================================================
51!  Local variables:
52
53!      INTEGER radpas
54!      REAL co2_ppm
55!      REAL solaire
56
57      real xmin,xmax ! to display min and max of a field
58!
59      INTEGER ig,iq,lmax
60      INTEGER nid, nvarid
61      INTEGER ierr, i, nsrf
62!      integer isoil
63!      INTEGER length
64!      PARAMETER (length=100)
65      CHARACTER*7 str7
66      CHARACTER*2 str2
67      CHARACTER*1 yes
68!
69      REAL p_rad,p_omeg,p_g,p_cpp,p_mugaz,p_daysec
70      INTEGER nqold
71
72! flag which identifies if 'startfi.nc' file is using old names (qsurf01,...)
73!      logical :: oldtracernames=.false.
74      integer :: count
75      character(len=30) :: txt ! to store some text
76     
77      INTEGER :: indextime=1 ! index of selected time, default value=1
78      logical :: found
79
80!
81! ALLOCATE ARRAYS IN surfdat_h
82!
83IF (.not. ALLOCATED(albedodat)) ALLOCATE(albedodat(ngrid))
84IF (.not. ALLOCATED(phisfi)) ALLOCATE(phisfi(ngrid))
85IF (.not. ALLOCATED(zmea)) ALLOCATE(zmea(ngrid))
86IF (.not. ALLOCATED(zstd)) ALLOCATE(zstd(ngrid))
87IF (.not. ALLOCATED(zsig)) ALLOCATE(zsig(ngrid))
88IF (.not. ALLOCATED(zgam)) ALLOCATE(zgam(ngrid))
89IF (.not. ALLOCATED(zthe)) ALLOCATE(zthe(ngrid))
90
91! open physics initial state file:
92call open_startphy(fichnom)
93
94
95! possibility to modify tab_cntrl in tabfi
96write(*,*)
97write(*,*) 'TABFI in phyeta0: Lmodif=',Lmodif," tab0=",tab0
98call tabfi (ngrid,nid_start,Lmodif,tab0,day_ini,lmax,p_rad, &
99                   p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time)
100
101!c
102!c Lecture des latitudes (coordonnees):
103!c
104!      ierr = NF_INQ_VARID (nid, "latitude", nvarid)
105!      IF (ierr.NE.NF_NOERR) THEN
106!         PRINT*, 'phyetat0: Le champ <latitude> est absent'
107!         CALL abort
108!      ENDIF
109!#ifdef NC_DOUBLE
110!      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,sta,ngrid,lati)
111!#else
112!      ierr = NF_GET_VARA_REAL(nid,nvarid,sta,ngrid,lati)
113!#endif
114!      IF (ierr.NE.NF_NOERR) THEN
115!         PRINT*, 'phyetat0: Lecture echouee pour <latitude>'
116!         CALL abort
117!      ENDIF
118!c
119!c Lecture des longitudes (coordonnees):
120!c
121!      ierr = NF_INQ_VARID (nid, "longitude", nvarid)
122!      IF (ierr.NE.NF_NOERR) THEN
123!         PRINT*, 'phyetat0: Le champ <longitude> est absent'
124!         CALL abort
125!      ENDIF
126!#ifdef NC_DOUBLE
127!      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,sta,ngrid,long)
128!#else
129!      ierr = NF_GET_VARA_REAL(nid,nvarid,sta,ngrid,long)
130!#endif
131!      IF (ierr.NE.NF_NOERR) THEN
132!         PRINT*, 'phyetat0: Lecture echouee pour <longitude>'
133!         CALL abort
134!      ENDIF
135!c
136!c Lecture des aires des mailles:
137!c
138!      ierr = NF_INQ_VARID (nid, "area", nvarid)
139!      IF (ierr.NE.NF_NOERR) THEN
140!         PRINT*, 'phyetat0: Le champ <area> est absent'
141!         CALL abort
142!      ENDIF
143!#ifdef NC_DOUBLE
144!      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,sta,ngrid,area)
145!#else
146!      ierr = NF_GET_VARA_REAL(nid,nvarid,sta,ngrid,area)
147!#endif
148!      IF (ierr.NE.NF_NOERR) THEN
149!         PRINT*, 'phyetat0: Lecture echouee pour <area>'
150!         CALL abort
151!      ENDIF
152!      xmin = 1.0E+20
153!      xmax = -1.0E+20
154!      xmin = MINVAL(area)
155!      xmax = MAXVAL(area)
156!      PRINT*,'Aires des mailles <area>:', xmin, xmax
157
158! Load surface geopotential:
159call get_field("phisfi",phisfi,found)
160if (.not.found) then
161  write(*,*) "phyetat0: Failed loading <phisfi>"
162  call abort
163else
164  write(*,*) "phyetat0: surface geopotential <phisfi> range:", &
165             minval(phisfi), maxval(phisfi)
166endif
167
168! Load bare ground albedo:
169call get_field("albedodat",albedodat,found)
170if (.not.found) then
171  write(*,*) "phyetat0: Failed loading <albedodat>"
172  call abort
173else
174  write(*,*) "phyetat0: Bare ground albedo <albedodat> range:", &
175             minval(albedodat), maxval(albedodat)
176endif
177
178! ZMEA
179call get_field("ZMEA",zmea,found)
180if (.not.found) then
181  write(*,*) "phyetat0: Failed loading <ZMEA>"
182  call abort
183else
184  write(*,*) "phyetat0: <ZMEA> range:", &
185             minval(zmea), maxval(zmea)
186endif
187
188! ZSTD
189call get_field("ZSTD",zstd,found)
190if (.not.found) then
191  write(*,*) "phyetat0: Failed loading <ZSTD>"
192  call abort
193else
194  write(*,*) "phyetat0: <ZSTD> range:", &
195             minval(zstd), maxval(zstd)
196endif
197
198! ZSIG
199call get_field("ZSIG",zsig,found)
200if (.not.found) then
201  write(*,*) "phyetat0: Failed loading <ZSIG>"
202  call abort
203else
204  write(*,*) "phyetat0: <ZSIG> range:", &
205             minval(zsig), maxval(zsig)
206endif
207
208! ZGAM
209call get_field("ZGAM",zgam,found)
210if (.not.found) then
211  write(*,*) "phyetat0: Failed loading <ZGAM>"
212  call abort
213else
214  write(*,*) "phyetat0: <ZGAM> range:", &
215             minval(zgam), maxval(zgam)
216endif
217
218! ZTHE
219call get_field("ZTHE",zthe,found)
220if (.not.found) then
221  write(*,*) "phyetat0: Failed loading <ZTHE>"
222  call abort
223else
224  write(*,*) "phyetat0: <ZTHE> range:", &
225             minval(zthe), maxval(zthe)
226endif
227
228! Surface temperature :
229call get_field("tsurf",tsurf,found,indextime)
230if (.not.found) then
231  write(*,*) "phyetat0: Failed loading <tsurf>"
232  call abort
233else
234  write(*,*) "phyetat0: Surface temperature <tsurf> range:", &
235             minval(tsurf), maxval(tsurf)
236endif
237
238! Surface emissivity
239call get_field("emis",emis,found,indextime)
240if (.not.found) then
241  write(*,*) "phyetat0: Failed loading <emis>"
242  call abort
243else
244  write(*,*) "phyetat0: Surface emissivity <emis> range:", &
245             minval(emis), maxval(emis)
246endif
247
248! Cloud fraction (added by BC 2010)
249call get_field("cloudfrac",cloudfrac,found,indextime)
250if (.not.found) then
251  write(*,*) "phyetat0: Failed loading <cloudfrac>"
252  call abort
253else
254  write(*,*) "phyetat0: Cloud fraction <cloudfrac> range:", &
255             minval(cloudfrac), maxval(cloudfrac)
256endif
257
258! Total cloud fraction (added by BC 2010)
259call get_field("totcloudfrac",totcloudfrac,found,indextime)
260if (.not.found) then
261  write(*,*) "phyetat0: Failed loading <totcloudfrac>"
262  call abort
263else
264  write(*,*) "phyetat0: Total cloud fraction <totcloudfrac> range:", &
265             minval(totcloudfrac), maxval(totcloudfrac)
266endif
267
268! Height of oceanic ice (added by BC 2010)
269call get_field("hice",hice,found,indextime)
270if (.not.found) then
271  write(*,*) "phyetat0: Failed loading <hice>"
272  call abort
273else
274  write(*,*) "phyetat0: Height of oceanic ice <hice> range:", &
275             minval(hice), maxval(hice)
276endif
277
278! pbl wind variance
279call get_field("q2",q2,found,indextime)
280if (.not.found) then
281  write(*,*) "phyetat0: Failed loading <q2>"
282  call abort
283else
284  write(*,*) "phyetat0: PBL wind variance <q2> range:", &
285             minval(q2), maxval(q2)
286endif
287
288! tracer on surface
289if (nq.ge.1) then
290  do iq=1,nq
291    txt=tname(iq)
292    if (txt.eq."h2o_vap") then
293      ! There is no surface tracer for h2o_vap;
294      ! "h2o_ice" should be loaded instead
295      txt="h2o_ice"
296      write(*,*) 'phyetat0: loading surface tracer', &
297                           ' h2o_ice instead of h2o_vap'
298    endif
299    call get_field(txt,qsurf(:,iq),found,indextime)
300    if (.not.found) then
301      write(*,*) "phyetat0: Failed loading <",trim(txt),">"
302      write(*,*) "         ",trim(txt)," is set to zero"
303    else
304      write(*,*) "phyetat0: Surface tracer <",trim(txt),"> range:", &
305                 minval(qsurf(:,iq)), maxval(qsurf(:,iq))
306    endif
307  enddo
308endif ! of if (nq.ge.1)
309
310! Call to soil_settings, in order to read soil temperatures,
311! as well as thermal inertia and volumetric heat capacity
312
313call soil_settings(nid_start,ngrid,nsoil,tsurf,tsoil,indextime)
314
315!
316! close file:
317!
318call close_startphy
319
320END SUBROUTINE phyetat0
Note: See TracBrowser for help on using the repository browser.