1 | ! $Id: physiq.F 1565 2011-08-31 12:53:29Z jghattas $ |
---|
2 | MODULE physiqex_mod |
---|
3 | |
---|
4 | IMPLICIT NONE |
---|
5 | |
---|
6 | CONTAINS |
---|
7 | |
---|
8 | SUBROUTINE physiqex(nlon,nlev, & |
---|
9 | debut,lafin,pdtphys, & |
---|
10 | paprs,pplay,pphi,pphis,presnivs, & |
---|
11 | u,v,rot,t,qx, & |
---|
12 | flxmass_w, & |
---|
13 | d_u, d_v, d_t, d_qx, d_ps) |
---|
14 | |
---|
15 | USE dimphy, ONLY: klon,klev |
---|
16 | USE infotrac_phy, ONLY: nqtot |
---|
17 | USE lmdz_geometry, ONLY: latitude |
---|
18 | ! USE comcstphy, ONLY: rg |
---|
19 | USE ioipsl, ONLY: ymds2ju |
---|
20 | USE phys_state_var_mod, ONLY: phys_state_var_init |
---|
21 | USE phyetat0_mod, ONLY: phyetat0 |
---|
22 | USE output_physiqex_mod, ONLY: output_physiqex |
---|
23 | |
---|
24 | IMPLICIT NONE |
---|
25 | |
---|
26 | ! Routine argument: |
---|
27 | |
---|
28 | INTEGER,INTENT(IN) :: nlon ! number of atmospheric colums |
---|
29 | INTEGER,INTENT(IN) :: nlev ! number of vertical levels (should be =klev) |
---|
30 | logical,INTENT(IN) :: debut ! signals first CALL to physics |
---|
31 | logical,INTENT(IN) :: lafin ! signals last CALL to physics |
---|
32 | REAL,INTENT(IN) :: pdtphys ! physics time step (s) |
---|
33 | REAL,INTENT(IN) :: paprs(klon,klev+1) ! interlayer pressure (Pa) |
---|
34 | REAL,INTENT(IN) :: pplay(klon,klev) ! mid-layer pressure (Pa) |
---|
35 | REAL,INTENT(IN) :: pphi(klon,klev) ! geopotential at mid-layer |
---|
36 | REAL,INTENT(IN) :: pphis(klon) ! surface geopotential |
---|
37 | REAL,INTENT(IN) :: presnivs(klev) ! pseudo-pressure (Pa) of mid-layers |
---|
38 | REAL,INTENT(IN) :: u(klon,klev) ! eastward zonal wind (m/s) |
---|
39 | REAL,INTENT(IN) :: v(klon,klev) ! northward meridional wind (m/s) |
---|
40 | REAL,INTENT(IN) :: rot(klon,klev) ! northward meridional wind (m/s) |
---|
41 | REAL,INTENT(IN) :: t(klon,klev) ! temperature (K) |
---|
42 | REAL,INTENT(IN) :: qx(klon,klev,nqtot) ! tracers (.../kg_air) |
---|
43 | REAL,INTENT(IN) :: flxmass_w(klon,klev) ! vertical mass flux |
---|
44 | REAL,INTENT(OUT) :: d_u(klon,klev) ! physics tendency on u (m/s/s) |
---|
45 | REAL,INTENT(OUT) :: d_v(klon,klev) ! physics tendency on v (m/s/s) |
---|
46 | REAL,INTENT(OUT) :: d_t(klon,klev) ! physics tendency on t (K/s) |
---|
47 | REAL,INTENT(OUT) :: d_qx(klon,klev,nqtot) ! physics tendency on tracers |
---|
48 | REAL,INTENT(OUT) :: d_ps(klon) ! physics tendency on surface pressure |
---|
49 | |
---|
50 | ! include "clesphys.h" |
---|
51 | INTEGER length |
---|
52 | PARAMETER ( length = 100 ) |
---|
53 | REAL tabcntr0( length ) |
---|
54 | INTEGER, PARAMETER :: longcles=20 |
---|
55 | REAL, SAVE :: clesphy0(longcles) |
---|
56 | !$OMP THREADPRIVATE(clesphy0) |
---|
57 | |
---|
58 | |
---|
59 | REAL :: temp_newton(klon,klev) |
---|
60 | INTEGER :: k |
---|
61 | logical, save :: first=.TRUE. |
---|
62 | !$OMP THREADPRIVATE(first) |
---|
63 | |
---|
64 | REAL,save :: rg=9.81 |
---|
65 | !$OMP THREADPRIVATE(rg) |
---|
66 | |
---|
67 | ! For I/Os |
---|
68 | INTEGER :: itau0 |
---|
69 | REAL :: zjulian |
---|
70 | |
---|
71 | |
---|
72 | !------------------------------------------------------------ |
---|
73 | ! Initialisations de la physique au premier pas de temps |
---|
74 | !------------------------------------------------------------ |
---|
75 | |
---|
76 | PRINT*,'Debut physiqex',debut |
---|
77 | ! initializations |
---|
78 | IF (debut) then ! Things to do only for the first CALL to physics |
---|
79 | PRINT*,'Debut physiqex IN' |
---|
80 | |
---|
81 | ! load initial conditions for physics (including the grid) |
---|
82 | CALL phys_state_var_init(1) ! some initializations, required before calling phyetat0 |
---|
83 | CALL phyetat0("startphy.nc", clesphy0, tabcntr0) |
---|
84 | |
---|
85 | ! Initialize outputs: |
---|
86 | itau0=0 |
---|
87 | ! compute zjulian for annee0=1979 and month=1 dayref=1 and hour=0.0 |
---|
88 | !CALL ymds2ju(annee0, month, dayref, hour, zjulian) |
---|
89 | CALL ymds2ju(1979, 1, 1, 0.0, zjulian) |
---|
90 | |
---|
91 | #ifndef CPP_IOIPSL_NO_OUTPUT |
---|
92 | ! Initialize IOIPSL output file |
---|
93 | #endif |
---|
94 | |
---|
95 | END IF ! of if (debut) |
---|
96 | |
---|
97 | !------------------------------------------------------------ |
---|
98 | ! Initialisations a chaque pas de temps |
---|
99 | !------------------------------------------------------------ |
---|
100 | |
---|
101 | |
---|
102 | ! set all tendencies to zero |
---|
103 | d_u(1:klon,1:klev)=0. |
---|
104 | d_v(1:klon,1:klev)=0. |
---|
105 | d_t(1:klon,1:klev)=0. |
---|
106 | d_qx(1:klon,1:klev,1:nqtot)=0. |
---|
107 | d_ps(1:klon)=0. |
---|
108 | |
---|
109 | !------------------------------------------------------------ |
---|
110 | ! Calculs |
---|
111 | !------------------------------------------------------------ |
---|
112 | |
---|
113 | ! compute tendencies to return to the dynamics: |
---|
114 | ! "friction" on the first layer |
---|
115 | d_u(1:klon,1)=-u(1:klon,1)/86400. |
---|
116 | d_v(1:klon,1)=-v(1:klon,1)/86400. |
---|
117 | ! newtonian relaxation towards temp_newton() |
---|
118 | DO k=1,klev |
---|
119 | temp_newton(1:klon,k)=280.+cos(latitude(1:klon))*40.-pphi(1:klon,k)/rg*6.e-3 |
---|
120 | d_t(1:klon,k)=(temp_newton(1:klon,k)-t(1:klon,k))/1.e5 |
---|
121 | END DO |
---|
122 | |
---|
123 | |
---|
124 | !------------------------------------------------------------ |
---|
125 | ! Entrees sorties |
---|
126 | !------------------------------------------------------------ |
---|
127 | |
---|
128 | |
---|
129 | CALL output_physiqex(debut,zjulian,pdtphys,presnivs,paprs,u,v,t,qx,0.*t,0.*t,0.*t,0.*t,0.*t,0.*t) |
---|
130 | |
---|
131 | |
---|
132 | ! if lastcall, then it is time to write "restartphy.nc" file |
---|
133 | IF (lafin) THEN |
---|
134 | CALL phyredem("restartphy.nc") |
---|
135 | END IF |
---|
136 | |
---|
137 | |
---|
138 | END SUBROUTINE physiqex |
---|
139 | |
---|
140 | END MODULE physiqex_mod |
---|