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

Last change on this file since 3917 was 3916, checked in by tbertrand, 3 months ago

Pluto PCM :
Small fix to initialize n2frac in startfi
TB

File size: 9.2 KB
RevLine 
[3184]1module phyetat0_mod
2
3implicit none
4
[3736]5integer,save :: nid_start ! NetCDF file identifier for startfi.nc file
6
[3184]7contains
8
9subroutine phyetat0 (startphy_file, &
10                     ngrid,nlayer,fichnom,tab0,Lmodif,nsoil,nq, &
11                     day_ini,time,tsurf,tsoil, &
[3483]12                     emis,q2,qsurf,therm_inertia)
[3572]13                    !  ,hice, &
[3184]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!!
[3635]22  use comsoil_h, only: nsoilmx,inertiedat
[3772]23  use tabfi_mod, only: tabfi,ini_tab_controle_dyn_xios,tab_cntrl_mod
[3184]24  USE tracer_h, ONLY: noms
[3910]25  USE surfdat_h, only: phisfi, albedodat, zmea, zstd, zsig, zgam, zthe, n2frac
[3184]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
[3504]30  use mod_phys_lmdz_para, only : is_master
[3184]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
[3483]52  real,intent(out) :: q2(ngrid,nlayer+1) !
[3184]53  real,intent(out) :: qsurf(ngrid,nq) ! tracers on surface
[3483]54  real,intent(out) :: therm_inertia(ngrid,nsoilmx) ! thermal inertia
[3184]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
[3483]69!      integer isoil
[3184]70!      INTEGER length
71!      PARAMETER (length=100)
72      CHARACTER*7 str7
73      CHARACTER*2 str2
74      CHARACTER*1 yes
75!
[3502]76      REAL p_rad,p_omeg,p_g,p_cpp,p_mugaz,p_daysec,thermal_inertia_if_no_startfi
[3184]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
[3483]83
[3184]84      INTEGER :: indextime=1 ! index of selected time, default value=1
85      logical :: found
[3483]86
[3184]87      character(len=8) :: modname="phyetat0"
88
89!
90! ALLOCATE ARRAYS IN surfdat_h
91!
92IF (.not. ALLOCATED(albedodat)) ALLOCATE(albedodat(ngrid))
[3910]93IF (.not. ALLOCATED(n2frac)) ALLOCATE(n2frac(ngrid))
[3184]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:
[3736]103  call open_startphy(fichnom, nid_start)
[3184]104
105  ! possibility to modify tab_cntrl in tabfi
[3504]106  if (is_master) write(*,*)
107  if (is_master) write(*,*) 'TABFI in phyeta0: Lmodif=',Lmodif," tab0=",tab0
[3184]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:
[3736]118  call get_field(nid_start,"phisfi",phisfi,found)
[3184]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)
[3504]125if (is_master) write(*,*) "phyetat0: surface geopotential <phisfi> range:", &
[3184]126               minval(phisfi), maxval(phisfi)
127
128if (startphy_file) then
129  ! Load bare ground albedo:
[3736]130  call get_field(nid_start,"albedodat",albedodat,found)
[3184]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)
[3504]138  if (is_master) print*,"surfalbedo",surfalbedo
[3184]139  albedodat(:)=surfalbedo
140endif ! of if (startphy_file)
[3504]141if (is_master) write(*,*) "phyetat0: Bare ground albedo <albedodat> range:", &
[3184]142             minval(albedodat), maxval(albedodat)
143
[3910]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
[3916]150    n2frac(:)=1.
151    !call abort_physic(modname,"Failed loading <n2frac>",1)
[3910]152  endif
153else
154  ! If no startfi file, use fixed value to test
[3916]155  n2frac(:)=1.
[3910]156endif ! of if (startphy_file)
157if (is_master) write(*,*) "phyetat0: n2 fraction of ice  <n2frac> range:", &
158             minval(n2frac), maxval(n2frac)
159
[3184]160! ZMEA
161if (startphy_file) then
[3736]162  call get_field(nid_start,"ZMEA",zmea,found)
[3184]163  if (.not.found) then
164    call abort_physic(modname,"Failed loading <ZMEA>",1)
165  endif
166else
167  zmea(:)=0.
168endif ! of if (startphy_file)
[3504]169if (is_master) write(*,*) "phyetat0: <ZMEA> range:", &
[3184]170             minval(zmea), maxval(zmea)
171
172! ZSTD
173if (startphy_file) then
[3736]174  call get_field(nid_start,"ZSTD",zstd,found)
[3184]175  if (.not.found) then
176    call abort_physic(modname,"Failed loading <ZSTD>",1)
177  endif
178else
179  zstd(:)=0.
180endif ! of if (startphy_file)
[3504]181if (is_master) write(*,*) "phyetat0: <ZSTD> range:", &
[3184]182             minval(zstd), maxval(zstd)
183
184! ZSIG
185if (startphy_file) then
[3736]186  call get_field(nid_start,"ZSIG",zsig,found)
[3184]187  if (.not.found) then
188    call abort_physic(modname,"Failed loading <ZSIG>",1)
189  endif
190else
191  zsig(:)=0.
192endif ! of if (startphy_file)
[3504]193if (is_master) write(*,*) "phyetat0: <ZSIG> range:", &
[3184]194             minval(zsig), maxval(zsig)
195
196! ZGAM
197if (startphy_file) then
[3736]198  call get_field(nid_start,"ZGAM",zgam,found)
[3184]199  if (.not.found) then
200    call abort_physic(modname,"Failed loading <ZGAM>",1)
201  endif
202else
203  zgam(:)=0.
204endif ! of if (startphy_file)
[3504]205if (is_master) write(*,*) "phyetat0: <ZGAM> range:", &
[3184]206             minval(zgam), maxval(zgam)
207
208! ZTHE
209if (startphy_file) then
[3736]210  call get_field(nid_start,"ZTHE",zthe,found)
[3184]211  if (.not.found) then
212    call abort_physic(modname,"Failed loading <ZTHE>",1)
213  endif
214else
215  zthe(:)=0.
216endif ! of if (startphy_file)
[3504]217if (is_master) write(*,*) "phyetat0: <ZTHE> range:", &
[3184]218             minval(zthe), maxval(zthe)
219
220! Surface temperature :
221if (startphy_file) then
[3736]222  call get_field(nid_start,"tsurf",tsurf,found,indextime)
[3184]223  if (.not.found) then
224    call abort_physic(modname,"Failed loading <tsurf>",1)
225  endif
226else
227  tsurf(:)=0. ! will be updated afterwards in physiq !
228endif ! of if (startphy_file)
[3504]229if (is_master) write(*,*) "phyetat0: Surface temperature <tsurf> range:", &
[3184]230             minval(tsurf), maxval(tsurf)
231
232! Surface emissivity
233if (startphy_file) then
[3736]234  call get_field(nid_start,"emis",emis,found,indextime)
[3184]235  if (.not.found) then
236    call abort_physic(modname,"Failed loading <emis>",1)
237  endif
238else
239  ! If no startfi file, use parameter surfemis in def file
240  surfemis=1.0
241  call getin_p("surfemis",surfemis)
[3504]242  if (is_master) print*,"surfemis",surfemis
[3184]243  emis(:)=surfemis
244endif ! of if (startphy_file)
[3504]245if (is_master) write(*,*) "phyetat0: Surface emissivity <emis> range:", &
[3184]246             minval(emis), maxval(emis)
247
248! !AF24 removed ocean stuff
249
250! pbl wind variance
251if (startphy_file) then
[3736]252  call get_field(nid_start,"q2",q2,found,indextime)
[3184]253  if (.not.found) then
254    call abort_physic(modname,"Failed loading <q2>",1)
255  endif
256else
257  q2(:,:)=0.
258endif ! of if (startphy_file)
[3504]259if (is_master) write(*,*) "phyetat0: PBL wind variance <q2> range:", &
[3184]260             minval(q2), maxval(q2)
261
262! tracer on surface
263if (nq.ge.1) then
264  do iq=1,nq
265    txt=noms(iq)
266    if (startphy_file) then
[3736]267      call get_field(nid_start,txt,qsurf(:,iq),found,indextime)
[3184]268      if (.not.found) then
269        write(*,*) "phyetat0: Failed loading <",trim(txt),">"
270        write(*,*) "         ",trim(txt)," is set to zero"
271        qsurf(:,iq) = 0.
272      endif
273    else
274      qsurf(:,iq)=0.
275    endif ! of if (startphy_file)
276    write(*,*) "phyetat0: Surface tracer <",trim(txt),"> range:", &
277                 minval(qsurf(:,iq)), maxval(qsurf(:,iq))
278  enddo! of do iq=1,nq
279endif ! of if (nq.ge.1)
280
[3275]281!!call WriteField_phy("in_phyetat0_qsurf",qsurf(1:ngrid,igcm_h2o_gas),1)
[3184]282
283if (startphy_file) then
284  ! Call to soil_settings, in order to read soil temperatures,
285  ! as well as thermal inertia and volumetric heat capacity
286  if (callsoil) then
287    call soil_settings(nid_start,ngrid,nsoil,tsurf,tsoil,indextime)
288  endif
[3635]289  therm_inertia(:,:) = inertiedat(:,:)
[3483]290else
[3502]291  thermal_inertia_if_no_startfi=400 ! default value
292  call getin_p("thermal_inertia_if_no_startfi",thermal_inertia_if_no_startfi)
293  therm_inertia(:,:) = thermal_inertia_if_no_startfi
[3483]294    !AF24
[3184]295endif ! of if (startphy_file)
[3772]296
297call ini_tab_controle_dyn_xios(day_ini)
[3184]298!
299! close file:
300!
[3736]301if (startphy_file) call close_startphy(nid_start)
[3184]302
303end subroutine phyetat0
304
305end module phyetat0_mod
Note: See TracBrowser for help on using the repository browser.