source: codes/icosagcm/devel/src/initial/etat0.f90 @ 797

Last change on this file since 797 was 732, checked in by dubos, 6 years ago

devel : more cleanup and reorganization in dynamics/

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