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

Last change on this file since 4025 was 3935, checked in by jliu, 3 months ago

#Non-orographic gravity waves and induced turbulence
#are added to the model. Further tunning are still needed.

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