source: codes/icosagcm/trunk/src/etat0.f90 @ 488

Last change on this file since 488 was 483, checked in by ymipsl, 8 years ago
  • Add functionnality to input/output field of type U (value on the edges)
  • Management of start/restart files by XIOS

YM

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