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

Last change on this file since 2282 was 2281, checked in by adelavois, 5 years ago

Mars GCM:
Martian physics is now able to start without startfi.nc
Major update for phyetat0_mod and physiq_mod based on what have been done for the Generic physics

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