source: LMDZ6/branches/LMDZ_ECRad/libf/phydev/physiq_mod.F90 @ 4999

Last change on this file since 4999 was 4727, checked in by idelkadi, 11 months ago

Merged trunk changes -r4488:4726 LMDZ_ECRad branch

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