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

Last change on this file since 3914 was 3910, checked in by tbertrand, 4 months ago

Pluto PCM:

  • adding option to use N2 ice fractional maps (n2frac) read in the startfi.nc
  • adding option in newstart to correct (tsurf and tsoil) for too warm or too cold N2-free (correct_t_non2) or N2-rich (correct_t_n2) patches

TB

File size: 9.2 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, n2frac
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(n2frac)) ALLOCATE(n2frac(ngrid))
94IF (.not. ALLOCATED(phisfi)) ALLOCATE(phisfi(ngrid))
95IF (.not. ALLOCATED(zmea)) ALLOCATE(zmea(ngrid))
96IF (.not. ALLOCATED(zstd)) ALLOCATE(zstd(ngrid))
97IF (.not. ALLOCATED(zsig)) ALLOCATE(zsig(ngrid))
98IF (.not. ALLOCATED(zgam)) ALLOCATE(zgam(ngrid))
99IF (.not. ALLOCATED(zthe)) ALLOCATE(zthe(ngrid))
100
101if (startphy_file) then
102  ! open physics initial state file:
103  call open_startphy(fichnom, nid_start)
104
105  ! possibility to modify tab_cntrl in tabfi
106  if (is_master) write(*,*)
107  if (is_master) write(*,*) 'TABFI in phyeta0: Lmodif=',Lmodif," tab0=",tab0
108  call tabfi (ngrid,nid_start,Lmodif,tab0,day_ini,lmax,p_rad, &
109                   p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time)
110
111else ! "academic" initialization of planetary parameters via tabfi
112  call tabfi (ngrid,0,0,0,day_ini,lmax,p_rad, &
113                   p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time)
114endif ! of if (startphy_file)
115
116if (startphy_file) then
117  ! Load surface geopotential:
118  call get_field(nid_start,"phisfi",phisfi,found)
119  if (.not.found) then
120    call abort_physic(modname,"Failed loading <phisfi>",1)
121  endif
122else
123  phisfi(:)=0.
124endif ! of if (startphy_file)
125if (is_master) write(*,*) "phyetat0: surface geopotential <phisfi> range:", &
126               minval(phisfi), maxval(phisfi)
127
128if (startphy_file) then
129  ! Load bare ground albedo:
130  call get_field(nid_start,"albedodat",albedodat,found)
131  if (.not.found) then
132    call abort_physic(modname,"Failed loading <albedodat>",1)
133  endif
134else
135  ! If no startfi file, use parameter surfalbedo in def file
136  surfalbedo=0.5
137  call getin_p("surfalbedo",surfalbedo)
138  if (is_master) print*,"surfalbedo",surfalbedo
139  albedodat(:)=surfalbedo
140endif ! of if (startphy_file)
141if (is_master) write(*,*) "phyetat0: Bare ground albedo <albedodat> range:", &
142             minval(albedodat), maxval(albedodat)
143
144!n2frac
145
146if (startphy_file) then
147  ! Load bare ground albedo:
148  call get_field(nid_start,"n2frac",n2frac,found)
149  if (.not.found) then
150    call abort_physic(modname,"Failed loading <n2frac>",1)
151  endif
152else
153  ! If no startfi file, use fixed value to test
154  n2frac(:)=1
155endif ! of if (startphy_file)
156if (is_master) write(*,*) "phyetat0: n2 fraction of ice  <n2frac> range:", &
157             minval(n2frac), maxval(n2frac)
158
159! ZMEA
160if (startphy_file) then
161  call get_field(nid_start,"ZMEA",zmea,found)
162  if (.not.found) then
163    call abort_physic(modname,"Failed loading <ZMEA>",1)
164  endif
165else
166  zmea(:)=0.
167endif ! of if (startphy_file)
168if (is_master) write(*,*) "phyetat0: <ZMEA> range:", &
169             minval(zmea), maxval(zmea)
170
171! ZSTD
172if (startphy_file) then
173  call get_field(nid_start,"ZSTD",zstd,found)
174  if (.not.found) then
175    call abort_physic(modname,"Failed loading <ZSTD>",1)
176  endif
177else
178  zstd(:)=0.
179endif ! of if (startphy_file)
180if (is_master) write(*,*) "phyetat0: <ZSTD> range:", &
181             minval(zstd), maxval(zstd)
182
183! ZSIG
184if (startphy_file) then
185  call get_field(nid_start,"ZSIG",zsig,found)
186  if (.not.found) then
187    call abort_physic(modname,"Failed loading <ZSIG>",1)
188  endif
189else
190  zsig(:)=0.
191endif ! of if (startphy_file)
192if (is_master) write(*,*) "phyetat0: <ZSIG> range:", &
193             minval(zsig), maxval(zsig)
194
195! ZGAM
196if (startphy_file) then
197  call get_field(nid_start,"ZGAM",zgam,found)
198  if (.not.found) then
199    call abort_physic(modname,"Failed loading <ZGAM>",1)
200  endif
201else
202  zgam(:)=0.
203endif ! of if (startphy_file)
204if (is_master) write(*,*) "phyetat0: <ZGAM> range:", &
205             minval(zgam), maxval(zgam)
206
207! ZTHE
208if (startphy_file) then
209  call get_field(nid_start,"ZTHE",zthe,found)
210  if (.not.found) then
211    call abort_physic(modname,"Failed loading <ZTHE>",1)
212  endif
213else
214  zthe(:)=0.
215endif ! of if (startphy_file)
216if (is_master) write(*,*) "phyetat0: <ZTHE> range:", &
217             minval(zthe), maxval(zthe)
218
219! Surface temperature :
220if (startphy_file) then
221  call get_field(nid_start,"tsurf",tsurf,found,indextime)
222  if (.not.found) then
223    call abort_physic(modname,"Failed loading <tsurf>",1)
224  endif
225else
226  tsurf(:)=0. ! will be updated afterwards in physiq !
227endif ! of if (startphy_file)
228if (is_master) write(*,*) "phyetat0: Surface temperature <tsurf> range:", &
229             minval(tsurf), maxval(tsurf)
230
231! Surface emissivity
232if (startphy_file) then
233  call get_field(nid_start,"emis",emis,found,indextime)
234  if (.not.found) then
235    call abort_physic(modname,"Failed loading <emis>",1)
236  endif
237else
238  ! If no startfi file, use parameter surfemis in def file
239  surfemis=1.0
240  call getin_p("surfemis",surfemis)
241  if (is_master) print*,"surfemis",surfemis
242  emis(:)=surfemis
243endif ! of if (startphy_file)
244if (is_master) write(*,*) "phyetat0: Surface emissivity <emis> range:", &
245             minval(emis), maxval(emis)
246
247! !AF24 removed ocean stuff
248
249! pbl wind variance
250if (startphy_file) then
251  call get_field(nid_start,"q2",q2,found,indextime)
252  if (.not.found) then
253    call abort_physic(modname,"Failed loading <q2>",1)
254  endif
255else
256  q2(:,:)=0.
257endif ! of if (startphy_file)
258if (is_master) write(*,*) "phyetat0: PBL wind variance <q2> range:", &
259             minval(q2), maxval(q2)
260
261! tracer on surface
262if (nq.ge.1) then
263  do iq=1,nq
264    txt=noms(iq)
265    if (startphy_file) then
266      call get_field(nid_start,txt,qsurf(:,iq),found,indextime)
267      if (.not.found) then
268        write(*,*) "phyetat0: Failed loading <",trim(txt),">"
269        write(*,*) "         ",trim(txt)," is set to zero"
270        qsurf(:,iq) = 0.
271      endif
272    else
273      qsurf(:,iq)=0.
274    endif ! of if (startphy_file)
275    write(*,*) "phyetat0: Surface tracer <",trim(txt),"> range:", &
276                 minval(qsurf(:,iq)), maxval(qsurf(:,iq))
277  enddo! of do iq=1,nq
278endif ! of if (nq.ge.1)
279
280!!call WriteField_phy("in_phyetat0_qsurf",qsurf(1:ngrid,igcm_h2o_gas),1)
281
282if (startphy_file) then
283  ! Call to soil_settings, in order to read soil temperatures,
284  ! as well as thermal inertia and volumetric heat capacity
285  if (callsoil) then
286    call soil_settings(nid_start,ngrid,nsoil,tsurf,tsoil,indextime)
287  endif
288  therm_inertia(:,:) = inertiedat(:,:)
289else
290  thermal_inertia_if_no_startfi=400 ! default value
291  call getin_p("thermal_inertia_if_no_startfi",thermal_inertia_if_no_startfi)
292  therm_inertia(:,:) = thermal_inertia_if_no_startfi
293    !AF24
294endif ! of if (startphy_file)
295
296call ini_tab_controle_dyn_xios(day_ini)
297!
298! close file:
299!
300if (startphy_file) call close_startphy(nid_start)
301
302end subroutine phyetat0
303
304end module phyetat0_mod
Note: See TracBrowser for help on using the repository browser.