source: trunk/LMDZ.PLUTO/libf/phypluto/phyetat0_mod.F90 @ 3765

Last change on this file since 3765 was 3736, checked in by afalco, 8 months ago

Pluto: added missing controle descriptor parameters.
Update for restarts from generic (restarts in 1D)
AF

File size: 9.5 KB
Line 
1module phyetat0_mod
2
3implicit none
4
5real, save :: tab_cntrl_mod(100)
6
7integer,save :: nid_start ! NetCDF file identifier for startfi.nc file
8
9!$OMP THREADPRIVATE(tab_cntrl_mod)
10
11
12contains
13
14subroutine phyetat0 (startphy_file, &
15                     ngrid,nlayer,fichnom,tab0,Lmodif,nsoil,nq, &
16                     day_ini,time,tsurf,tsoil, &
17                     emis,q2,qsurf,therm_inertia)
18                    !  ,hice, &
19                    !  rnat,pctsrf_sic)
20                    !  ,tslab,tsea_ice,sea_ice) !AF24
21
22! to use  'getin_p'
23      use ioipsl_getin_p_mod, only: getin_p
24!!
25  use write_field_phy, only: Writefield_phy
26!!
27  use comsoil_h, only: nsoilmx,inertiedat
28  use tabfi_mod, only: tabfi
29  USE tracer_h, ONLY: noms
30  USE surfdat_h, only: phisfi, albedodat, zmea, zstd, zsig, zgam, zthe
31  use iostart, only: nid_start, open_startphy, close_startphy, &
32                     get_field, get_var, inquire_field, &
33                     inquire_dimension, inquire_dimension_length
34  use callkeys_mod, only: surfalbedo,surfemis, callsoil
35  use mod_phys_lmdz_para, only : is_master
36  implicit none
37
38!======================================================================
39!  Arguments:
40!  ---------
41!  inputs:
42  logical,intent(in) :: startphy_file ! .true. if reading start file
43  integer,intent(in) :: ngrid
44  integer,intent(in) :: nlayer
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) :: nq
50  integer,intent(out) :: day_ini
51  real,intent(out) :: time
52
53!  outputs:
54  real,intent(out) :: tsurf(ngrid) ! surface temperature
55  real,intent(out) :: tsoil(ngrid,nsoil) ! soil temperature
56  real,intent(out) :: emis(ngrid) ! surface emissivity
57  real,intent(out) :: q2(ngrid,nlayer+1) !
58  real,intent(out) :: qsurf(ngrid,nq) ! tracers on surface
59  real,intent(out) :: therm_inertia(ngrid,nsoilmx) ! thermal inertia
60! real n2ice(ngrid) ! n2 ice cover
61
62!======================================================================
63!  Local variables:
64
65!      INTEGER radpas
66!      REAL n2_ppm
67!      REAL solaire
68
69      real xmin,xmax ! to display min and max of a field
70!
71      INTEGER ig,iq,lmax
72      INTEGER nid, nvarid
73      INTEGER ierr, i, nsrf
74!      integer isoil
75!      INTEGER length
76!      PARAMETER (length=100)
77      CHARACTER*7 str7
78      CHARACTER*2 str2
79      CHARACTER*1 yes
80!
81      REAL p_rad,p_omeg,p_g,p_cpp,p_mugaz,p_daysec,thermal_inertia_if_no_startfi
82      INTEGER nqold
83
84! flag which identifies if 'startfi.nc' file is using old names (qsurf01,...)
85!      logical :: oldtracernames=.false.
86      integer :: count
87      character(len=30) :: txt ! to store some text
88
89      INTEGER :: indextime=1 ! index of selected time, default value=1
90      logical :: found
91
92      character(len=8) :: modname="phyetat0"
93
94!
95! ALLOCATE ARRAYS IN surfdat_h
96!
97IF (.not. ALLOCATED(albedodat)) ALLOCATE(albedodat(ngrid))
98IF (.not. ALLOCATED(phisfi)) ALLOCATE(phisfi(ngrid))
99IF (.not. ALLOCATED(zmea)) ALLOCATE(zmea(ngrid))
100IF (.not. ALLOCATED(zstd)) ALLOCATE(zstd(ngrid))
101IF (.not. ALLOCATED(zsig)) ALLOCATE(zsig(ngrid))
102IF (.not. ALLOCATED(zgam)) ALLOCATE(zgam(ngrid))
103IF (.not. ALLOCATED(zthe)) ALLOCATE(zthe(ngrid))
104
105if (startphy_file) then
106  ! open physics initial state file:
107  call open_startphy(fichnom, nid_start)
108
109  ! possibility to modify tab_cntrl in tabfi
110  if (is_master) write(*,*)
111  if (is_master) write(*,*) 'TABFI in phyeta0: Lmodif=',Lmodif," tab0=",tab0
112  call tabfi (ngrid,nid_start,Lmodif,tab0,day_ini,lmax,p_rad, &
113                   p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time)
114
115else ! "academic" initialization of planetary parameters via tabfi
116  call tabfi (ngrid,0,0,0,day_ini,lmax,p_rad, &
117                   p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time)
118endif ! of if (startphy_file)
119
120if (startphy_file) then
121  ! Load surface geopotential:
122  call get_field(nid_start,"phisfi",phisfi,found)
123  if (.not.found) then
124    call abort_physic(modname,"Failed loading <phisfi>",1)
125  endif
126else
127  phisfi(:)=0.
128endif ! of if (startphy_file)
129if (is_master) write(*,*) "phyetat0: surface geopotential <phisfi> range:", &
130               minval(phisfi), maxval(phisfi)
131
132if (startphy_file) then
133  ! Load bare ground albedo:
134  call get_field(nid_start,"albedodat",albedodat,found)
135  if (.not.found) then
136    call abort_physic(modname,"Failed loading <albedodat>",1)
137  endif
138else
139  ! If no startfi file, use parameter surfalbedo in def file
140  surfalbedo=0.5
141  call getin_p("surfalbedo",surfalbedo)
142  if (is_master) print*,"surfalbedo",surfalbedo
143  albedodat(:)=surfalbedo
144endif ! of if (startphy_file)
145if (is_master) write(*,*) "phyetat0: Bare ground albedo <albedodat> range:", &
146             minval(albedodat), maxval(albedodat)
147
148! ZMEA
149if (startphy_file) then
150  call get_field(nid_start,"ZMEA",zmea,found)
151  if (.not.found) then
152    call abort_physic(modname,"Failed loading <ZMEA>",1)
153  endif
154else
155  zmea(:)=0.
156endif ! of if (startphy_file)
157if (is_master) write(*,*) "phyetat0: <ZMEA> range:", &
158             minval(zmea), maxval(zmea)
159
160! ZSTD
161if (startphy_file) then
162  call get_field(nid_start,"ZSTD",zstd,found)
163  if (.not.found) then
164    call abort_physic(modname,"Failed loading <ZSTD>",1)
165  endif
166else
167  zstd(:)=0.
168endif ! of if (startphy_file)
169if (is_master) write(*,*) "phyetat0: <ZSTD> range:", &
170             minval(zstd), maxval(zstd)
171
172! ZSIG
173if (startphy_file) then
174  call get_field(nid_start,"ZSIG",zsig,found)
175  if (.not.found) then
176    call abort_physic(modname,"Failed loading <ZSIG>",1)
177  endif
178else
179  zsig(:)=0.
180endif ! of if (startphy_file)
181if (is_master) write(*,*) "phyetat0: <ZSIG> range:", &
182             minval(zsig), maxval(zsig)
183
184! ZGAM
185if (startphy_file) then
186  call get_field(nid_start,"ZGAM",zgam,found)
187  if (.not.found) then
188    call abort_physic(modname,"Failed loading <ZGAM>",1)
189  endif
190else
191  zgam(:)=0.
192endif ! of if (startphy_file)
193if (is_master) write(*,*) "phyetat0: <ZGAM> range:", &
194             minval(zgam), maxval(zgam)
195
196! ZTHE
197if (startphy_file) then
198  call get_field(nid_start,"ZTHE",zthe,found)
199  if (.not.found) then
200    call abort_physic(modname,"Failed loading <ZTHE>",1)
201  endif
202else
203  zthe(:)=0.
204endif ! of if (startphy_file)
205if (is_master) write(*,*) "phyetat0: <ZTHE> range:", &
206             minval(zthe), maxval(zthe)
207
208! Surface temperature :
209if (startphy_file) then
210  call get_field(nid_start,"tsurf",tsurf,found,indextime)
211  if (.not.found) then
212    call abort_physic(modname,"Failed loading <tsurf>",1)
213  endif
214else
215  tsurf(:)=0. ! will be updated afterwards in physiq !
216endif ! of if (startphy_file)
217if (is_master) write(*,*) "phyetat0: Surface temperature <tsurf> range:", &
218             minval(tsurf), maxval(tsurf)
219
220! Surface emissivity
221if (startphy_file) then
222  call get_field(nid_start,"emis",emis,found,indextime)
223  if (.not.found) then
224    call abort_physic(modname,"Failed loading <emis>",1)
225  endif
226else
227  ! If no startfi file, use parameter surfemis in def file
228  surfemis=1.0
229  call getin_p("surfemis",surfemis)
230  if (is_master) print*,"surfemis",surfemis
231  emis(:)=surfemis
232endif ! of if (startphy_file)
233if (is_master) write(*,*) "phyetat0: Surface emissivity <emis> range:", &
234             minval(emis), maxval(emis)
235
236! !AF24 removed ocean stuff
237
238! pbl wind variance
239if (startphy_file) then
240  call get_field(nid_start,"q2",q2,found,indextime)
241  if (.not.found) then
242    call abort_physic(modname,"Failed loading <q2>",1)
243  endif
244else
245  q2(:,:)=0.
246endif ! of if (startphy_file)
247if (is_master) write(*,*) "phyetat0: PBL wind variance <q2> range:", &
248             minval(q2), maxval(q2)
249
250! tracer on surface
251if (nq.ge.1) then
252  do iq=1,nq
253    txt=noms(iq)
254    if (startphy_file) then
255      call get_field(nid_start,txt,qsurf(:,iq),found,indextime)
256      if (.not.found) then
257        write(*,*) "phyetat0: Failed loading <",trim(txt),">"
258        write(*,*) "         ",trim(txt)," is set to zero"
259        qsurf(:,iq) = 0.
260      endif
261    else
262      qsurf(:,iq)=0.
263    endif ! of if (startphy_file)
264    write(*,*) "phyetat0: Surface tracer <",trim(txt),"> range:", &
265                 minval(qsurf(:,iq)), maxval(qsurf(:,iq))
266  enddo! of do iq=1,nq
267endif ! of if (nq.ge.1)
268
269!!call WriteField_phy("in_phyetat0_qsurf",qsurf(1:ngrid,igcm_h2o_gas),1)
270
271if (startphy_file) then
272  ! Call to soil_settings, in order to read soil temperatures,
273  ! as well as thermal inertia and volumetric heat capacity
274  if (callsoil) then
275    call soil_settings(nid_start,ngrid,nsoil,tsurf,tsoil,indextime)
276  endif
277  therm_inertia(:,:) = inertiedat(:,:)
278else
279  thermal_inertia_if_no_startfi=400 ! default value
280  call getin_p("thermal_inertia_if_no_startfi",thermal_inertia_if_no_startfi)
281  therm_inertia(:,:) = thermal_inertia_if_no_startfi
282    !AF24
283endif ! of if (startphy_file)
284!
285! close file:
286!
287if (startphy_file) call close_startphy(nid_start)
288
289end subroutine phyetat0
290
291
292!======================================================================
293subroutine ini_tab_controle_dyn_xios(idayref)
294
295use comcstfi_mod,        only: g, mugaz, omeg, rad, rcp
296use time_phylmdz_mod,  only: daysec, dtphys
297use mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, nbp_lev
298
299implicit none
300
301integer*4, intent(in) :: idayref ! date (initial date for this run)
302
303integer :: length, l
304parameter (length = 100)
305real    :: tab_cntrl(length) ! run parameters are stored in this array
306
307do l = 1,length
308    tab_cntrl(l) = 0.
309enddo
310tab_cntrl(1)  = real(nbp_lon)
311tab_cntrl(2)  = real(nbp_lat-1)
312tab_cntrl(3)  = real(nbp_lev)
313tab_cntrl(4)  = real(idayref)
314tab_cntrl(5)  = rad
315tab_cntrl(6)  = omeg
316tab_cntrl(7)  = g
317tab_cntrl(8)  = mugaz
318tab_cntrl(9)  = rcp
319tab_cntrl(10) = daysec
320tab_cntrl(11) = dtphys
321
322tab_cntrl_mod = tab_cntrl
323
324end subroutine ini_tab_controle_dyn_xios
325
326
327end module phyetat0_mod
Note: See TracBrowser for help on using the repository browser.