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

Last change on this file since 1660 was 1621, checked in by emillour, 8 years ago

Further work on full dynamics/physics separation.

LMDZ.COMMON:

  • added phy_common/vertical_layers_mod.F90 to store information on vertical grid. This is where routines in the physics should get the information.
  • The contents of vertical_layers_mod intialized via dynphy_lonlat/inigeomphy_mod.F90.

LMDZ.MARS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • created an "ini_tracer_mod" routine in module "tracer_mod" for a cleaner initialization of the later.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.GENERIC:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added nqtot to tracer_h.F90.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.VENUS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics. Initialized via iniphysiq. IMPORTANT: there are some hard-coded constants! These should match what is in cpdet_mod.F90 in the dynamics.
  • got rid of references to moyzon_mod module within the physics. The required variables (tmoy, plevmoy) are passed to the physics as arguments to physiq.

LMDZ.TITAN:

  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics.
  • Extra work required to completely decouple physics and dynamics: moyzon_mod should be cleaned up and information passed from dynamics to physics as as arguments. Likewise moyzon_ch and moyzon_mu should not be queried from logic_mod (which is in the dynamics).

EM

File size: 9.0 KB
RevLine 
[1130]1subroutine phyetat0 (fichnom,tab0,Lmodif,nsoil,ngrid,nlay,nq, &
[1208]2                     day_ini,time0,tsurf,tsoil,emis,q2,qsurf,co2ice, &
3                     tauscaling)
[1130]4!  use netcdf
[1621]5  use tracer_mod, only: noms ! tracer names
[1130]6  use surfdat_h, only: phisfi, albedodat, z0, z0_default,&
7                       zmea, zstd, zsig, zgam, zthe
8  use iostart, only: nid_start, open_startphy, close_startphy, &
9                     get_field, get_var, inquire_field, &
10                     inquire_dimension, inquire_dimension_length
[1525]11  use ioipsl_getincom, only : getin
[1226]12
[1130]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  INTEGER nbsrf !Mars nbsrf a 1 au lieu de 4
25  PARAMETER (nbsrf=1) ! nombre de sous-fractions pour une maille
26!======================================================================
27!  Arguments:
28!  ---------
29!  inputs:
30  character*(*),intent(in) :: fichnom ! "startfi.nc" file
31  integer,intent(in) :: tab0
32  integer,intent(in) :: Lmodif
33  integer,intent(in) :: nsoil ! # of soil layers
34  integer,intent(in) :: ngrid ! # of atmospheric columns
35  integer,intent(in) :: nlay ! # of atmospheric layers
36  integer,intent(in) :: nq
37  integer :: day_ini
38  real :: time0
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,nlay+1) !
45  real,intent(out) :: qsurf(ngrid,nq) ! tracers on surface
46  real,intent(out) :: co2ice(ngrid) ! co2 ice cover
[1208]47  real,intent(out) :: tauscaling(ngrid) ! dust conversion factor
[1130]48
49!======================================================================
50!  Local variables:
51
52      real surffield(ngrid) ! to temporarily store a surface field
53      real xmin,xmax ! to display min and max of a field
54!
55      INTEGER ig,iq,lmax
56      INTEGER nid, nvarid
57      INTEGER ierr, i, nsrf
58!      integer isoil
59!      INTEGER length
60!      PARAMETER (length=100)
61      CHARACTER*7 str7
62      CHARACTER*2 str2
63      CHARACTER*1 yes
64!
65      REAL p_rad,p_omeg,p_g,p_mugaz,p_daysec
66      INTEGER nqold
67
68! flag which identifies if 'startfi.nc' file is using old names (qsurf01,...)
69      logical :: oldtracernames=.false.
70      integer :: count
71      character(len=30) :: txt ! to store some text
72
73! specific for time
74      REAL,ALLOCATABLE :: time(:) ! times stored in start
75      INTEGER timelen ! number of times stored in the file
76      INTEGER indextime ! index of selected time
77
78      INTEGER :: edges(3),corner(3)
79      LOGICAL :: found
80
[1525]81      REAL :: timestart ! to pick which initial state to start from
82
[1130]83! open physics initial state file:
84call open_startphy(fichnom)
85
86
87! possibility to modify tab_cntrl in tabfi
88write(*,*)
89write(*,*) 'TABFI in phyeta0: Lmodif=',Lmodif," tab0=",tab0
90call tabfi (nid_start,Lmodif,tab0,day_ini,lmax,p_rad, &
91            p_omeg,p_g,p_mugaz,p_daysec,time0)
92
93
94! Load surface geopotential:
95call get_field("phisfi",phisfi,found)
96if (.not.found) then
97  write(*,*) "phyetat0: Failed loading <phisfi>"
98  call abort
99else
100  write(*,*) "phyetat0: surface geopotential <phisfi> range:", &
101             minval(phisfi), maxval(phisfi)
102endif
103
104
105! Load bare ground albedo:
106call get_field("albedodat",albedodat,found)
107if (.not.found) then
108  write(*,*) "phyetat0: Failed loading <albedodat>"
109  call abort
110else
111  write(*,*) "phyetat0: Bare ground albedo <albedodat> range:", &
112             minval(albedodat), maxval(albedodat)
113endif
114
115! ZMEA
116call get_field("ZMEA",zmea,found)
117if (.not.found) then
118  write(*,*) "phyetat0: Failed loading <ZMEA>"
119  call abort
120else
121  write(*,*) "phyetat0: <ZMEA> range:", &
122             minval(zmea), maxval(zmea)
123endif
124
125
126! ZSTD
127call get_field("ZSTD",zstd,found)
128if (.not.found) then
129  write(*,*) "phyetat0: Failed loading <ZSTD>"
130  call abort
131else
132  write(*,*) "phyetat0: <ZSTD> range:", &
133             minval(zstd), maxval(zstd)
134endif
135
136
137! ZSIG
138call get_field("ZSIG",zsig,found)
139if (.not.found) then
140  write(*,*) "phyetat0: Failed loading <ZSIG>"
141  call abort
142else
143  write(*,*) "phyetat0: <ZSIG> range:", &
144             minval(zsig), maxval(zsig)
145endif
146
147
148! ZGAM
149call get_field("ZGAM",zgam,found)
150if (.not.found) then
151  write(*,*) "phyetat0: Failed loading <ZGAM>"
152  call abort
153else
154  write(*,*) "phyetat0: <ZGAM> range:", &
155             minval(zgam), maxval(zgam)
156endif
157
158
159! ZTHE
160call get_field("ZTHE",zthe,found)
161if (.not.found) then
162  write(*,*) "phyetat0: Failed loading <ZTHE>"
163  call abort
164else
165  write(*,*) "phyetat0: <ZTHE> range:", &
166             minval(zthe), maxval(zthe)
167endif
168
169     
170! Time axis
[1525]171! obtain timestart from run.def
172timestart=-9999 ! default value
173call getin("timestart",timestart)
174
[1130]175found=inquire_dimension("Time")
176if (.not.found) then
177  indextime = 1
178  write(*,*) "phyetat0: No time axis found in "//trim(fichnom)
179else
180  write(*,*) "phyetat0: Time axis found in "//trim(fichnom)
181  timelen=inquire_dimension_length("Time")
182  allocate(time(timelen))
183  ! load "Time" array:
184  call get_var("Time",time,found)
185  if (.not.found) then
186    write(*,*) "phyetat0: Failed loading <Time>"
187    call abort
188  endif
189  ! seclect the desired time index
190  IF (timestart .lt. 0) THEN  ! default: we use the last time value
191    indextime = timelen
192  ELSE  ! else we look for the desired value in the time axis
193    indextime = 0
194    DO i=1,timelen
195      IF (abs(time(i) - timestart) .lt. 0.01) THEN
196        indextime = i
197        EXIT
198      ENDIF
199    ENDDO
200    IF (indextime .eq. 0) THEN
201      PRINT*, "Time", timestart," is not in "//trim(fichnom)//"!!"
202      PRINT*, "Stored times are:"
203      DO i=1,timelen
204         PRINT*, time(i)
205      ENDDO
206      CALL abort
207    ENDIF
208  ENDIF ! of IF (timestart .lt. 0)
209  ! In startfi the absolute date is day_ini + time0 + time
210  ! For now on, in the GCM physics, it is day_ini + time0
211  time0 = time(indextime) + time0
212  day_ini = day_ini + INT(time0)
213  time0 = time0 - INT(time0)
214       
215  PRINT*, "phyetat0: Selected time ",time(indextime), &
216          " at index ",indextime
217     
218  DEALLOCATE(time)
219endif ! of if Time not found in file
220
221
222! CO2 ice cover
223call get_field("co2ice",co2ice,found,indextime)
224if (.not.found) then
225  write(*,*) "phyetat0: Failed loading <co2ice>"
226  call abort
227else
228  write(*,*) "phyetat0: CO2 ice cover <co2ice> range:", &
229             minval(co2ice), maxval(co2ice)
230endif
231
232
[1208]233! Dust conversion factor
234call get_field("tauscaling",tauscaling,found,indextime)
235if (.not.found) then
236  write(*,*) "phyetat0: <tauscaling> not in file"
237  tauscaling(:) = -1
238else
239  write(*,*) "phyetat0: dust conversion factor <tauscaling> range:", &
240             minval(tauscaling), maxval(tauscaling)
241endif
242
243
[1130]244! Surface temperature :
245call get_field("tsurf",tsurf,found,indextime)
246if (.not.found) then
247  write(*,*) "phyetat0: Failed loading <tsurf>"
248  call abort
249else
250  write(*,*) "phyetat0: Surface temperature <tsurf> range:", &
251             minval(tsurf), maxval(tsurf)
252endif
253
254! Surface emissivity
255call get_field("emis",emis,found,indextime)
256if (.not.found) then
257  write(*,*) "phyetat0: Failed loading <emis>"
258  call abort
259else
260  write(*,*) "phyetat0: Surface emissivity <emis> range:", &
261             minval(emis), maxval(emis)
262endif
263
264
265! surface roughness length (NB: z0 is a common in surfdat_h)
266call get_field("z0",z0,found)
267if (.not.found) then
268  write(*,*) "phyetat0: Failed loading <z0>"
269  write(*,*) 'will use constant value of z0_default:',z0_default
270  z0(:)=z0_default
271else
272  write(*,*) "phyetat0: Surface roughness <z0> range:", &
273             minval(z0), maxval(z0)
274endif
275
276
277! pbl wind variance
278call get_field("q2",q2,found,indextime)
279if (.not.found) then
280  write(*,*) "phyetat0: Failed loading <q2>"
281  call abort
282else
283  write(*,*) "phyetat0: PBL wind variance <q2> range:", &
284             minval(q2), maxval(q2)
285endif
286
287
288! tracer on surface
289if (nq.ge.1) then
290  do iq=1,nq
[1621]291    txt=noms(iq)
[1130]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
313      call soil_settings(nid_start,ngrid,nsoil,tsurf,tsoil,indextime)
314
315!
316! close file:
317!
318      call close_startphy
319
320      END
Note: See TracBrowser for help on using the repository browser.