source: LMDZ5/trunk/libf/phydev/physiq.F90 @ 2261

Last change on this file since 2261 was 2221, checked in by Ehouarn Millour, 10 years ago

Some cleanup: remove (unused) clesph0 from dynamics.
EM

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 7.0 KB
RevLine 
[1615]1! $Id: physiq.F 1565 2011-08-31 12:53:29Z jghattas $
2!#define IO_DEBUG
3
4      SUBROUTINE physiq (nlon,nlev, &
5     &            debut,lafin,jD_cur, jH_cur,pdtphys, &
[2221]6     &            paprs,pplay,pphi,pphis,presnivs, &
[1615]7     &            u,v,t,qx, &
8     &            flxmass_w, &
9     &            d_u, d_v, d_t, d_qx, d_ps &
[2037]10     &            , dudyn)
[1615]11
[1671]12      USE dimphy, only : klon,klev
13      USE infotrac, only : nqtot
14      USE comgeomphy, only : rlatd
15      USE comcstphy, only : rg
[1686]16      USE iophy, only : histbeg_phy,histwrite_phy
17      USE ioipsl, only : getin,histvert,histdef,histend,ymds2ju
18      USE mod_phys_lmdz_para, only : jj_nb
19      USE phys_state_var_mod, only : phys_state_var_init
[1615]20
[1852]21#ifdef CPP_XIOS
[2002]22      USE xios, ONLY: xios_update_calendar
[1897]23      USE wxios, only: wxios_add_vaxis, wxios_set_timestep, wxios_closedef, &
[2002]24                       histwrite_phy
[1852]25#endif
26
[1615]27      IMPLICIT none
28#include "dimensions.h"
29
[1686]30      integer,parameter :: jjmp1=jjm+1-1/jjm
31      integer,parameter :: iip1=iim+1
[1615]32!
[1686]33! Routine argument:
[1615]34!
[1686]35      integer,intent(in) :: nlon ! number of atmospheric colums
36      integer,intent(in) :: nlev ! number of vertical levels (should be =klev)
37      real,intent(in) :: jD_cur ! current day number (Julian day)
38      real,intent(in) :: jH_cur ! current time of day (as fraction of day)
39      logical,intent(in) :: debut ! signals first call to physics
40      logical,intent(in) :: lafin ! signals last call to physics
41      real,intent(in) :: pdtphys ! physics time step (s)
42      real,intent(in) :: paprs(klon,klev+1) ! interlayer pressure (Pa)
43      real,intent(in) :: pplay(klon,klev) ! mid-layer pressure (Pa)
44      real,intent(in) :: pphi(klon,klev) ! geopotential at mid-layer
45      real,intent(in) :: pphis(klon) ! surface geopotential
46      real,intent(in) :: presnivs(klev) ! pseudo-pressure (Pa) of mid-layers
47      real,intent(in) :: u(klon,klev) ! eastward zonal wind (m/s)
48      real,intent(in) :: v(klon,klev) ! northward meridional wind (m/s)
49      real,intent(in) :: t(klon,klev) ! temperature (K)
50      real,intent(in) :: qx(klon,klev,nqtot) ! tracers (.../kg_air)
51      real,intent(in) :: flxmass_w(klon,klev) ! vertical mass flux
52      real,intent(out) :: d_u(klon,klev) ! physics tendency on u (m/s/s)
53      real,intent(out) :: d_v(klon,klev) ! physics tendency on v (m/s/s)
54      real,intent(out) :: d_t(klon,klev) ! physics tendency on t (K/s)
55      real,intent(out) :: d_qx(klon,klev,nqtot) ! physics tendency on tracers
56      real,intent(out) :: d_ps(klon) ! physics tendency on surface pressure
57      real,intent(in) :: dudyn(iim+1,jjmp1,klev) ! Not used
[1615]58
[1686]59integer,save :: itau=0 ! counter to count number of calls to physics
60!$OMP THREADPRIVATE(itau)
[1671]61real :: temp_newton(klon,klev)
[1686]62integer :: k
[1615]63logical, save :: first=.true.
[1671]64!$OMP THREADPRIVATE(first)
[1615]65
[1686]66! For I/Os
67integer :: itau0
68real :: zjulian
69real :: dtime
70integer :: nhori ! horizontal coordinate ID
71integer,save :: nid_hist ! output file ID
72!$OMP THREADPRIVATE(nid_hist)
73integer :: zvertid ! vertical coordinate ID
74integer,save :: iwrite_phys ! output every iwrite_phys physics step
75!$OMP THREADPRIVATE(iwrite_phys)
[1900]76integer,save :: iwrite_phys_omp ! intermediate variable to read iwrite_phys
77                                ! (must be shared by all threads)
[1686]78real :: t_ops ! frequency of the IOIPSL operations (eg average over...)
79real :: t_wrt ! frequency of the IOIPSL outputs
[1615]80
[1671]81! initializations
[1686]82if (debut) then ! Things to do only for the first call to physics
83! load initial conditions for physics (including the grid)
84  call phys_state_var_init() ! some initializations, required before calling phyetat0
85  call phyetat0("startphy.nc")
[1615]86
[1686]87! Initialize outputs:
88  itau0=0
[1759]89!$OMP MASTER
90  iwrite_phys_omp=1 !default: output every physics timestep
91  ! NB: getin() is not threadsafe; only one thread should call it.
92  call getin("iwrite_phys",iwrite_phys_omp)
93!$OMP END MASTER
94!$OMP BARRIER
95  iwrite_phys=iwrite_phys_omp
[1686]96  t_ops=pdtphys*iwrite_phys ! frequency of the IOIPSL operation
97  t_wrt=pdtphys*iwrite_phys ! frequency of the outputs in the file
98  ! compute zjulian for annee0=1979 and month=1 dayref=1 and hour=0.0
99  !CALL ymds2ju(annee0, month, dayref, hour, zjulian)
100  call ymds2ju(1979, 1, 1, 0.0, zjulian)
101  dtime=pdtphys
[2097]102#ifndef CPP_IOIPSL_NO_OUTPUT
[1882]103  ! Initialize IOIPSL output file
[1686]104  call histbeg_phy("histins.nc",itau0,zjulian,dtime,nhori,nid_hist)
[1882]105#endif
[1852]106
[1686]107!$OMP MASTER
[1852]108
[2097]109#ifndef CPP_IOIPSL_NO_OUTPUT
[1882]110! IOIPSL
[1686]111  ! define vertical coordinate
112  call histvert(nid_hist,"presnivs","Vertical levels","Pa",klev, &
113                presnivs,zvertid,'down')
114  ! define variables which will be written in "histins.nc" file
115  call histdef(nid_hist,'temperature','Atmospheric temperature','K', &
116               iim,jj_nb,nhori,klev,1,klev,zvertid,32, &
117               'inst(X)',t_ops,t_wrt)
118  call histdef(nid_hist,'u','Eastward Zonal Wind','m/s', &
119               iim,jj_nb,nhori,klev,1,klev,zvertid,32, &
120               'inst(X)',t_ops,t_wrt)
121  call histdef(nid_hist,'v','Northward Meridional Wind','m/s', &
122               iim,jj_nb,nhori,klev,1,klev,zvertid,32, &
123               'inst(X)',t_ops,t_wrt)
124  call histdef(nid_hist,'ps','Surface Pressure','Pa', &
125               iim,jj_nb,nhori,1,1,1,zvertid,32, &
126               'inst(X)',t_ops,t_wrt)
127  ! end definition sequence
128  call histend(nid_hist)
[1882]129#endif
[1852]130
[1882]131#ifdef CPP_XIOS
[1852]132!XIOS
[2002]133    ! Declare available vertical axes to be used in output files:   
134    !CALL wxios_add_vaxis("presnivs", "dummy-not-used", klev, presnivs)
135    CALL wxios_add_vaxis("presnivs", klev, presnivs)
[1852]136
[2002]137    ! Declare time step length (in s):
[1882]138    CALL wxios_set_timestep(dtime)
[1852]139
[2002]140    !Finalize the context:
[1882]141    CALL wxios_closedef()
[1852]142#endif
[1686]143!$OMP END MASTER
144endif ! of if (debut)
[1615]145
[1882]146! increment local time counter itau
[1686]147itau=itau+1
148
[1671]149! set all tendencies to zero
[1686]150d_u(1:klon,1:klev)=0.
151d_v(1:klon,1:klev)=0.
152d_t(1:klon,1:klev)=0.
153d_qx(1:klon,1:klev,1:nqtot)=0.
154d_ps(1:klon)=0.
[1615]155
[1671]156! compute tendencies to return to the dynamics:
157! "friction" on the first layer
[1686]158d_u(1:klon,1)=-u(1:klon,1)/86400.
159d_v(1:klon,1)=-v(1:klon,1)/86400.
160! newtonian relaxation towards temp_newton()
[1671]161do k=1,klev
[1686]162  temp_newton(1:klon,k)=280.+cos(rlatd(1:klon))*40.-pphi(1:klon,k)/rg*6.e-3
163  d_t(1:klon,k)=(temp_newton(1:klon,k)-t(1:klon,k))/1.e5
[1671]164enddo
165
166
[1897]167print*,'PHYDEV: itau=',itau
[1671]168
[1686]169! write some outputs:
[1882]170! IOIPSL
[2097]171#ifndef CPP_IOIPSL_NO_OUTPUT
[1686]172if (modulo(itau,iwrite_phys)==0) then
173  call histwrite_phy(nid_hist,.false.,"temperature",itau,t)
174  call histwrite_phy(nid_hist,.false.,"u",itau,u)
175  call histwrite_phy(nid_hist,.false.,"v",itau,v)
176  call histwrite_phy(nid_hist,.false.,"ps",itau,paprs(:,1))
177endif
[1882]178#endif
[1686]179
[1852]180!XIOS
181#ifdef CPP_XIOS
182!$OMP MASTER
[1882]183    !Increment XIOS time
[2002]184    CALL xios_update_calendar(itau)
[1897]185!$OMP END MASTER
186!$OMP BARRIER
[1852]187
[2002]188    !Send fields to XIOS: (NB these fields must also be defined as
189    ! <field id="..." /> in iodef.xml to be correctly used
[1882]190    CALL histwrite_phy("temperature",t)
[2002]191    CALL histwrite_phy("temp_newton",temp_newton)
[1882]192    CALL histwrite_phy("u",u)
193    CALL histwrite_phy("v",v)
194    CALL histwrite_phy("ps",paprs(:,1))
[1852]195#endif
196
[1671]197! if lastcall, then it is time to write "restartphy.nc" file
198if (lafin) then
199  call phyredem("restartphy.nc")
200endif
201
[1897]202end subroutine physiq
Note: See TracBrowser for help on using the repository browser.