source: trunk/LMDZ.TITAN/libf/phytitan/phyetat0_mod.F90 @ 3318

Last change on this file since 3318 was 3318, checked in by slebonnois, 7 months ago

Titan PCM update : optics + microphysics

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