source: codes/icosagcm/devel/src/physics/physics.f90 @ 739

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

devel : small cleanup in idealized physics

File size: 12.4 KB
Line 
1MODULE physics_mod
2  USE icosa
3  USE field_mod
4  USE physics_interface_mod
5  USE omp_para
6  IMPLICIT NONE
7  PRIVATE
8
9  INTEGER, PARAMETER :: phys_none=0, phys_column=1, &
10       phys_HS94=3, phys_LB2012=4, &
11       phys_DCMIP=11, phys_DCMIP2016=12, &
12       phys_lmdz_generic=21, phys_external=22
13  INTEGER :: phys_type
14  TYPE(t_field),POINTER,SAVE :: f_extra_physics_2D(:), f_extra_physics_3D(:)
15  TYPE(t_field),POINTER,SAVE :: f_dulon(:), f_dulat(:)
16  TYPE(t_field),POINTER,SAVE :: f_ulon(:), f_ulat(:)
17  TYPE(t_field),POINTER,SAVE :: f_p(:), f_pk(:)
18  TYPE(t_field),POINTER,SAVE :: f_temp(:)
19  TYPE(t_field),POINTER,SAVE :: f_du_phys(:)
20
21  CHARACTER(LEN=255),SAVE :: physics_type
22!$OMP THREADPRIVATE(physics_type)
23
24  PUBLIC :: physics, init_physics, zero_du_phys
25
26CONTAINS
27
28  SUBROUTINE init_physics
29    USE mpipara
30    USE etat0_mod
31    USE etat0_venus_mod, ONLY : init_phys_venus=>init_physics
32    USE physics_dcmip_mod, ONLY : init_physics_dcmip=>init_physics
33    USE physics_dcmip2016_mod, ONLY : init_physics_dcmip2016=>init_physics
34    USE physics_lmdz_generic_mod, ONLY : init_physics_lmdz_generic=>init_physics
35    USE physics_external_mod, ONLY : init_physics_external=>init_physics
36    LOGICAL :: done
37    physics_inout%dt_phys = dt*itau_physics
38!$OMP PARALLEL
39    CALL allocate_field(f_du_phys,field_u,type_real,llm, name='du_phys')
40
41    physics_type='none'
42    CALL getin("physics",physics_type)
43    ! below, flag done is set to .FALSE. if the CALL to init_XXX must be done outside any OMP PARALLEL region
44    done=.TRUE.
45    phys_type=phys_column
46    SELECT CASE(TRIM(physics_type))
47    CASE ('none')
48       IF(is_mpi_root) PRINT*,"NO PHYSICAL PACKAGE USED"
49       phys_type = phys_none
50    CASE ('held_suarez')
51       phys_type = phys_HS94
52    CASE ('Lebonnois2012')
53       phys_type = phys_LB2012
54       CALL init_phys_venus       
55    CASE ('phys_lmdz_generic')
56       phys_type=phys_lmdz_generic
57       done = .FALSE.
58    CASE ('phys_external')
59       phys_type=phys_external
60       done = .FALSE.
61    END SELECT
62
63    IF(phys_type == phys_column) THEN
64       CALL allocate_field(f_dulon,field_t,type_real,llm, name='dulon')
65       CALL allocate_field(f_dulat,field_t,type_real,llm, name='dulat')
66       CALL allocate_field(f_temp,field_t,type_real,llm, name='temp')
67       CALL allocate_field(f_ulon,field_t,type_real,llm, name='ulon')
68       CALL allocate_field(f_ulat,field_t,type_real,llm, name='ulat')
69       CALL allocate_field(f_p,field_t,type_real,llm+1, name='p')
70       CALL allocate_field(f_pk,field_t,type_real,llm, name='pk')
71       CALL init_pack_before ! Compute physics_inout%ngrid and offsets used by pack/unpack
72       CALL init_pack_after  ! Defines Ai, lon, lat in physics_inout
73       
74       SELECT CASE(TRIM(physics_type))
75       CASE ('dcmip')
76          phys_type = phys_DCMIP
77          CALL init_physics_dcmip
78       CASE ('dcmip2016')
79          phys_type = phys_DCMIP2016
80          CALL init_physics_dcmip2016
81       CASE DEFAULT
82          IF(is_mpi_root) PRINT*, 'init_physics : Bad selector for variable physics <',&
83               TRIM(physics_type), '> options are <none>, <held_suarez>, <Lebonnois2012>,', &
84               '<dcmip>, <dcmip2016>, <phys_lmdz_generic>, <phys_external>'
85          STOP
86       END SELECT
87       
88    END IF
89!$OMP END PARALLEL
90
91    IF(done==.FALSE.) THEN
92       SELECT CASE(phys_type)
93       CASE(phys_external) 
94          CALL init_physics_external
95       CASE(phys_lmdz_generic)
96          CALL init_physics_lmdz_generic
97       END SELECT
98    END IF
99
100    IF(is_mpi_root) PRINT *, 'phys_type = ',phys_type
101
102  END SUBROUTINE init_physics
103
104  SUBROUTINE zero_du_phys()
105    REAL(rstd), DIMENSION(:,:), POINTER :: du
106    INTEGER :: ind
107    DO ind=1,ndomain
108       IF (.NOT. assigned_domain(ind)) CYCLE
109       CALL swap_dimensions(ind)
110       CALL swap_geometry(ind)
111       du=f_du_phys(ind)
112       du(:,ll_begin:ll_end) = 0.
113    END DO
114  END SUBROUTINE zero_du_phys
115
116  SUBROUTINE add_du_phys(coef, f_u)
117    REAL(rstd), INTENT(IN) :: coef  ! -1 before physics, +1 after physics
118    TYPE(t_field),POINTER :: f_u(:) ! velocity field before/after call to physics
119    REAL(rstd), DIMENSION(:,:), POINTER :: u, du
120    INTEGER :: ind
121    DO ind=1,ndomain
122       IF (.NOT. assigned_domain(ind)) CYCLE
123       CALL swap_dimensions(ind)
124       CALL swap_geometry(ind)
125       du=f_du_phys(ind)
126       u=f_u(ind)
127       du(:,ll_begin:ll_end) = du(:,ll_begin:ll_end) + coef*u(:,ll_begin:ll_end)
128    END DO
129  END SUBROUTINE add_du_phys
130
131  SUBROUTINE physics(it,f_phis, f_ps, f_theta_rhodz, f_ue, f_wflux, f_q)
132    USE physics_lmdz_generic_mod, ONLY : physics_lmdz_generic => physics
133    USE physics_external_mod, ONLY : physics_external => physics
134    USE physics_dcmip_mod, ONLY : write_physics_dcmip => write_physics
135    USE physics_dcmip2016_mod, ONLY : write_physics_dcmip2016 => write_physics
136    USE etat0_heldsz_mod
137    USE etat0_venus_mod, ONLY : phys_venus => physics
138    INTEGER, INTENT(IN)   :: it
139    TYPE(t_field),POINTER :: f_phis(:)
140    TYPE(t_field),POINTER :: f_ps(:)
141    TYPE(t_field),POINTER :: f_theta_rhodz(:)
142    TYPE(t_field),POINTER :: f_ue(:)
143    TYPE(t_field),POINTER :: f_wflux(:)
144    TYPE(t_field),POINTER :: f_q(:)
145
146    LOGICAL:: firstcall,lastcall
147    INTEGER :: ind
148    TYPE(t_physics_inout) :: args
149
150    IF(MOD(it,itau_physics)==0 .AND. phys_type/=phys_none) THEN
151
152       ! as a result of the the two calls to add_du_phys,
153       ! du_phys increases by u(after physics) - u (before physics)
154       CALL add_du_phys(-1., f_ue)
155
156       SELECT CASE(phys_type)
157       CASE(phys_HS94)
158          CALL held_suarez(f_ps,f_theta_rhodz,f_ue) 
159       CASE (phys_lmdz_generic)
160         CALL physics_lmdz_generic(it ,f_phis, f_ps, f_theta_rhodz, f_ue, f_wflux, f_q)
161       CASE (phys_external)
162         CALL physics_external(it ,f_phis, f_ps, f_theta_rhodz, f_ue, f_wflux, f_q)
163       CASE(phys_LB2012)
164          CALL phys_venus(f_ps,f_theta_rhodz,f_ue) 
165       CASE DEFAULT
166          CALL physics_column(it, f_phis, f_ps, f_theta_rhodz, f_ue, f_q)
167       END SELECT
168
169       CALL transfert_request(f_theta_rhodz,req_i0)
170       CALL transfert_request(f_ue,req_e0_vect)
171       CALL transfert_request(f_q,req_i0)
172
173       CALL add_du_phys(1., f_ue)
174    END IF
175
176    IF (mod(it,itau_out)==0 ) THEN
177       CALL write_physics_tendencies
178       CALL zero_du_phys
179       SELECT CASE(phys_type)
180       CASE (phys_DCMIP)
181          CALL write_physics_dcmip
182       CASE (phys_DCMIP2016)
183          CALL write_physics_dcmip2016
184       END SELECT
185    END IF
186   
187  END SUBROUTINE physics
188
189  SUBROUTINE write_physics_tendencies
190    USE observable_mod, ONLY : f_buf_ulon, f_buf_ulat
191    USE wind_mod
192    USE output_field_mod
193    CALL transfert_request(f_du_phys,req_e1_vect)
194    CALL un2ulonlat(f_du_phys, f_buf_ulon, f_buf_ulat, (1./(dt*itau_out)))
195    CALL output_field("dulon_phys",f_buf_ulon)
196    CALL output_field("dulat_phys",f_buf_ulat)
197  END SUBROUTINE write_physics_tendencies
198   
199  SUBROUTINE physics_column(it, f_phis, f_ps, f_theta_rhodz, f_ue, f_q)
200    USE physics_dcmip_mod, ONLY : full_physics_dcmip => full_physics
201    USE physics_dcmip2016_mod, ONLY : full_physics_dcmip2016 => full_physics
202    USE theta2theta_rhodz_mod
203    USE mpipara
204    USE checksum_mod
205    TYPE(t_field),POINTER :: f_phis(:)
206    TYPE(t_field),POINTER :: f_ps(:)
207    TYPE(t_field),POINTER :: f_theta_rhodz(:)
208    TYPE(t_field),POINTER :: f_ue(:)
209    TYPE(t_field),POINTER :: f_q(:)
210    REAL(rstd),POINTER :: phis(:)
211    REAL(rstd),POINTER :: ps(:)
212    REAL(rstd),POINTER :: temp(:,:)
213    REAL(rstd),POINTER :: ue(:,:)
214    REAL(rstd),POINTER :: dulon(:,:)
215    REAL(rstd),POINTER :: dulat(:,:)
216    REAL(rstd),POINTER :: q(:,:,:)
217    REAL(rstd),POINTER :: p(:,:)
218    REAL(rstd),POINTER :: pk(:,:)
219    REAL(rstd),POINTER :: ulon(:,:)
220    REAL(rstd),POINTER :: ulat(:,:)
221    INTEGER :: it, ind
222
223    CALL theta_rhodz2temperature(f_ps,f_theta_rhodz,f_temp)
224   
225    DO ind=1,ndomain
226       IF (.NOT. assigned_domain(ind)) CYCLE
227       CALL swap_dimensions(ind)
228       CALL swap_geometry(ind)
229       phis=f_phis(ind)
230       ps=f_ps(ind)
231       temp=f_temp(ind)
232       ue=f_ue(ind)
233       q=f_q(ind)
234       p=f_p(ind)
235       pk=f_pk(ind)
236       ulon=f_ulon(ind)
237       ulat=f_ulat(ind)
238       CALL pack_physics(pack_info(ind), phis, ps, temp, ue, q, p, pk, ulon, ulat)
239    END DO
240
241    SELECT CASE(phys_type)
242    CASE (phys_DCMIP)
243       IF (is_omp_level_master) CALL full_physics_dcmip
244    CASE (phys_DCMIP2016)
245       IF (is_omp_level_master) CALL full_physics_dcmip2016
246    CASE DEFAULT
247       IF(is_master) PRINT *,'Internal error : illegal value of phys_type', phys_type
248       STOP
249    END SELECT
250
251    DO ind=1,ndomain
252       IF (.NOT. assigned_domain(ind)) CYCLE
253       CALL swap_dimensions(ind)
254       CALL swap_geometry(ind)
255       ps=f_ps(ind)
256       temp=f_temp(ind)
257       q=f_q(ind)
258       dulon=f_dulon(ind)
259       dulat=f_dulat(ind)
260       CALL unpack_physics(pack_info(ind), ps, temp, q, dulon, dulat)
261    END DO
262   
263    CALL temperature2theta_rhodz(f_ps,f_temp,f_theta_rhodz)
264
265    ! Transfer dulon, dulat
266    CALL transfert_request(f_dulon,req_i0)
267    CALL transfert_request(f_dulat,req_i0)
268
269    DO ind=1,ndomain
270       IF (.NOT. assigned_domain(ind)) CYCLE
271       CALL swap_dimensions(ind)
272       CALL swap_geometry(ind)
273       ue=f_ue(ind)
274       dulon=f_dulon(ind)
275       dulat=f_dulat(ind)
276       CALL compute_update_velocity(dulon, dulat, ue)
277    END DO
278
279  END SUBROUTINE physics_column
280
281  SUBROUTINE pack_physics(info, phis, ps, temp, ue, q, p, pk, ulon, ulat )
282    USE wind_mod
283    USE pression_mod
284    USE theta2theta_rhodz_mod
285    USE exner_mod
286    TYPE(t_pack_info) :: info
287    REAL(rstd) :: phis(iim*jjm)
288    REAL(rstd) :: ps(iim*jjm)
289    REAL(rstd) :: temp(iim*jjm,llm)
290    REAL(rstd) :: pks(iim*jjm)
291    REAL(rstd) :: pk(iim*jjm,llm)
292    REAL(rstd) :: ue(3*iim*jjm,llm)
293    REAL(rstd) :: q(iim*jjm,llm,nqtot)
294
295    REAL(rstd) :: p(iim*jjm,llm+1)
296    REAL(rstd) :: uc(iim*jjm,llm,3)
297    REAL(rstd) :: ulon(iim*jjm,llm)
298    REAL(rstd) :: ulat(iim*jjm,llm)
299
300!$OMP BARRIER
301    CALL compute_pression(ps,p,0)
302!$OMP BARRIER
303    CALL compute_exner(ps,p,pks,pk,0) 
304!$OMP BARRIER
305    CALL compute_wind_centered(ue,uc)
306    CALL compute_wind_centered_lonlat_compound(uc, ulon, ulat)
307!$OMP BARRIER
308    IF (is_omp_level_master) THEN
309      CALL pack_domain(info, phis, physics_inout%phis)
310      CALL pack_domain(info, p, physics_inout%p)
311      CALL pack_domain(info, pk, physics_inout%pk)
312      CALL pack_domain(info, Temp, physics_inout%Temp)
313      CALL pack_domain(info, ulon, physics_inout%ulon)
314      CALL pack_domain(info, ulat, physics_inout%ulat)
315      CALL pack_domain(info, q, physics_inout%q)
316    ENDIF
317!$OMP BARRIER
318  END SUBROUTINE pack_physics
319
320  SUBROUTINE unpack_physics(info, ps,temp, q, dulon, dulat)
321    USE theta2theta_rhodz_mod
322    TYPE(t_pack_info) :: info
323    REAL(rstd) :: ps(iim*jjm)
324    REAL(rstd) :: temp(iim*jjm,llm)
325    REAL(rstd) :: q(iim*jjm,llm,nqtot)
326    REAL(rstd) :: dulon(iim*jjm,llm)
327    REAL(rstd) :: dulat(iim*jjm,llm)
328
329    REAL(rstd) :: dq(iim*jjm,llm,nqtot)
330    REAL(rstd) :: dTemp(iim*jjm,llm)
331
332!$OMP BARRIER
333    IF (is_omp_level_master) THEN
334      CALL unpack_domain(info, dulon, physics_inout%dulon)
335      CALL unpack_domain(info, dulat, physics_inout%dulat)
336      CALL unpack_domain(info, dq, physics_inout%dq)
337      CALL unpack_domain(info, Temp, physics_inout%Temp)
338      CALL unpack_domain(info, dTemp, physics_inout%dTemp)
339      q = q + physics_inout%dt_phys * dq
340      Temp = Temp + physics_inout%dt_phys * dTemp
341    ENDIF
342!$OMP BARRIER
343
344!    CALL compute_temperature2theta_rhodz(ps,Temp,theta_rhodz,0)
345  END SUBROUTINE unpack_physics
346
347  SUBROUTINE compute_update_velocity(dulon, dulat, ue)
348    USE wind_mod
349    REAL(rstd) :: dulon(iim*jjm,llm)
350    REAL(rstd) :: dulat(iim*jjm,llm)
351    REAL(rstd) :: ue(3*iim*jjm,llm)
352    REAL(rstd) :: duc(iim*jjm,llm,3)
353    REAL(rstd) :: dt2, due
354    INTEGER :: i,j,ij,l
355    ! Reconstruct wind tendencies at edges and add to normal wind
356    CALL compute_wind_centered_from_lonlat_compound(dulon,dulat,duc)
357    dt2=.5*physics_inout%dt_phys
358    DO l=ll_begin,ll_end
359      DO j=jj_begin,jj_end
360        DO i=ii_begin,ii_end
361          ij=(j-1)*iim+i
362          due = sum( (duc(ij,l,:) + duc(ij+t_right,l,:))*ep_e(ij+u_right,:) )
363          ue(ij+u_right,l) = ue(ij+u_right,l) + dt2*due
364
365          due = sum( (duc(ij,l,:) + duc(ij+t_lup,l,:))*ep_e(ij+u_lup,:) )
366          ue(ij+u_lup,l)=ue(ij+u_lup,l) + dt2*due
367
368          due = sum( (duc(ij,l,:) + duc(ij+t_ldown,l,:))*ep_e(ij+u_ldown,:) )
369          ue(ij+u_ldown,l)=ue(ij+u_ldown,l) + dt2*due
370        ENDDO
371      ENDDO
372    ENDDO
373  END SUBROUTINE compute_update_velocity
374
375END MODULE physics_mod
Note: See TracBrowser for help on using the repository browser.