source: dynamico_lmdz/simple_physics/phyparam/dynphy_lonlat/physiq_mod.F90

Last change on this file was 4228, checked in by dubos, 5 years ago

simple_physics : clarify initialization sequence

File size: 7.6 KB
Line 
1! $Id: physiq.F 1565 2011-08-31 12:53:29Z jghattas $
2MODULE physiq_mod
3  USE dimphy, only : klon,klev
4
5  IMPLICIT NONE
6  PRIVATE
7  SAVE
8
9  REAL, PARAMETER :: oneday = 86400. ! hard-coded
10
11  INTEGER :: itau=0 ! counter to count number of calls to physics
12!$OMP THREADPRIVATE(itau)
13  INTEGER :: nid_hist ! NetCDF ID of output file
14!$OMP THREADPRIVATE(nid_hist)
15
16  INTEGER :: iwrite_phys ! output every iwrite_phys physics step
17
18  PUBLIC :: physiq
19
20CONTAINS
21
22  SUBROUTINE physiq (nlon,nlev, &
23       &            debut,lafin,pdtphys, &
24       &            paprs,pplay,pphi,pphis,presnivs, &
25       &            u,v,t,qx, &
26       &            flxmass_w, &
27       &            d_u, d_v, d_t, d_qx, d_ps)
28   
29    USE infotrac_phy, only : nqtot
30    USE iophys,       ONLY : iophys_ini
31    USE phyparam_mod, ONLY : phyparam
32    !
33    ! Routine argument:
34    !
35    integer,intent(in) :: nlon ! number of atmospheric colums
36    integer,intent(in) :: nlev ! number of vertical levels (should be =klev)
37    logical,intent(in) :: debut ! signals first call to physics
38    logical,intent(in) :: lafin ! signals last call to physics
39    real,intent(in) :: pdtphys ! physics time step (s)
40    real,intent(in) :: paprs(klon,klev+1) ! interlayer pressure (Pa)
41    real,intent(in) :: pplay(klon,klev) ! mid-layer pressure (Pa)
42    real,intent(in) :: pphi(klon,klev) ! geopotential at mid-layer
43    real,intent(in) :: pphis(klon) ! surface geopotential
44    real,intent(in) :: presnivs(klev) ! pseudo-pressure (Pa) of mid-layers
45    real,intent(in) :: u(klon,klev) ! eastward zonal wind (m/s)
46    real,intent(in) :: v(klon,klev) ! northward meridional wind (m/s)
47    real,intent(in) :: t(klon,klev) ! temperature (K)
48    real,intent(in) :: qx(klon,klev,nqtot) ! tracers (.../kg_air)
49    real,intent(in) :: flxmass_w(klon,klev) ! vertical mass flux
50    real,intent(out) :: d_u(klon,klev) ! physics tendency on u (m/s/s)
51    real,intent(out) :: d_v(klon,klev) ! physics tendency on v (m/s/s)
52    real,intent(out) :: d_t(klon,klev) ! physics tendency on t (K/s)
53    real,intent(out) :: d_qx(klon,klev,nqtot) ! physics tendency on tracers
54    real,intent(out) :: d_ps(klon) ! physics tendency on surface pressure
55   
56    logical, save :: first=.true.
57    !$OMP THREADPRIVATE(first)
58   
59    ! For I/Os
60    REAL,SAVE :: rjourvrai=0.
61    REAL,SAVE :: gmtime=0.
62    !$OMP THREADPRIVATE(rjourvrai,gmtime)
63       
64    ! initializations
65    if (debut) CALL init_physiq_mod(pdtphys, presnivs) ! Things to do only for the first call to physics
66   
67    ! increment local time counter itau
68    itau=itau+1
69    gmtime=gmtime+pdtphys/oneday
70    IF (gmtime>=1.) THEN
71       gmtime=gmtime-1.
72       rjourvrai=rjourvrai+1.
73    ENDIF
74   
75    IF(debut) CALL iophys_ini('phys.nc    ',presnivs) ! calls iotd_ini
76
77    CALL phyparam(klon,klev,       &
78         debut,lafin,              &
79         rjourvrai,gmtime,pdtphys, &
80         paprs,pplay,pphi,         &
81         u,v,t,                    &
82         d_u,d_v,d_t,d_ps)
83
84    d_qx(:,:,:)=0.
85
86    IF(lafin) THEN
87       call iotd_fin
88       PRINT*,'Ecriture du fichier de reinitialiastion de la physique'
89!       write(75)  tsurf,tsoil FIXME
90    ENDIF
91
92   
93    print*,'PHYDEV: itau=',itau
94
95    CALL write_hist(paprs, t, u, v)      ! write some outputs
96
97    ! if lastcall, then it is time to write "restartphy.nc" file
98    IF (lafin) CALL phyredem("restartphy.nc")
99   
100  END SUBROUTINE physiq
101
102  SUBROUTINE init_physiq_mod(dtime, presnivs)
103    USE iophy, only : histbeg_phy
104    USE phys_state_var_mod, only : phys_state_var_init
105    USE ioipsl, only : getin,histvert,histdef,histend,ymds2ju
106    USE mod_phys_lmdz_para, only : jj_nb
107    USE mod_grid_phy_lmdz, ONLY: nbp_lon,nbp_lat
108    REAL, INTENT(IN) :: dtime
109    REAL, INTENT(IN) :: presnivs(klev) ! pseudo-pressure (Pa) of mid-layers
110
111    ! For I/Os
112    INTEGER, PARAMETER :: itau0=0, annee0=1979, month=1, dayref=1
113    REAL, PARAMETER :: hour=0.0
114    INTEGER :: nid_hori    ! NetCDF ID of horizontal coordinate
115    INTEGER :: nid_vert ! NetCDF ID of vertical coordinate
116    REAL :: t_ops ! frequency of the IOIPSL operations (eg average over...)
117    REAL :: t_wrt ! frequency of the IOIPSL outputs
118    REAL :: zjulian
119
120    ! load initial conditions for physics (including the grid)
121    call phys_state_var_init() ! some initializations, required before calling phyetat0
122    call phyetat0("startphy.nc")
123   
124    ! Initialize outputs:
125
126    ! NB: getin() is not threadsafe; only one thread should call it.
127    !$OMP MASTER
128    iwrite_phys=1 !default: output every physics timestep
129    call getin("iwrite_phys",iwrite_phys)
130    !$OMP END MASTER
131    !$OMP BARRIER
132
133    t_ops=dtime*iwrite_phys ! frequency of the IOIPSL operation
134    t_wrt=dtime*iwrite_phys ! frequency of the outputs in the file
135
136    ! compute zjulian for annee0=1979 and month=1 dayref=1 and hour=0.0
137    CALL ymds2ju(annee0, month, dayref, hour, zjulian)
138#ifndef CPP_IOIPSL_NO_OUTPUT
139    ! Initialize IOIPSL output file
140    call histbeg_phy("histins.nc",itau0,zjulian,dtime,nid_hori,nid_hist)
141#endif
142   
143    !$OMP MASTER
144   
145#ifndef CPP_IOIPSL_NO_OUTPUT
146    ! IOIPSL
147    ! define vertical coordinate
148    call histvert(nid_hist,"presnivs","Vertical levels","Pa",klev, &
149         presnivs,nid_vert,'down')
150    ! define variables which will be written in "histins.nc" file
151    call histdef(nid_hist,'temperature','Atmospheric temperature','K', &
152         nbp_lon,jj_nb,nid_hori,klev,1,klev,nid_vert,32, &
153         'inst(X)',t_ops,t_wrt)
154    call histdef(nid_hist,'u','Eastward Zonal Wind','m/s', &
155         nbp_lon,jj_nb,nid_hori,klev,1,klev,nid_vert,32, &
156         'inst(X)',t_ops,t_wrt)
157    call histdef(nid_hist,'v','Northward Meridional Wind','m/s', &
158         nbp_lon,jj_nb,nid_hori,klev,1,klev,nid_vert,32, &
159         'inst(X)',t_ops,t_wrt)
160    call histdef(nid_hist,'ps','Surface Pressure','Pa', &
161         nbp_lon,jj_nb,nid_hori,1,1,1,nid_vert,32, &
162         'inst(X)',t_ops,t_wrt)
163    ! end definition sequence
164    call histend(nid_hist)
165#endif
166   
167#ifdef CPP_XIOS
168    !XIOS
169    ! Declare available vertical axes to be used in output files:   
170    CALL wxios_add_vaxis("presnivs", klev, presnivs)
171   
172    ! Declare calendar and time step
173    CALL wxios_set_cal(dtime,"earth_360d",1,1,1,0.0,1,1,1,0.0)
174   
175    !Finalize the context:
176    CALL wxios_closedef()
177#endif
178    !$OMP END MASTER
179    !$OMP BARRIER
180  END SUBROUTINE init_physiq_mod
181 
182  SUBROUTINE write_hist(paprs, t, u, v)
183    USE iophy, only : histwrite_phy
184#ifdef CPP_XIOS
185    USE xios, ONLY: xios_update_calendar
186    USE wxios, only: wxios_add_vaxis, wxios_set_cal, wxios_closedef
187    USE iophy, ONLY: histwrite_phy
188#endif
189    REAL, INTENT(IN) :: paprs(klon,klev+1), & ! interlayer pressure (Pa)
190         &              t(klon,klev),       & ! temperature (K)
191         &              u(klon,klev),       & ! eastward zonal wind (m/s)
192         &              v(klon,klev)          ! northward meridional wind (m/s)
193    ! output using IOIPSL
194#ifndef CPP_IOIPSL_NO_OUTPUT
195    if (modulo(itau,iwrite_phys)==0) then
196       call histwrite_phy(nid_hist,.false.,"temperature",itau,t)
197       call histwrite_phy(nid_hist,.false.,"u",itau,u)
198       call histwrite_phy(nid_hist,.false.,"v",itau,v)
199       call histwrite_phy(nid_hist,.false.,"ps",itau,paprs(:,1))
200    endif
201#endif
202   
203    ! output using XIOS
204#ifdef CPP_XIOS
205    !$OMP MASTER
206    !Increment XIOS time
207    CALL xios_update_calendar(itau)
208    !$OMP END MASTER
209    !$OMP BARRIER
210   
211    !Send fields to XIOS: (NB these fields must also be defined as
212    ! <field id="..." /> in iodef.xml to be correctly used
213    CALL histwrite_phy("temperature",t)
214    CALL histwrite_phy("temp_newton",temp_newton)
215    CALL histwrite_phy("u",u)
216    CALL histwrite_phy("v",v)
217    CALL histwrite_phy("ps",paprs(:,1))
218#endif
219   
220  END SUBROUTINE write_hist
221 
222END MODULE physiq_mod
Note: See TracBrowser for help on using the repository browser.