source: trunk/LMDZ.MARS/libf/phymars/phyetat0_mod.F90 @ 2043

Last change on this file since 2043 was 1974, checked in by mvals, 7 years ago

Mars GCM:
Integration of the detached dust layer parametrizations (rocket dust storm, slope wind lifting, CW, and dust injection scheme, DB).
Still experimental, default behaviour (rdstorm=.false., dustinjection=0) identical to previous revision.
NB: Updated newstart requires an updated "surface.nc" containing the "hmons" field.
EM+MV

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