source: codes/icosagcm/trunk/src/initial/etat0.f90 @ 899

Last change on this file since 899 was 899, checked in by adurocher, 5 years ago

trunk : Fixed GCC warnings

Fixed iso c bindings
fixed warnings with -Wall -Wno-aliasing -Wno-unused -Wno-unused-dummy-argument -Wno-maybe-uninitialized -Wno-tabs warnings
Removed all unused variables (-Wunused-variable)
vector%dot_product is now dot_product_3d to avoid compilation warning "dot_product shadows intrinsic" with GCC

File size: 16.8 KB
Line 
1MODULE etat0_mod
2  USE icosa
3  USE omp_para
4  IMPLICIT NONE         
5  PRIVATE
6
7    CHARACTER(len=255),SAVE :: etat0_type
8!$OMP THREADPRIVATE(etat0_type)
9
10    REAL(rstd) :: etat0_temp
11
12    PUBLIC :: etat0, init_etat0, etat0_type
13
14! Important notes for OpenMP
15! When etat0 is called, vertical OpenMP parallelism is deactivated.
16! Therefore only the omp_level_master thread must work, i.e. :
17!   !$OMP BARRIER
18!    DO ind=1,ndomain
19!      IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE
20!      ...
21!    END DO
22!   !$OMP BARRIER
23! There MUST be NO OMP BARRIER inside the DO-LOOP or any routine it calls.
24
25CONTAINS
26 
27  SUBROUTINE init_etat0
28    USE etat0_database_mod, ONLY: init_etat0_database => init_etat0 
29    USE etat0_start_file_mod, ONLY: init_etat0_start_file => init_etat0 
30    USE etat0_heldsz_mod, ONLY: init_etat0_held_suarez => init_etat0 
31   
32    CALL getin("etat0",etat0_type)
33
34    SELECT CASE (TRIM(etat0_type))
35      CASE ('isothermal')
36      CASE ('temperature_profile')
37      CASE ('jablonowsky06')
38      CASE ('dcmip5')
39      CASE ('williamson91.6')
40      CASE ('start_file')
41        CALL init_etat0_start_file
42      CASE ('database')
43        CALL init_etat0_database
44      CASE ('academic')
45      CASE ('held_suarez')
46         CALL init_etat0_held_suarez
47      CASE ('venus')
48      CASE ('dcmip1')
49      CASE ('dcmip2_mountain','dcmip2_schaer_noshear','dcmip2_schaer_shear')
50      CASE ('dcmip3')
51      CASE ('dcmip4')
52      CASE ('dcmip2016_baroclinic_wave')
53      CASE ('dcmip2016_cyclone')
54      CASE ('dcmip2016_supercell')
55      CASE ('bubble')
56      CASE DEFAULT
57         PRINT*, 'Bad selector for variable etat0 <',TRIM(etat0_type),'>'// &
58            ' options are  <isothermal>, <temperature_profile>, <jablonowsky06>, <dcmip5>, <williamson91.6>,'& 
59                         //' <start_file>, <database>, <academic>, <held_suarez>, <venus>, <dcmip1>,'         &
60                         //' <dcmip2_mountain,dcmip2_schaer_noshear,dcmip2_schaer_shear>, <dcmip3>, <dcmip4>,'&
61                         //' <dcmip2016_baroclinic_wave>, <dcmip2016_cyclone>, <dcmip2016_supercell>', 'bubble'
62         STOP
63    END SELECT
64
65  END SUBROUTINE init_etat0
66
67  SUBROUTINE etat0(f_ps,f_mass,f_phis,f_theta_rhodz,f_u, f_geopot,f_w, f_q)
68    USE disvert_mod
69    ! Generic interface
70    USE etat0_dcmip1_mod, ONLY : getin_etat0_dcmip1=>getin_etat0
71    USE etat0_dcmip2_mod, ONLY : getin_etat0_dcmip2=>getin_etat0
72    USE etat0_dcmip4_mod, ONLY : getin_etat0_dcmip4=>getin_etat0
73    USE etat0_dcmip5_mod, ONLY : getin_etat0_dcmip5=>getin_etat0
74    USE etat0_bubble_mod, ONLY : getin_etat0_bubble=>getin_etat0
75    USE etat0_williamson_mod, ONLY : getin_etat0_williamson=>getin_etat0
76    USE etat0_temperature_mod, ONLY: getin_etat0_temperature=>getin_etat0
77    USE etat0_dcmip2016_baroclinic_wave_mod, ONLY : getin_etat0_dcmip2016_baroclinic_wave=>getin_etat0
78    USE etat0_dcmip2016_cyclone_mod, ONLY : getin_etat0_dcmip2016_cyclone=>getin_etat0
79    USE etat0_dcmip2016_supercell_mod, ONLY : getin_etat0_dcmip2016_supercell=>getin_etat0
80    ! Ad hoc interfaces
81    USE etat0_academic_mod, ONLY : etat0_academic=>etat0
82    USE etat0_heldsz_mod, ONLY : etat0_heldsz=>etat0
83    USE etat0_venus_mod,  ONLY : etat0_venus=>etat0
84    USE etat0_database_mod, ONLY : etat0_database=>etat0
85    USE etat0_start_file_mod, ONLY : etat0_start_file=>etat0 
86
87    TYPE(t_field),POINTER :: f_ps(:)
88    TYPE(t_field),POINTER :: f_mass(:)
89    TYPE(t_field),POINTER :: f_phis(:)
90    TYPE(t_field),POINTER :: f_theta_rhodz(:)
91    TYPE(t_field),POINTER :: f_u(:)
92    TYPE(t_field),POINTER :: f_geopot(:)
93    TYPE(t_field),POINTER :: f_w(:)
94    TYPE(t_field),POINTER :: f_q(:)
95   
96    REAL(rstd),POINTER :: ps(:), mass(:,:)
97    LOGICAL :: autoinit_mass, collocated
98    INTEGER :: ind
99
100    ! most etat0 routines set ps and not mass
101    ! in that case and if caldyn_eta == eta_lag
102    ! the initial distribution of mass is taken to be the same
103    ! as what the mass coordinate would dictate
104    ! however if etat0_XXX defines mass then the flag autoinit_mass must be set to .FALSE.
105    ! otherwise mass will be overwritten
106    autoinit_mass = (caldyn_eta == eta_lag)
107
108    etat0_type='jablonowsky06'
109    CALL getin("etat0",etat0_type)
110   
111    !------------------- Generic interface ---------------------
112    collocated=.TRUE.
113    SELECT CASE (TRIM(etat0_type))
114    CASE ('isothermal')
115       CALL getin_etat0_isothermal
116    CASE ('temperature_profile')
117       CALL getin_etat0_temperature
118    CASE ('jablonowsky06')
119    CASE ('dcmip1')
120        CALL getin_etat0_dcmip1
121    CASE ('dcmip2_mountain','dcmip2_schaer_noshear','dcmip2_schaer_shear')
122       CALL getin_etat0_dcmip2
123    CASE ('dcmip3')
124    CASE ('dcmip4')
125        CALL getin_etat0_dcmip4
126    CASE ('dcmip5')
127        CALL getin_etat0_dcmip5
128    CASE ('bubble')
129        CALL getin_etat0_bubble
130    CASE ('williamson91.6')
131       autoinit_mass=.FALSE.
132       CALL getin_etat0_williamson
133    CASE ('dcmip2016_baroclinic_wave')
134        CALL getin_etat0_dcmip2016_baroclinic_wave
135    CASE ('dcmip2016_cyclone')
136        CALL getin_etat0_dcmip2016_cyclone
137    CASE ('dcmip2016_supercell')
138        CALL getin_etat0_dcmip2016_supercell
139    CASE DEFAULT
140       collocated=.FALSE.
141       autoinit_mass = .FALSE.
142    END SELECT
143
144    !------------------- Ad hoc interfaces --------------------
145    SELECT CASE (TRIM(etat0_type))
146     CASE ('database')
147        CALL etat0_database(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
148    CASE ('start_file')
149       CALL etat0_start_file(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
150    CASE ('academic')
151       CALL etat0_academic(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
152    CASE ('held_suarez')
153       PRINT *,"Held & Suarez (1994) test case"
154       CALL etat0_heldsz(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
155    CASE ('venus')
156       CALL etat0_venus(f_ps, f_phis, f_theta_rhodz, f_u, f_q)
157       PRINT *, "Venus (Lebonnois et al., 2012) test case"
158   CASE DEFAULT
159      IF(collocated) THEN
160         CALL etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_geopot,f_W, f_q)
161      ELSE
162         PRINT*, 'Bad selector for variable etat0 <',TRIM(etat0_type),'>'// &
163            ' options are  <isothermal>, <temperature_profile>, <jablonowsky06>, <dcmip5>, <williamson91.6>,'& 
164                         //' <start_file>, <database>, <academic>, <held_suarez>, <venus>, <dcmip1>,'         &
165                         //' <dcmip2_mountain,dcmip2_schaer_noshear,dcmip2_schaer_shear>, <dcmip3>, <dcmip4>,'&
166                         //' <dcmip2016_baroclinic_wave>, <dcmip2016_cyclone>, <dcmip2016_supercell>'
167         STOP
168      END IF
169    END SELECT
170
171    IF(autoinit_mass) THEN
172       DO ind=1,ndomain
173          IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE
174          CALL swap_dimensions(ind)
175          CALL swap_geometry(ind)
176          mass=f_mass(ind); ps=f_ps(ind)
177          CALL compute_rhodz(.TRUE., ps, mass) ! initialize mass distribution using ps
178       END DO
179    END IF
180 
181  END SUBROUTINE etat0
182
183  SUBROUTINE etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_geopot,f_W, f_q)
184    USE theta2theta_rhodz_mod
185    TYPE(t_field),POINTER :: f_ps(:)
186    TYPE(t_field),POINTER :: f_mass(:)
187    TYPE(t_field),POINTER :: f_phis(:)
188    TYPE(t_field),POINTER :: f_theta_rhodz(:)
189    TYPE(t_field),POINTER :: f_u(:)
190    TYPE(t_field),POINTER :: f_geopot(:)
191    TYPE(t_field),POINTER :: f_W(:)
192    TYPE(t_field),POINTER :: f_q(:)
193 
194    TYPE(t_field),POINTER,SAVE :: f_temp(:)
195    REAL(rstd),POINTER :: ps(:)
196    REAL(rstd),POINTER :: mass(:,:)
197    REAL(rstd),POINTER :: phis(:)
198    REAL(rstd),POINTER :: theta_rhodz(:,:,:)
199    REAL(rstd),POINTER :: temp(:,:)
200    REAL(rstd),POINTER :: u(:,:)
201    REAL(rstd),POINTER :: geopot(:,:)
202    REAL(rstd),POINTER :: W(:,:)
203    REAL(rstd),POINTER :: q(:,:,:)
204    INTEGER :: ind
205
206    CALL allocate_field(f_temp,field_t,type_real,llm,name='temp')
207
208    DO ind=1,ndomain
209      IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE
210!      IF (.NOT. assigned_domain(ind)) CYCLE
211      CALL swap_dimensions(ind)
212      CALL swap_geometry(ind)
213      ps=f_ps(ind)
214      mass=f_mass(ind)
215      phis=f_phis(ind)
216      theta_rhodz=f_theta_rhodz(ind)
217      temp=f_temp(ind)
218      u=f_u(ind)
219      geopot=f_geopot(ind)
220      w=f_w(ind)
221      q=f_q(ind)
222
223      IF( TRIM(etat0_type)=='williamson91.6' ) THEN
224         CALL compute_etat0_collocated(ps,mass, phis, theta_rhodz(:,:,1), u, geopot, W, q)
225      ELSE
226         CALL compute_etat0_collocated(ps,mass, phis, temp, u, geopot, W, q)
227      ENDIF
228
229      IF( TRIM(etat0_type)/='williamson91.6' ) CALL compute_temperature2entropy(ps,temp,q,theta_rhodz, 1)
230   
231    ENDDO
232   
233    CALL deallocate_field(f_temp)
234   
235  END SUBROUTINE etat0_collocated
236
237  SUBROUTINE compute_temperature2entropy(ps,temp,q,theta_rhodz,offset)
238    USE icosa
239    USE pression_mod
240    USE exner_mod
241    USE omp_para
242    REAL(rstd),INTENT(IN)  :: ps(iim*jjm)
243    REAL(rstd),INTENT(IN)  :: temp(iim*jjm,llm)
244    REAL(rstd),INTENT(IN)  :: q(iim*jjm,llm,nqtot)
245    REAL(rstd),INTENT(OUT) :: theta_rhodz(iim*jjm,llm)
246    INTEGER,INTENT(IN) :: offset
247
248    REAL(rstd) :: p(iim*jjm,llm+1)
249    REAL(rstd) :: cppd,Rd, mass, p_ij, chi,nu, entropy, theta
250    INTEGER :: i,j,ij,l
251
252    cppd=cpp
253    Rd=kappa*cppd
254
255    CALL compute_pression(ps,p,offset)
256    ! flush p
257    DO    l    = ll_begin, ll_end
258       DO j=jj_begin-offset,jj_end+offset
259          DO i=ii_begin-offset,ii_end+offset
260             ij=(j-1)*iim+i
261             mass = (p(ij,l)-p(ij,l+1))/g ! dry+moist mass
262             p_ij = .5*(p(ij,l)+p(ij,l+1))  ! pressure at full level
263             SELECT CASE(caldyn_thermo)
264             CASE(thermo_theta)
265                theta = temp(ij,l)*(p_ij/preff)**(-kappa) 
266                theta_rhodz(ij,l) = mass * theta
267             CASE(thermo_entropy)
268                nu = log(p_ij/preff)
269                chi = log(temp(ij,l)/Treff)
270                entropy = cppd*chi-Rd*nu
271                theta_rhodz(ij,l) = mass * entropy
272!             CASE(thermo_moist)
273!                q_ij=q(ij,l,1)
274!                r_ij=1.-q_ij
275!                mass=mass*(1-q_ij) ! dry mass
276!                nu = log(p_ij/preff)
277!                chi = log(temp(ij,l)/Treff)
278!                entropy = r_ij*(cppd*chi-Rd*nu) + q_ij*(cppv*chi-Rv*nu)
279!                theta_rhodz(ij,l) = mass * entropy               
280                CASE DEFAULT
281                   STOP
282             END SELECT
283          ENDDO
284       ENDDO
285    ENDDO
286  END SUBROUTINE compute_temperature2entropy
287
288  SUBROUTINE compute_etat0_collocated(ps,mass,phis,temp_i,u, geopot,W, q)
289    USE wind_mod
290    USE disvert_mod
291    USE etat0_jablonowsky06_mod, ONLY : compute_jablonowsky06 => compute_etat0
292    USE etat0_dcmip1_mod, ONLY : compute_dcmip1 => compute_etat0
293    USE etat0_dcmip2_mod, ONLY : compute_dcmip2 => compute_etat0
294    USE etat0_dcmip3_mod, ONLY : compute_dcmip3 => compute_etat0
295    USE etat0_dcmip4_mod, ONLY : compute_dcmip4 => compute_etat0
296    USE etat0_dcmip5_mod, ONLY : compute_dcmip5 => compute_etat0
297    USE etat0_bubble_mod, ONLY : compute_bubble => compute_etat0 
298    USE etat0_williamson_mod, ONLY : compute_w91_6 => compute_etat0
299    USE etat0_temperature_mod, ONLY: compute_etat0_temperature => compute_etat0
300    USE etat0_dcmip2016_baroclinic_wave_mod, ONLY : compute_dcmip2016_baroclinic_wave => compute_etat0
301    USE etat0_dcmip2016_cyclone_mod, ONLY : compute_dcmip2016_cyclone => compute_etat0
302    USE etat0_dcmip2016_supercell_mod, ONLY : compute_dcmip2016_supercell => compute_etat0
303    REAL(rstd),INTENT(INOUT) :: ps(iim*jjm)
304    REAL(rstd),INTENT(INOUT) :: mass(iim*jjm,llm)
305    REAL(rstd),INTENT(OUT) :: phis(iim*jjm)
306    REAL(rstd),INTENT(OUT) :: temp_i(iim*jjm,llm)
307    REAL(rstd),INTENT(OUT) :: u(3*iim*jjm,llm)
308    REAL(rstd),INTENT(OUT) :: W(iim*jjm,llm+1)
309    REAL(rstd),INTENT(OUT) :: geopot(iim*jjm,llm+1)
310    REAL(rstd),INTENT(OUT) :: q(iim*jjm,llm,nqtot)
311
312    REAL(rstd) :: ulon_i(iim*jjm,llm)
313    REAL(rstd) :: ulat_i(iim*jjm,llm)
314
315    REAL(rstd) :: ps_e(3*iim*jjm)
316    REAL(rstd) :: mass_e(3*iim*jjm,llm)
317    REAL(rstd) :: phis_e(3*iim*jjm)
318    REAL(rstd) :: temp_e(3*iim*jjm,llm)
319    REAL(rstd) :: geopot_e(3*iim*jjm,llm+1)
320    REAL(rstd) :: ulon_e(3*iim*jjm,llm)
321    REAL(rstd) :: ulat_e(3*iim*jjm,llm)
322    REAL(rstd) :: q_e(3*iim*jjm,llm,nqtot)
323
324    INTEGER :: l,ij
325    REAL :: p_ik, v_ik, mass_ik
326    LOGICAL :: autoinit_mass, autoinit_NH
327
328    ! For NH geopotential and vertical momentum must be initialized.
329    ! Unless autoinit_NH is set to .FALSE. , they will be initialized
330    ! to hydrostatic geopotential and zero
331    autoinit_mass = .TRUE.
332    autoinit_NH = .NOT. hydrostatic
333    w(:,:) = 0
334
335    SELECT CASE (TRIM(etat0_type))
336    CASE ('isothermal')
337       CALL compute_etat0_isothermal(iim*jjm, phis, ps, temp_i, ulon_i, ulat_i, q)
338       CALL compute_etat0_isothermal(3*iim*jjm, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e)
339    CASE ('temperature_profile')
340       CALL compute_etat0_temperature(iim*jjm, phis, ps, temp_i, ulon_i, ulat_i, q)
341       CALL compute_etat0_temperature(3*iim*jjm, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e)
342    CASE('jablonowsky06')
343       CALL compute_jablonowsky06(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i)
344       CALL compute_jablonowsky06(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e)
345    CASE('dcmip1')
346       CALL compute_dcmip1(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, q)
347       CALL compute_dcmip1(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e)
348    CASE ('dcmip2_mountain','dcmip2_schaer_noshear','dcmip2_schaer_shear')
349       CALL compute_dcmip2(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i)
350       CALL compute_dcmip2(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e)     
351    CASE('dcmip3')
352       CALL compute_dcmip3(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, geopot, q)
353       CALL compute_dcmip3(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, geopot_e, q_e)
354       autoinit_NH = .FALSE. ! compute_dcmip3 initializes geopot
355    CASE('dcmip4')
356       CALL compute_dcmip4(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, q)
357       CALL compute_dcmip4(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e)
358    CASE('dcmip5')
359       CALL compute_dcmip5(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, q)
360       CALL compute_dcmip5(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e)
361    CASE('bubble')
362       CALL compute_bubble(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, geopot, q)
363       CALL compute_bubble(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, geopot_e, q_e)
364!       autoinit_NH = .FALSE. ! compute_bubble initializes geopot
365    CASE('williamson91.6')
366       CALL compute_w91_6(iim*jjm,lon_i,lat_i, phis, mass(:,1), temp_i(:,1), ulon_i(:,1), ulat_i(:,1))
367       CALL compute_w91_6(3*iim*jjm,lon_e,lat_e, phis_e, mass_e(:,1), temp_e(:,1), ulon_e(:,1), ulat_e(:,1))
368       autoinit_mass = .FALSE. ! do not overwrite mass
369    CASE('dcmip2016_baroclinic_wave')
370       CALL compute_dcmip2016_baroclinic_wave(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, q)
371       CALL compute_dcmip2016_baroclinic_wave(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e)
372    CASE('dcmip2016_cyclone')
373       CALL compute_dcmip2016_cyclone(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, q)
374       CALL compute_dcmip2016_cyclone(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e)
375    CASE('dcmip2016_supercell')
376       CALL compute_dcmip2016_supercell(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, q)
377       CALL compute_dcmip2016_supercell(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e)
378    END SELECT
379
380    IF(autoinit_mass) CALL compute_rhodz(.TRUE., ps, mass) ! initialize mass distribution using ps
381    IF(autoinit_NH) THEN
382       geopot(:,1) = phis(:) ! surface geopotential
383       DO l = 1, llm
384          DO ij=1,iim*jjm
385             ! hybrid pressure coordinate
386             p_ik = ptop + mass_ak(l) + mass_bk(l)*ps(ij)
387             mass_ik = (mass_dak(l) + mass_dbk(l)*ps(ij))/g
388             ! v=R.T/p, R=kappa*cpp
389             v_ik = kappa*cpp*temp_i(ij,l)/p_ik
390             geopot(ij,l+1) = geopot(ij,l) + mass_ik*v_ik*g
391          END DO
392       END DO
393    END IF
394
395    CALL compute_wind_perp_from_lonlat_compound(ulon_e, ulat_e, u)
396
397  END SUBROUTINE compute_etat0_collocated
398
399!----------------------------- Resting isothermal state --------------------------------
400
401  SUBROUTINE getin_etat0_isothermal
402    etat0_temp=300
403    CALL getin("etat0_isothermal_temp",etat0_temp)
404  END SUBROUTINE getin_etat0_isothermal
405
406  SUBROUTINE compute_etat0_isothermal(ngrid, phis, ps, temp, ulon, ulat, q)
407    INTEGER, INTENT(IN)    :: ngrid
408    REAL(rstd),INTENT(OUT) :: phis(ngrid)
409    REAL(rstd),INTENT(OUT) :: ps(ngrid)
410    REAL(rstd),INTENT(OUT) :: temp(ngrid,llm)
411    REAL(rstd),INTENT(OUT) :: ulon(ngrid,llm)
412    REAL(rstd),INTENT(OUT) :: ulat(ngrid,llm)
413    REAL(rstd),INTENT(OUT) :: q(ngrid,llm,nqtot)
414    phis(:)=0
415    ps(:)=preff
416    temp(:,:)=etat0_temp
417    ulon(:,:)=0
418    ulat(:,:)=0
419    q(:,:,:)=0
420  END SUBROUTINE compute_etat0_isothermal
421
422END MODULE etat0_mod
Note: See TracBrowser for help on using the repository browser.