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

Last change on this file since 3026 was 1943, checked in by jvatant, 7 years ago

Add XIOS outputs for chemistry including "*_tot" fields (concat GCM+upper atm : 0->1300km )
Only in pseudo-pressure axis for now, pseudo-altitude TBD.
--JVO

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