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

Last change on this file since 252 was 217, checked in by dubos, 10 years ago

Removed "automatic" physics + bugfix

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