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