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

Last change on this file since 3812 was 3772, checked in by afalco, 7 months ago

Pluto: allow to write controle in XIOS output.
AF

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