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

Last change on this file since 2832 was 2826, checked in by romain.vande, 3 years ago

Mars GCM:
The variable co2ice is deleted. All the co2 ice on surface is now in qsurf(:,igcm_co2).
CO2 tracer is now mandatory. diagfi output is unchanged.
RV

File size: 20.9 KB
Line 
1module phyetat0_mod
2
3implicit none
4  real,save :: tab_cntrl_mod(100)
5
6!$OMP THREADPRIVATE(tab_cntrl_mod)
7
8contains
9
10subroutine phyetat0 (fichnom,tab0,Lmodif,nsoil,ngrid,nlay,nq, &
11                     day_ini,time0,tsurf,tsoil,albedo,emis,q2,qsurf, &
12                     tauscaling,totcloudfrac,wstar,watercap)
13
14  use tracer_mod, only: noms ! tracer names
15  use surfdat_h, only: phisfi, albedodat, z0, z0_default,&
16                       zmea, zstd, zsig, zgam, zthe, hmons, summit, base
17  use iostart, only: nid_start, open_startphy, close_startphy, &
18                     get_field, get_var, inquire_field, &
19                     inquire_dimension, inquire_dimension_length
20  use nonoro_gwd_ran_mod, only: du_nonoro_gwd, dv_nonoro_gwd
21  use compute_dtau_mod, only: dtau
22  use dust_rad_adjust_mod, only: dust_rad_adjust_prev,dust_rad_adjust_next
23  use dust_param_mod, only: dustscaling_mode
24  USE ioipsl_getin_p_mod, ONLY : getin_p
25
26  implicit none
27 
28  include "callkeys.h"
29!======================================================================
30! Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818
31!  Adaptation � Mars : Yann Wanherdrick
32! Objet: Lecture de l etat initial pour la physique
33! Modifs: Aug.2010 EM : use NetCDF90 to load variables (enables using
34!                      r4 or r8 restarts independently of having compiled
35!                      the GCM in r4 or r8)
36!         June 2013 TN : Possibility to read files with a time axis
37!         November 2013 EM : Enabeling parallel, using iostart module
38!         March 2020 AD: Enabling initialization of physics without startfi
39!                        flag: startphy_file
40!======================================================================
41  INTEGER nbsrf !Mars nbsrf a 1 au lieu de 4
42  PARAMETER (nbsrf=1) ! nombre de sous-fractions pour une maille
43!======================================================================
44!  Arguments:
45!  ---------
46!  inputs:
47!  logical,intent(in) :: startphy_file ! .true. if reading start file
48  character*(*),intent(in) :: fichnom ! "startfi.nc" file
49  integer,intent(in) :: tab0
50  integer,intent(in) :: Lmodif
51  integer,intent(in) :: nsoil ! # of soil layers
52  integer,intent(in) :: ngrid ! # of atmospheric columns
53  integer,intent(in) :: nlay ! # of atmospheric layers
54  integer,intent(in) :: nq
55  integer :: day_ini
56  real :: time0
57
58!  outputs:
59  real,intent(out) :: tsurf(ngrid) ! surface temperature
60  real,intent(out) :: tsoil(ngrid,nsoil) ! soil temperature
61  real,intent(out) :: albedo(ngrid,2) ! surface albedo
62  real,intent(out) :: emis(ngrid) ! surface emissivity
63  real,intent(out) :: q2(ngrid,nlay+1) !
64  real,intent(out) :: qsurf(ngrid,nq) ! tracers on surface
65  real,intent(out) :: tauscaling(ngrid) ! dust conversion factor
66  real,intent(out) :: totcloudfrac(ngrid) ! total cloud fraction
67  real,intent(out) :: wstar(ngrid) ! Max vertical velocity in thermals (m/s)
68  real,intent(out) :: watercap(ngrid) ! h2o_ice_cover
69!======================================================================
70!  Local variables:
71
72      real surffield(ngrid) ! to temporarily store a surface field
73      real xmin,xmax ! to display min and max of a field
74!
75      INTEGER ig,iq,lmax
76      INTEGER nid, nvarid
77      INTEGER ierr, i, nsrf
78!      integer isoil
79!      INTEGER length
80!      PARAMETER (length=100)
81      CHARACTER*7 str7
82      CHARACTER*2 str2
83      CHARACTER*1 yes
84!
85      REAL p_rad,p_omeg,p_g,p_mugaz,p_daysec
86      INTEGER nqold
87
88! flag which identifies if 'startfi.nc' file is using old names (qsurf01,...)
89      logical :: oldtracernames=.false.
90      integer :: count
91      character(len=30) :: txt ! to store some text
92
93! specific for time
94      REAL,ALLOCATABLE :: time(:) ! times stored in start
95      INTEGER timelen ! number of times stored in the file
96      INTEGER indextime ! index of selected time
97
98      INTEGER :: edges(3),corner(3)
99      LOGICAL :: found
100
101      REAL :: timestart ! to pick which initial state to start from
102      REAL :: surfemis  ! constant emissivity when no startfi
103      REAL :: surfalbedo  ! constant albedo when no startfi
104      CHARACTER(len=5) :: modname="phyetat0"
105
106write(*,*) "phyetat0: startphy_file", startphy_file
107
108if (startphy_file) then
109   ! open physics initial state file:
110   call open_startphy(fichnom)
111   ! possibility to modify tab_cntrl in tabfi
112   write(*,*)
113   write(*,*) 'TABFI in phyeta0: Lmodif=',Lmodif," tab0=",tab0
114   call tabfi (nid_start,Lmodif,tab0,day_ini,lmax,p_rad, &
115               p_omeg,p_g,p_mugaz,p_daysec,time0)
116else ! "academic" initialization of planetary parameters via tabfi
117   call tabfi (0,0,0,day_ini,lmax,p_rad, &
118               p_omeg,p_g,p_mugaz,p_daysec,time0)
119endif ! of if (startphy_file)
120
121if (startphy_file) then
122   ! Load surface geopotential:
123   call get_field("phisfi",phisfi,found)
124   if (.not.found) then
125     call abort_physic(modname, &
126                "phyetat0: Failed loading <phisfi>",1)
127   endif
128else
129  phisfi(:)=0.
130endif ! of if (startphy_file)
131write(*,*) "phyetat0: surface geopotential <phisfi> range:", &
132               minval(phisfi), maxval(phisfi)
133
134
135if (startphy_file) then
136   ! Load bare ground albedo:
137   call get_field("albedodat",albedodat,found)
138   if (.not.found) then
139     call abort_physic(modname, &
140                "phyetat0: Failed loading <albedodat>",1)
141   endif
142else ! If no startfi file, use parameter surfalbedo in def file
143  surfalbedo=0.1
144  call getin_p("surfalbedo_without_startfi",surfalbedo)
145  print*,"surfalbedo_without_startfi",surfalbedo
146  albedodat(:)=surfalbedo
147endif ! of if (startphy_file)
148write(*,*) "phyetat0: Bare ground albedo <albedodat> range:", &
149             minval(albedodat), maxval(albedodat)
150
151! ZMEA
152if (startphy_file) then
153   call get_field("ZMEA",zmea,found)
154   if (.not.found) then
155     call abort_physic(modname, &
156                "phyetat0: Failed loading <ZMEA>",1)
157   endif
158else
159  zmea(:)=0.
160endif ! of if (startphy_file)
161write(*,*) "phyetat0: <ZMEA> range:", &
162            minval(zmea), maxval(zmea)
163
164
165! ZSTD
166if (startphy_file) then
167   call get_field("ZSTD",zstd,found)
168   if (.not.found) then
169     call abort_physic(modname, &
170                "phyetat0: Failed loading <ZSTD>",1)
171   endif
172else
173  zstd(:)=0.
174endif ! of if (startphy_file)
175write(*,*) "phyetat0: <ZSTD> range:", &
176            minval(zstd), maxval(zstd)
177
178
179! ZSIG
180if (startphy_file) then
181   call get_field("ZSIG",zsig,found)
182   if (.not.found) then
183     call abort_physic(modname, &
184                "phyetat0: Failed loading <ZSIG>",1)
185   endif
186else
187  zsig(:)=0.
188endif ! of if (startphy_file)
189write(*,*) "phyetat0: <ZSIG> range:", &
190            minval(zsig), maxval(zsig)
191
192
193! ZGAM
194if (startphy_file) then
195   call get_field("ZGAM",zgam,found)
196   if (.not.found) then
197     call abort_physic(modname, &
198                "phyetat0: Failed loading <ZGAM>",1)
199   endif
200else
201  zgam(:)=0.
202endif ! of if (startphy_file)
203write(*,*) "phyetat0: <ZGAM> range:", &
204            minval(zgam), maxval(zgam)
205
206
207! ZTHE
208if (startphy_file) then
209   call get_field("ZTHE",zthe,found)
210   if (.not.found) then
211     call abort_physic(modname, &
212                "phyetat0: Failed loading <ZTHE>",1)
213   endif
214else
215  zthe(:)=0.
216endif ! of if (startphy_file)
217write(*,*) "phyetat0: <ZTHE> range:", &
218             minval(zthe), maxval(zthe)
219
220! hmons
221if (startphy_file) then
222   call get_field("hmons",hmons,found)
223   if (.not.found) then
224     write(*,*) "WARNING: phyetat0: Failed loading <hmons>"
225     if (rdstorm) then
226     call abort_physic(modname, &
227                "phyetat0: Failed loading <hmons>",1)
228     else
229       write(*,*) "will continue anyway..."
230       write(*,*) "because you may not need it."
231       hmons(:)=0.
232     end if ! if (rdstorm)
233   else
234     do ig=1,ngrid
235       if (hmons(ig) .eq. -999999.)  hmons(ig)=0.
236     enddo
237   endif ! (.not.found)
238else
239   hmons(:)=0.
240endif ! if (startphy_file)
241write(*,*) "phyetat0: <hmons> range:", &
242            minval(hmons), maxval(hmons)
243
244
245! summit
246if (startphy_file) then
247   call get_field("summit",summit,found)
248   if (.not.found) then
249     write(*,*) "WARNING: phyetat0: Failed loading <summit>"
250     if (rdstorm) then
251     call abort_physic(modname, &
252                "phyetat0: Failed loading <summit>",1)
253     else
254       write(*,*) "will continue anyway..."
255       write(*,*) "because you may not need it."
256       summit(:)=0.
257     end if
258   else
259     do ig=1,ngrid
260       if (summit(ig) .eq. -999999.)  summit(ig)=0.
261     enddo
262   endif ! if (.not.found)
263else
264   summit(:)=0. 
265endif ! if (startphy_file)
266write(*,*) "phyetat0: <summit> range:", &
267            minval(summit), maxval(summit)
268
269
270! base
271if (startphy_file) then
272   call get_field("base",base,found)
273   if (.not.found) then
274     write(*,*) "WARNING: phyetat0: Failed loading <base>"
275     if (rdstorm) then
276     call abort_physic(modname, &
277                "phyetat0: Failed loading <base>",1)
278     else
279       write(*,*) "will continue anyway..."
280       write(*,*) "because you may not need it."
281       base(:)=0.
282     end if
283   else
284     do ig=1,ngrid
285       if (base(ig) .eq. -999999.)  base(ig)=0.
286     enddo
287   endif ! if(.not.found)
288else
289   base(:)=0.
290endif ! if (startphy_file)
291write(*,*) "phyetat0: <base> range:", &
292            minval(base), maxval(base)
293
294! Time axis
295! obtain timestart from run.def
296timestart=-9999 ! default value
297call getin_p("timestart",timestart)
298if (startphy_file) then
299   found=inquire_dimension("Time")
300   if (.not.found) then
301     indextime = 1
302     write(*,*) "phyetat0: No time axis found in "//trim(fichnom)
303   else
304     write(*,*) "phyetat0: Time axis found in "//trim(fichnom)
305     timelen=inquire_dimension_length("Time")
306     allocate(time(timelen))
307     ! load "Time" array:
308     call get_var("Time",time,found)
309     if (.not.found) then
310     call abort_physic(modname, &
311                "phyetat0: Failed loading <Time>",1)
312     endif
313     ! seclect the desired time index
314     IF (timestart .lt. 0) THEN  ! default: we use the last time value
315       indextime = timelen
316     ELSE  ! else we look for the desired value in the time axis
317       indextime = 0
318       DO i=1,timelen
319         IF (abs(time(i) - timestart) .lt. 0.01) THEN
320           indextime = i
321           EXIT
322         ENDIF
323       ENDDO
324       IF (indextime .eq. 0) THEN
325         PRINT*, "Time", timestart," is not in "//trim(fichnom)//"!!"
326         PRINT*, "Stored times are:"
327         DO i=1,timelen
328            PRINT*, time(i)
329         ENDDO
330         call abort_physic(modname,"phyetat0: Time error",1)
331       ENDIF
332     ENDIF ! of IF (timestart .lt. 0)
333     ! In startfi the absolute date is day_ini + time0 + time
334     ! For now on, in the GCM physics, it is day_ini + time0
335     time0 = time(indextime) + time0
336     day_ini = day_ini + INT(time0)
337     time0 = time0 - INT(time0)   
338     PRINT*, "phyetat0: Selected time ",time(indextime), &
339             " at index ",indextime
340     DEALLOCATE(time)
341   endif ! of if Time not found in file
342
343   call ini_tab_controle_dyn_xios(day_ini)
344
345else
346  indextime = 1
347endif ! if (startphy_file)
348
349! Dust conversion factor
350if (startphy_file) then
351   call get_field("tauscaling",tauscaling,found,indextime)
352   if (.not.found) then
353     write(*,*) "phyetat0: <tauscaling> not in file"
354     tauscaling(:) = 1
355   endif
356else
357   tauscaling(:) = 1
358endif ! if (startphy_file)
359write(*,*) "phyetat0: dust conversion factor <tauscaling> range:", &
360            minval(tauscaling), maxval(tauscaling)
361
362! dust_rad_adjust_* for radiative rescaling of dust
363if (dustscaling_mode==2) then
364 if (startphy_file) then
365   call get_field("dust_rad_adjust_prev",dust_rad_adjust_prev,found,indextime)
366   if (.not.found) then
367     write(*,*) "phyetat0: <dust_rad_adjust_prev> not in file; set to 1"
368     dust_rad_adjust_prev(:) = 1
369   endif
370   call get_field("dust_rad_adjust_next",dust_rad_adjust_next,found,indextime)
371   if (.not.found) then
372     write(*,*) "phyetat0: <dust_rad_adjust_next> not in file; set to 1"
373     dust_rad_adjust_next(:) = 1
374   endif
375 else
376   dust_rad_adjust_prev(:)= 0
377   dust_rad_adjust_next(:)= 0
378 endif ! if (startphy_file)
379 write(*,*) "phyetat0: radiative scaling coeff <dust_rad_adjust_prev> range:", &
380            minval(dust_rad_adjust_prev), maxval(dust_rad_adjust_prev)
381 write(*,*) "phyetat0: radiative scaling coeff <dust_rad_adjust_next> range:", &
382            minval(dust_rad_adjust_next), maxval(dust_rad_adjust_next)
383endif ! of if (dustscaling_mode==2)
384
385! dtau: opacity difference between GCM and dust scenario
386if (startphy_file) then
387   call get_field("dtau",dtau,found,indextime)
388   if (.not.found) then
389     write(*,*) "phyetat0: <dtau> not in file; set to zero"
390     dtau(:) = 0
391   endif
392else
393   dtau(:)= 0
394endif ! if (startphy_file)
395write(*,*) "phyetat0: opacity diff wrt scenario <dtau> range:", &
396            minval(dtau), maxval(dtau)
397
398
399! Sub-grid cloud fraction
400if (startphy_file) then
401   call get_field("totcloudfrac",totcloudfrac,found,indextime)
402   if (.not.found) then
403     write(*,*) "phyetat0: <totcloudfrac> not in file WARNING put to 1"
404     totcloudfrac(:) = 1.0 !valeur par defaut (CLFfixval par defaut)
405   endif
406else
407   totcloudfrac(:)=1.0
408endif ! if (startphy_file)
409write(*,*) "phyetat0: total cloud fraction <totcloudfrac> range:", &
410            minval(totcloudfrac), maxval(totcloudfrac)
411
412
413! Max vertical velocity in thermals
414if (startphy_file) then
415   call get_field("wstar",wstar,found,indextime)
416   if (.not.found) then
417     write(*,*) "phyetat0: <wstar> not in file! Set to zero"
418     wstar(:)=0
419   endif
420else
421   wstar(:)=0
422endif ! if (startphy_file)
423write(*,*) "phyetat0: Max vertical velocity in thermals <wstar> range:", &
424            minval(wstar),maxval(wstar)
425
426
427! Surface temperature :
428if (startphy_file) then !tsurf
429   call get_field("tsurf",tsurf,found,indextime)
430   if (.not.found) then
431     call abort_physic(modname, &
432                "phyetat0: Failed loading <tsurf>",1)
433   endif
434else
435  tsurf(:)=0. ! will be updated afterwards in physiq !
436endif ! of if (startphy_file)
437write(*,*) "phyetat0: Surface temperature <tsurf> range:", &
438            minval(tsurf), maxval(tsurf)
439
440! Surface albedo
441if (startphy_file) then
442   call get_field("albedo",albedo(:,1),found,indextime)
443   if (.not.found) then
444     write(*,*) "phyetat0: Failed loading <albedo>"
445     albedo(:,1)=albedodat(:)
446   endif
447else
448   albedo(:,1)=albedodat(:)
449endif ! of if (startphy_file)
450write(*,*) "phyetat0: Surface albedo <albedo> range:", &
451            minval(albedo(:,1)), maxval(albedo(:,1))
452albedo(:,2)=albedo(:,1)
453
454! Surface emissivity
455if (startphy_file) then
456   call get_field("emis",emis,found,indextime)
457   if (.not.found) then
458     call abort_physic(modname, &
459                "phyetat0: Failed loading <emis>",1)
460   endif
461else
462  ! If no startfi file, use parameter surfemis in def file
463  surfemis=0.95
464  call getin_p("surfemis_without_startfi",surfemis)
465  print*,"surfemis_without_startfi",surfemis
466  emis(:)=surfemis
467endif ! of if (startphy_file)
468write(*,*) "phyetat0: Surface emissivity <emis> range:", &
469            minval(emis), maxval(emis)
470
471
472! surface roughness length (NB: z0 is a common in surfdat_h)
473if (startphy_file) then
474   call get_field("z0",z0,found)
475   if (.not.found) then
476     write(*,*) "phyetat0: Failed loading <z0>"
477     write(*,*) 'will use constant value of z0_default:',z0_default
478     z0(:)=z0_default
479   endif
480else
481   z0(:)=z0_default
482endif ! of if (startphy_file)
483write(*,*) "phyetat0: Surface roughness <z0> range:", &
484            minval(z0), maxval(z0)
485
486
487! pbl wind variance
488if (startphy_file) then
489   call get_field("q2",q2,found,indextime)
490   if (.not.found) then
491     call abort_physic(modname, &
492                "phyetat0: Failed loading <q2>",1)
493   endif
494else
495  q2(:,:)=0.
496endif ! of if (startphy_file)
497write(*,*) "phyetat0: PBL wind variance <q2> range:", &
498            minval(q2), maxval(q2)
499
500! Non-orographic gravity waves
501if (startphy_file) then
502   call get_field("du_nonoro_gwd",du_nonoro_gwd,found,indextime)
503   if (.not.found) then
504      write(*,*) "phyetat0: <du_nonoro_gwd> not in file"
505      du_nonoro_gwd(:,:)=0.
506   endif
507else
508du_nonoro_gwd(:,:)=0.
509endif ! if (startphy_file)
510write(*,*) "phyetat0: Memory of zonal wind tendency due to non-orographic GW"
511write(*,*) " <du_nonoro_gwd> range:", &
512             minval(du_nonoro_gwd), maxval(du_nonoro_gwd)
513
514if (startphy_file) then
515   call get_field("dv_nonoro_gwd",dv_nonoro_gwd,found,indextime)
516   if (.not.found) then
517      write(*,*) "phyetat0: <dv_nonoro_gwd> not in file"
518      dv_nonoro_gwd(:,:)=0.
519   endif
520else ! ! if (startphy_file)
521dv_nonoro_gwd(:,:)=0.
522endif ! if (startphy_file)
523write(*,*) "phyetat0: Memory of meridional wind tendency due to non-orographic GW"
524write(*,*) " <dv_nonoro_gwd> range:", &
525             minval(dv_nonoro_gwd), maxval(dv_nonoro_gwd)
526
527! tracer on surface
528if (nq.ge.1) then
529  do iq=1,nq
530    txt=noms(iq)
531    if (txt.eq."h2o_vap") then
532      ! There is no surface tracer for h2o_vap;
533      ! "h2o_ice" should be loaded instead
534      txt="h2o_ice"
535      write(*,*) 'phyetat0: loading surface tracer', &
536                           ' h2o_ice instead of h2o_vap'
537      write(*,*) 'iq = ', iq
538    endif
539
540    if (hdo) then
541    if (txt.eq."hdo_vap") then
542      txt="hdo_ice"
543      write(*,*) 'phyetat0: loading surface tracer', &
544                           ' hdo_ice instead of hdo_vap'
545    endif
546    endif !hdo
547
548    if (startphy_file) then
549      if (txt.eq."co2") then
550        ! We first check if co2ice exist in the startfi file (old way)
551        ! CO2 ice cover
552        call get_field("co2ice",qsurf(:,iq),found,indextime)
553        ! If not, we load the corresponding tracer in qsurf
554        if (.not.found) then
555          call get_field(txt,qsurf(:,iq),found,indextime)
556          if (.not.found) then
557            call abort_physic(modname, &
558                "phyetat0: Failed loading co2ice. there is neither the variable co2ice nor qsurf",1)
559          endif
560        endif
561      else ! (not the co2 tracer)
562        call get_field(txt,qsurf(:,iq),found,indextime)
563        if (.not.found) then
564          write(*,*) "phyetat0: Failed loading <",trim(txt),">"
565          write(*,*) "         ",trim(txt)," is set to zero"
566          qsurf(:,iq)=0.
567        endif
568      endif !endif co2
569    else !(not startphy_file)
570      qsurf(:,iq)=0.
571    endif ! of if (startphy_file)
572    write(*,*) "phyetat0: Surface tracer <",trim(txt),"> range:", &
573                 minval(qsurf(:,iq)), maxval(qsurf(:,iq))
574  enddo ! of do iq=1,nq
575
576    if (txt.eq."co2") then
577      ! We first check if co2ice exist in the startfi file (old way)
578      ! CO2 ice cover
579      if (startphy_file) then
580        call get_field("co2ice",qsurf(:,iq),found,indextime)
581      ! If not, we load the corresponding tracer in qsurf
582        if (.not.found) then
583          call get_field(txt,qsurf(:,iq),found,indextime)
584          if (.not.found) then
585            call abort_physic(modname, &
586                "phyetat0: Failed loading co2ice",1)
587          endif
588        endif
589      else
590       ! If we run without startfile, co2ice is set to 0
591        qsurf(:,iq)=0.
592      endif !if (startphy_file)
593        write(*,*) "phyetat0: CO2 ice cover <co2ice> range:", &
594            minval(qsurf(:,iq)), maxval(qsurf(:,iq))
595    endif
596
597endif ! of if (nq.ge.1)
598
599if (startphy_file) then
600   call get_field("watercap",watercap,found,indextime)
601   if (.not.found) then
602     write(*,*) "phyetat0: Failed loading <watercap> : ", &
603                          "<watercap> is set to zero"
604     watercap(:)=0
605
606     write(*,*) 'Now transfer negative surface water ice to', &
607                ' watercap !'
608     if (nq.ge.1) then
609      do iq=1,nq
610       txt=noms(iq)
611       if (txt.eq."h2o_ice") then
612         do ig=1,ngrid
613          if (qsurf(ig,iq).lt.0.0) then
614             watercap(ig) = qsurf(ig,iq)
615             qsurf(ig,iq) = 0.0
616          end if
617         end do
618       endif
619
620       if (txt.eq."hdo_ice") then
621         do ig=1,ngrid
622          if (qsurf(ig,iq).lt.0.0) then
623             qsurf(ig,iq) = 0.0
624          end if
625         end do
626       endif
627
628      enddo
629     endif ! of if (nq.ge.1)
630   endif ! of if (.not.found)
631else
632   watercap(:)=0
633endif ! of if (startphy_file)
634write(*,*) "phyetat0: Surface water ice <watercap> range:", &
635            minval(watercap), maxval(watercap)
636 
637
638
639if (startphy_file) then
640  ! Call to soil_settings, in order to read soil temperatures,
641  ! as well as thermal inertia and volumetric heat capacity
642  call soil_settings(nid_start,ngrid,nsoil,tsurf,tsoil,indextime)
643endif ! of if (startphy_file)
644!
645! close file:
646!
647if (startphy_file) call close_startphy
648
649end subroutine phyetat0
650
651
652subroutine ini_tab_controle_dyn_xios(idayref)
653
654      USE comcstfi_h, only: g, mugaz, omeg, rad, rcp
655      USE time_phylmdz_mod, ONLY: hour_ini, daysec, dtphys
656      USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev
657      IMPLICIT NONE
658
659
660      INTEGER*4,intent(in) :: idayref  ! date (initial date for this run)
661
662
663      INTEGER length,l
664      parameter (length = 100)
665      REAL tab_cntrl(length) ! run parameters are stored in this array
666
667      DO l=1,length
668         tab_cntrl(l)=0.
669      ENDDO
670      tab_cntrl(1)  = real(nbp_lon)
671      tab_cntrl(2)  = real(nbp_lat-1)
672      tab_cntrl(3)  = real(nbp_lev)
673      tab_cntrl(4)  = real(idayref)
674      tab_cntrl(5)  = rad
675      tab_cntrl(6)  = omeg
676      tab_cntrl(7)  = g
677      tab_cntrl(8)  = mugaz
678      tab_cntrl(9)  = rcp
679      tab_cntrl(10) = daysec
680      tab_cntrl(11) = dtphys
681
682      tab_cntrl(27) = hour_ini
683
684      tab_cntrl_mod = tab_cntrl
685
686end subroutine ini_tab_controle_dyn_xios
687
688end module phyetat0_mod
Note: See TracBrowser for help on using the repository browser.