source: codes/icosagcm/trunk/src/physics.f90 @ 387

Last change on this file since 387 was 387, checked in by dubos, 8 years ago

Infrastructure for multiple dynamical tracers - tested with JW06 and moist baroclinic wave

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