source: codes/icosagcm/trunk/src/physics_dcmip2016.f90 @ 416

Last change on this file since 416 was 416, checked in by ymipsl, 8 years ago

More option to parametrize dcmip2016 physics

YM

File size: 7.3 KB
Line 
1MODULE physics_dcmip2016_mod
2  USE ICOSA
3  PRIVATE
4 
5  INTEGER,SAVE :: testcase
6!$OMP THREADPRIVATE(testcase)
7
8  TYPE(t_field),POINTER :: f_out_i(:)
9  REAL(rstd),POINTER :: out_i(:,:)
10
11  TYPE(t_field),POINTER  :: f_precl(:)
12  REAL(rstd),ALLOCATABLE :: precl_packed(:)
13
14  PUBLIC :: init_physics, full_physics, write_physics
15
16  INTEGER, PARAMETER :: dry_baroclinic=0
17  INTEGER, PARAMETER :: moist_baroclinic_full=1
18  INTEGER, PARAMETER :: moist_baroclinic_kessler=2
19  INTEGER, PARAMETER :: cyclone=3
20  INTEGER, PARAMETER :: supercell=4
21
22  LOGICAL,SAVE :: PBL   !  boundary layer
23                        !  True : George Bryan
24                        !  False : Reed & Jablonowsi
25  !$OMP THREADPRIVATE(PBL)
26CONTAINS
27
28  SUBROUTINE init_physics
29    USE physics_interface_mod
30    IMPLICIT NONE
31    INTEGER :: ngrid
32    CHARACTER(LEN=255) :: testcase_str 
33   
34    CALL getin("physics_dcmip2016",testcase_str)
35   
36    SELECT CASE (TRIM(testcase_str))
37      CASE ('dry_baroclinic')
38        testcase=dry_baroclinic
39      CASE ('moist_baroclinic_full') 
40        testcase=moist_baroclinic_full
41      CASE ('moist_baroclinic_kessler') 
42        testcase=moist_baroclinic_kessler
43      CASE ('cyclone') 
44        testcase=cyclone
45      CASE ('supercell') 
46        testcase=supercell
47      CASE DEFAULT
48         PRINT*, 'Bad selector for dcmip2016 test case <', testcase_str, &
49              '> options are <dry_baroclinic>, <moist_baroclinic>, <cyclone>, <supercell>'
50         STOP
51    END SELECT
52
53    PBL=.FALSE.
54    CALL getin("physics_dcmip2016_PBL",PBL)
55
56    ngrid = physics_inout%ngrid
57    ! Input
58    ALLOCATE(physics_inout%Ai(ngrid))
59    ALLOCATE(physics_inout%lon(ngrid))
60    ALLOCATE(physics_inout%lat(ngrid))
61    ALLOCATE(physics_inout%phis(ngrid))
62    ALLOCATE(physics_inout%p(ngrid,llm+1))
63    ALLOCATE(physics_inout%pk(ngrid,llm))
64    ALLOCATE(physics_inout%Temp(ngrid,llm))
65    ALLOCATE(physics_inout%ulon(ngrid,llm))
66    ALLOCATE(physics_inout%ulat(ngrid,llm))
67    ALLOCATE(physics_inout%q(ngrid,llm,nqtot))
68    ! Output (tendencies)
69    ALLOCATE(physics_inout%dTemp(ngrid,llm))
70    ALLOCATE(physics_inout%dulon(ngrid,llm))
71    ALLOCATE(physics_inout%dulat(ngrid,llm))
72    ALLOCATE(physics_inout%dq(ngrid,llm,nqtot))
73    ! Physics-specific data
74    ALLOCATE(precl_packed(ngrid))
75    CALL allocate_field(f_precl, field_t,type_real)
76
77    PRINT *, 'init_physics_new', SIZE(physics_inout%Ai)
78  END SUBROUTINE init_physics
79
80  SUBROUTINE full_physics
81    USE physics_interface_mod
82    CALL compute_physics(physics_inout%ngrid, physics_inout%dt_phys, &
83         physics_inout%lon, physics_inout%lat, physics_inout%p, physics_inout%pk, physics_inout%Temp, & 
84         physics_inout%ulon, physics_inout%ulat, physics_inout%q(:,:,1:5), &
85         physics_inout%dTemp, physics_inout%dulon, physics_inout%dulat, &
86         physics_inout%dq(:,:,1:5), precl_packed)
87  END SUBROUTINE full_physics
88
89  SUBROUTINE write_physics
90    USE output_field_mod
91    USE physics_interface_mod
92    CALL unpack_field(f_precl, precl_packed)
93    CALL output_field("precl",f_precl)
94       
95  END SUBROUTINE write_physics
96
97  SUBROUTINE compute_physics(ngrid,dt_phys,lon, lat, p, pk, Temp,u,v,q, dTemp,du,dv,dq, precl)
98    USE icosa
99    USE dcmip2016_simple_physics_mod
100    USE dcmip2016_kessler_physic_mod
101    USE earth_const
102    USE terminator
103    IMPLICIT NONE
104    INTEGER    :: ngrid
105    REAL(rstd) :: lat(ngrid)
106    REAL(rstd) :: lon(ngrid)
107    REAL(rstd) :: ps(ngrid)
108    REAL(rstd) :: precl(ngrid)
109    ! arguments with bottom-up indexing (DYNAMICO)
110    REAL(rstd) :: p(ngrid,llm+1)
111    REAL(rstd) :: pk(ngrid,llm)
112    REAL(rstd) :: Temp(ngrid,llm)
113    REAL(rstd) :: u(ngrid,llm)
114    REAL(rstd) :: v(ngrid,llm)
115    REAL(rstd) :: q(ngrid,llm,5)
116    REAL(rstd) :: dTemp(ngrid,llm)
117    REAL(rstd) :: du(ngrid,llm)
118    REAL(rstd) :: dv(ngrid,llm)
119    REAL(rstd) :: dq(ngrid,llm,5)
120    ! local arrays with top-down vertical indexing (DCMIP)
121    REAL(rstd) :: pint(ngrid,llm+1)
122    REAL(rstd) :: pmid(ngrid,llm)
123    REAL(rstd) :: pdel(ngrid,llm)
124    REAL(rstd) :: Tfi(ngrid,llm)
125    REAL(rstd) :: ufi(ngrid,llm)
126    REAL(rstd) :: vfi(ngrid,llm)
127    REAL(rstd) :: qfi(ngrid,llm,5)
128
129    REAL(rstd)  :: rho(llm), z(llm), theta(llm), qv(llm),qc(llm),qr(llm)
130    REAL(rstd)  :: lastz
131    REAL(rstd)  :: dcl1,dcl2
132     INTEGER :: l,ll,ij
133    REAL(rstd) :: dt_phys, inv_dt
134    INTEGER :: simple_physic_testcase
135   
136    ! prepare input fields and mirror vertical index     
137    ps(:) = p(:,1) ! surface pressure
138
139    DO l=1,llm+1
140      DO ij=1,ngrid
141          pint(ij,l)=p(ij,llm+2-l)
142      ENDDO
143    ENDDO
144
145    DO l=1,llm
146       ll=llm+1-l
147       DO ij=1,ngrid
148          pmid(ij,l)=0.5*(pint(ij,l)+pint(ij,l+1)) ! Pressure inside layers
149          pdel(ij,l)=pint(ij,l+1)-pint(ij,l)       ! Pressure difference between two layers
150          ufi(ij,l)=u(ij,ll)
151          vfi(ij,l)=v(ij,ll)
152          qfi(ij,l,:)=q(ij,ll,:)
153          IF (physics_thermo==thermo_fake_moist) THEN
154            Tfi(ij,l)=Temp(ij,ll)/(1+0.608*qfi(ij,l,1)) 
155          ELSE
156            Tfi(ij,l)=Temp(ij,ll)
157          ENDIF
158       ENDDO
159    ENDDO
160   
161    precl=0.
162    IF (testcase==moist_baroclinic_full .OR. testcase==cyclone  ) THEN
163      IF (testcase==moist_baroclinic_full) simple_physic_testcase=1
164      IF (testcase==cyclone) simple_physic_testcase=0
165      CALL simple_physics(ngrid, llm, dt_phys, lat, tfi, qfi(:,:,1) , ufi, vfi, pmid, pint, pdel, 1./pdel, ps, precl, &
166                          simple_physic_testcase, .FALSE., PBL)
167    ENDIF
168
169 
170    IF (testcase==moist_baroclinic_full .OR. testcase==moist_baroclinic_kessler .OR. testcase==cyclone .OR. testcase==supercell ) THEN
171       DO ij=1,ngrid
172          lastz=0 
173          DO l=1,llm
174           ll=llm+1-l
175           rho(l) = pmid(ij,ll)/(287*Temp(ij,l))
176           z(l)=lastz
177           lastz=lastz+ (p(ij,l)-p(ij,l+1)) /g / rho(l)
178           theta(l)= Tfi(ij,ll) / ( pk(ij,l) / cpp)
179          ENDDO
180         
181          DO l=1,llm-1
182           z(l)= 0.5*(z(l)+z(l+1))
183          ENDDO
184          z(llm)=z(llm)+(z(llm)-z(llm-1))
185         
186          qv(:)=max(qfi(ij,llm:1:-1,1),0.)
187          qc(:)=max(qfi(ij,llm:1:-1,2),0.)
188          qr(:)=max(qfi(ij,llm:1:-1,3),0.)
189         
190          CALL KESSLER(theta(:), qv, qc, qr, rho(:),  &
191                       pk(ij,:)/cpp, dt_phys, z(:), llm, precl(ij)) 
192         
193         
194          DO l=1,llm
195           ll=llm+1-l
196           Tfi(ij,ll) = theta(l)  * ( pk(ij,l) / cpp)
197          ENDDO
198
199          qfi(ij,:,1)=qv(llm:1:-1)
200          qfi(ij,:,2)=qc(llm:1:-1)
201          qfi(ij,:,3)=qr(llm:1:-1)
202
203       ENDDO
204    ENDIF
205   
206    DO l=1,llm
207      ll=llm+1-l
208      DO ij=1,ngrid
209        CALL  tendency_terminator( lat(ij), lon(ij), qfi(ij,ll,4), qfi(ij,ll,5), dt_phys, dcl1, dcl2)
210        qfi(ij,ll,4)=qfi(ij,ll,4)+ dt_phys*dcl1
211        qfi(ij,ll,5)=qfi(ij,ll,5)+ dt_phys*dcl2
212      ENDDO
213    ENDDO
214   
215   
216    ! Mirror vertical index and compute tendencies
217    inv_dt = 1./dt_phys
218    DO l=1,llm
219       ll=llm+1-l
220       DO ij=1,ngrid
221          IF (physics_thermo==thermo_fake_moist) THEN
222            dTemp(ij,l) = inv_dt * ( Tfi(ij,ll)*(1+0.608*qfi(ij,ll,1)) - Temp(ij,l) )
223          ELSE
224            dTemp(ij,l) = inv_dt * ( Tfi(ij,ll) - Temp(ij,l) )
225          ENDIF
226         
227          du(ij,l) = inv_dt * (ufi(ij,ll) - u(ij,l))
228          dv(ij,l) = inv_dt * (vfi(ij,ll) - v(ij,l))
229          dq(ij,l,:)  = inv_dt * (qfi(ij,ll,:) - q(ij,l,:))
230       ENDDO
231    ENDDO
232
233  END SUBROUTINE compute_physics
234   
235END MODULE physics_dcmip2016_mod
236
237
Note: See TracBrowser for help on using the repository browser.