source: trunk/LMDZ.MARS/libf/phymars/phyetat0.F90 @ 1242

Last change on this file since 1242 was 1229, checked in by emillour, 11 years ago

Mars GCM:
Some minor fixes and cleanup.

  • allocation of qsurf() was missing in start2archive
  • 'tauscaling' was missing from argument list when calling physdem1 in testphys1d

EM

File size: 9.1 KB
Line 
1subroutine phyetat0 (fichnom,tab0,Lmodif,nsoil,ngrid,nlay,nq, &
2                     day_ini,time0,tsurf,tsoil,emis,q2,qsurf,co2ice, &
3                     tauscaling)
4!  use netcdf
5  use infotrac, only: nqtot, tname
6  use surfdat_h, only: phisfi, albedodat, z0, z0_default,&
7                       zmea, zstd, zsig, zgam, zthe
8  use control_mod, only: timestart
9  use iostart, only: nid_start, open_startphy, close_startphy, &
10                     get_field, get_var, inquire_field, &
11                     inquire_dimension, inquire_dimension_length
12
13  implicit none
14!======================================================================
15! Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818
16!  Adaptation à Mars : Yann Wanherdrick
17! Objet: Lecture de l etat initial pour la physique
18! Modifs: Aug.2010 EM : use NetCDF90 to load variables (enables using
19!                      r4 or r8 restarts independently of having compiled
20!                      the GCM in r4 or r8)
21!         June 2013 TN : Possibility to read files with a time axis
22!         November 2013 EM : Enabeling parallel, using iostart module
23!======================================================================
24!#include "netcdf.inc"
25!#include "dimensions.h"
26!#include "dimphys.h"
27!#include "comgeomfi.h"
28!#include "surfdat.h"
29!#include "dimradmars.h"
30!#include "yomaer.h"
31!#include "tracer.h"
32!#include "advtrac.h"
33!#include "control.h"
34!======================================================================
35  INTEGER nbsrf !Mars nbsrf a 1 au lieu de 4
36  PARAMETER (nbsrf=1) ! nombre de sous-fractions pour une maille
37!======================================================================
38!  Arguments:
39!  ---------
40!  inputs:
41  character*(*),intent(in) :: fichnom ! "startfi.nc" file
42  integer,intent(in) :: tab0
43  integer,intent(in) :: Lmodif
44  integer,intent(in) :: nsoil ! # of soil layers
45  integer,intent(in) :: ngrid ! # of atmospheric columns
46  integer,intent(in) :: nlay ! # of atmospheric layers
47  integer,intent(in) :: nq
48  integer :: day_ini
49  real :: time0
50
51!  outputs:
52  real,intent(out) :: tsurf(ngrid) ! surface temperature
53  real,intent(out) :: tsoil(ngrid,nsoil) ! soil temperature
54  real,intent(out) :: emis(ngrid) ! surface emissivity
55  real,intent(out) :: q2(ngrid,nlay+1) !
56  real,intent(out) :: qsurf(ngrid,nq) ! tracers on surface
57  real,intent(out) :: co2ice(ngrid) ! co2 ice cover
58  real,intent(out) :: tauscaling(ngrid) ! dust conversion factor
59
60!======================================================================
61!  Local variables:
62
63      real surffield(ngrid) ! to temporarily store a surface field
64      real xmin,xmax ! to display min and max of a field
65!
66      INTEGER ig,iq,lmax
67      INTEGER nid, nvarid
68      INTEGER ierr, i, nsrf
69!      integer isoil
70!      INTEGER length
71!      PARAMETER (length=100)
72      CHARACTER*7 str7
73      CHARACTER*2 str2
74      CHARACTER*1 yes
75!
76      REAL p_rad,p_omeg,p_g,p_mugaz,p_daysec
77      INTEGER nqold
78
79! flag which identifies if 'startfi.nc' file is using old names (qsurf01,...)
80      logical :: oldtracernames=.false.
81      integer :: count
82      character(len=30) :: txt ! to store some text
83
84! specific for time
85      REAL,ALLOCATABLE :: time(:) ! times stored in start
86      INTEGER timelen ! number of times stored in the file
87      INTEGER indextime ! index of selected time
88
89      INTEGER :: edges(3),corner(3)
90      LOGICAL :: found
91
92! open physics initial state file:
93call open_startphy(fichnom)
94
95
96! possibility to modify tab_cntrl in tabfi
97write(*,*)
98write(*,*) 'TABFI in phyeta0: Lmodif=',Lmodif," tab0=",tab0
99call tabfi (nid_start,Lmodif,tab0,day_ini,lmax,p_rad, &
100            p_omeg,p_g,p_mugaz,p_daysec,time0)
101
102
103! Load surface geopotential:
104call get_field("phisfi",phisfi,found)
105if (.not.found) then
106  write(*,*) "phyetat0: Failed loading <phisfi>"
107  call abort
108else
109  write(*,*) "phyetat0: surface geopotential <phisfi> range:", &
110             minval(phisfi), maxval(phisfi)
111endif
112
113
114! Load bare ground albedo:
115call get_field("albedodat",albedodat,found)
116if (.not.found) then
117  write(*,*) "phyetat0: Failed loading <albedodat>"
118  call abort
119else
120  write(*,*) "phyetat0: Bare ground albedo <albedodat> range:", &
121             minval(albedodat), maxval(albedodat)
122endif
123
124! ZMEA
125call get_field("ZMEA",zmea,found)
126if (.not.found) then
127  write(*,*) "phyetat0: Failed loading <ZMEA>"
128  call abort
129else
130  write(*,*) "phyetat0: <ZMEA> range:", &
131             minval(zmea), maxval(zmea)
132endif
133
134
135! ZSTD
136call get_field("ZSTD",zstd,found)
137if (.not.found) then
138  write(*,*) "phyetat0: Failed loading <ZSTD>"
139  call abort
140else
141  write(*,*) "phyetat0: <ZSTD> range:", &
142             minval(zstd), maxval(zstd)
143endif
144
145
146! ZSIG
147call get_field("ZSIG",zsig,found)
148if (.not.found) then
149  write(*,*) "phyetat0: Failed loading <ZSIG>"
150  call abort
151else
152  write(*,*) "phyetat0: <ZSIG> range:", &
153             minval(zsig), maxval(zsig)
154endif
155
156
157! ZGAM
158call get_field("ZGAM",zgam,found)
159if (.not.found) then
160  write(*,*) "phyetat0: Failed loading <ZGAM>"
161  call abort
162else
163  write(*,*) "phyetat0: <ZGAM> range:", &
164             minval(zgam), maxval(zgam)
165endif
166
167
168! ZTHE
169call get_field("ZTHE",zthe,found)
170if (.not.found) then
171  write(*,*) "phyetat0: Failed loading <ZTHE>"
172  call abort
173else
174  write(*,*) "phyetat0: <ZTHE> range:", &
175             minval(zthe), maxval(zthe)
176endif
177
178     
179! Time axis
180found=inquire_dimension("Time")
181if (.not.found) then
182  indextime = 1
183  write(*,*) "phyetat0: No time axis found in "//trim(fichnom)
184else
185  write(*,*) "phyetat0: Time axis found in "//trim(fichnom)
186  timelen=inquire_dimension_length("Time")
187  allocate(time(timelen))
188  ! load "Time" array:
189  call get_var("Time",time,found)
190  if (.not.found) then
191    write(*,*) "phyetat0: Failed loading <Time>"
192    call abort
193  endif
194  ! seclect the desired time index
195  IF (timestart .lt. 0) THEN  ! default: we use the last time value
196    indextime = timelen
197  ELSE  ! else we look for the desired value in the time axis
198    indextime = 0
199    DO i=1,timelen
200      IF (abs(time(i) - timestart) .lt. 0.01) THEN
201        indextime = i
202        EXIT
203      ENDIF
204    ENDDO
205    IF (indextime .eq. 0) THEN
206      PRINT*, "Time", timestart," is not in "//trim(fichnom)//"!!"
207      PRINT*, "Stored times are:"
208      DO i=1,timelen
209         PRINT*, time(i)
210      ENDDO
211      CALL abort
212    ENDIF
213  ENDIF ! of IF (timestart .lt. 0)
214  ! In startfi the absolute date is day_ini + time0 + time
215  ! For now on, in the GCM physics, it is day_ini + time0
216  time0 = time(indextime) + time0
217  day_ini = day_ini + INT(time0)
218  time0 = time0 - INT(time0)
219       
220  PRINT*, "phyetat0: Selected time ",time(indextime), &
221          " at index ",indextime
222     
223  DEALLOCATE(time)
224endif ! of if Time not found in file
225
226
227! CO2 ice cover
228call get_field("co2ice",co2ice,found,indextime)
229if (.not.found) then
230  write(*,*) "phyetat0: Failed loading <co2ice>"
231  call abort
232else
233  write(*,*) "phyetat0: CO2 ice cover <co2ice> range:", &
234             minval(co2ice), maxval(co2ice)
235endif
236
237
238! Dust conversion factor
239call get_field("tauscaling",tauscaling,found,indextime)
240if (.not.found) then
241  write(*,*) "phyetat0: <tauscaling> not in file"
242  tauscaling(:) = -1
243else
244  write(*,*) "phyetat0: dust conversion factor <tauscaling> range:", &
245             minval(tauscaling), maxval(tauscaling)
246endif
247
248
249! Surface temperature :
250call get_field("tsurf",tsurf,found,indextime)
251if (.not.found) then
252  write(*,*) "phyetat0: Failed loading <tsurf>"
253  call abort
254else
255  write(*,*) "phyetat0: Surface temperature <tsurf> range:", &
256             minval(tsurf), maxval(tsurf)
257endif
258
259! Surface emissivity
260call get_field("emis",emis,found,indextime)
261if (.not.found) then
262  write(*,*) "phyetat0: Failed loading <emis>"
263  call abort
264else
265  write(*,*) "phyetat0: Surface emissivity <emis> range:", &
266             minval(emis), maxval(emis)
267endif
268
269
270! surface roughness length (NB: z0 is a common in surfdat_h)
271call get_field("z0",z0,found)
272if (.not.found) then
273  write(*,*) "phyetat0: Failed loading <z0>"
274  write(*,*) 'will use constant value of z0_default:',z0_default
275  z0(:)=z0_default
276else
277  write(*,*) "phyetat0: Surface roughness <z0> range:", &
278             minval(z0), maxval(z0)
279endif
280
281
282! pbl wind variance
283call get_field("q2",q2,found,indextime)
284if (.not.found) then
285  write(*,*) "phyetat0: Failed loading <q2>"
286  call abort
287else
288  write(*,*) "phyetat0: PBL wind variance <q2> range:", &
289             minval(q2), maxval(q2)
290endif
291
292
293! tracer on surface
294if (nq.ge.1) then
295  do iq=1,nq
296    txt=tname(iq)
297    if (txt.eq."h2o_vap") then
298      ! There is no surface tracer for h2o_vap;
299      ! "h2o_ice" should be loaded instead
300      txt="h2o_ice"
301      write(*,*) 'phyetat0: loading surface tracer', &
302                           ' h2o_ice instead of h2o_vap'
303    endif
304    call get_field(txt,qsurf(:,iq),found,indextime)
305    if (.not.found) then
306      write(*,*) "phyetat0: Failed loading <",trim(txt),">"
307      write(*,*) "         ",trim(txt)," is set to zero"
308    else
309      write(*,*) "phyetat0: Surface tracer <",trim(txt),"> range:", &
310                 minval(qsurf(:,iq)), maxval(qsurf(:,iq))
311    endif
312  enddo
313endif ! of if (nq.ge.1)
314
315! Call to soil_settings, in order to read soil temperatures,
316! as well as thermal inertia and volumetric heat capacity
317
318      call soil_settings(nid_start,ngrid,nsoil,tsurf,tsoil,indextime)
319
320!
321! close file:
322!
323      call close_startphy
324
325      END
Note: See TracBrowser for help on using the repository browser.