1 | SUBROUTINE watercloud(ngrid,nlay, ptimestep, |
---|
2 | & pplev,pplay,pdpsrf,pzlev,pzlay,pt,pdt, |
---|
3 | & pq,pdq,pdqcloud,pdqscloud,pdtcloud, |
---|
4 | & nq,tau,tauscaling,rdust,rice,nuice, |
---|
5 | & rsedcloud,rhocloud) |
---|
6 | IMPLICIT NONE |
---|
7 | |
---|
8 | c======================================================================= |
---|
9 | c Water-ice cloud formation |
---|
10 | c |
---|
11 | c Includes two different schemes: |
---|
12 | c - A simplified scheme (see simpleclouds.F) |
---|
13 | c - An improved microphysical scheme (see improvedclouds.F) |
---|
14 | c |
---|
15 | c Authors: Franck Montmessin, Francois Forget, Ehouarn Millour, |
---|
16 | c J.-B. Madeleine |
---|
17 | c |
---|
18 | c 2004 - Oct. 2011 |
---|
19 | c======================================================================= |
---|
20 | |
---|
21 | c----------------------------------------------------------------------- |
---|
22 | c declarations: |
---|
23 | c ------------- |
---|
24 | |
---|
25 | #include "dimensions.h" |
---|
26 | #include "dimphys.h" |
---|
27 | #include "comcstfi.h" |
---|
28 | #include "callkeys.h" |
---|
29 | #include "tracer.h" |
---|
30 | #include "comgeomfi.h" |
---|
31 | #include "dimradmars.h" |
---|
32 | |
---|
33 | c Inputs: |
---|
34 | c ------ |
---|
35 | |
---|
36 | INTEGER ngrid,nlay |
---|
37 | integer nq ! nombre de traceurs |
---|
38 | REAL ptimestep ! pas de temps physique (s) |
---|
39 | REAL pplev(ngrid,nlay+1) ! pression aux inter-couches (Pa) |
---|
40 | REAL pplay(ngrid,nlay) ! pression au milieu des couches (Pa) |
---|
41 | REAL pdpsrf(ngrid) ! tendance surf pressure |
---|
42 | REAL pzlev(ngrid,nlay+1) ! altitude at layer boundaries |
---|
43 | REAL pzlay(ngrid,nlay) ! altitude at the middle of the layers |
---|
44 | REAL pt(ngrid,nlay) ! temperature at the middle of the layers (K) |
---|
45 | REAL pdt(ngrid,nlay) ! tendance temperature des autres param. |
---|
46 | |
---|
47 | real pq(ngrid,nlay,nq) ! traceur (kg/kg) |
---|
48 | real pdq(ngrid,nlay,nq) ! tendance avant condensation (kg/kg.s-1) |
---|
49 | |
---|
50 | REAL tau(ngridmx,naerkind) ! Column dust optical depth at each point |
---|
51 | REAL tauscaling(ngridmx) ! Convertion factor for dust amount |
---|
52 | real rdust(ngridmx,nlayermx) ! Dust geometric mean radius (m) |
---|
53 | |
---|
54 | c Outputs: |
---|
55 | c ------- |
---|
56 | |
---|
57 | real pdqcloud(ngrid,nlay,nq) ! tendance de la condensation H2O(kg/kg.s-1) |
---|
58 | real pdqscloud(ngrid,nq) ! flux en surface (kg.m-2.s-1) |
---|
59 | REAL pdtcloud(ngrid,nlay) ! tendance temperature due |
---|
60 | ! a la chaleur latente |
---|
61 | |
---|
62 | REAL rice(ngrid,nlay) ! Ice mass mean radius (m) |
---|
63 | ! (r_c in montmessin_2004) |
---|
64 | REAL nuice(ngrid,nlay) ! Estimated effective variance |
---|
65 | ! of the size distribution |
---|
66 | real rsedcloud(ngridmx,nlayermx) ! Cloud sedimentation radius |
---|
67 | real rhocloud(ngridmx,nlayermx) ! Cloud density (kg.m-3) |
---|
68 | |
---|
69 | c local: |
---|
70 | c ------ |
---|
71 | |
---|
72 | INTEGER ig,l |
---|
73 | LOGICAL,SAVE :: firstcall=.true. |
---|
74 | |
---|
75 | c ** un petit test de coherence |
---|
76 | c -------------------------- |
---|
77 | |
---|
78 | IF (firstcall) THEN |
---|
79 | IF(ngrid.NE.ngridmx) THEN |
---|
80 | PRINT*,'STOP dans watercloud' |
---|
81 | PRINT*,'probleme de dimensions :' |
---|
82 | PRINT*,'ngrid =',ngrid |
---|
83 | PRINT*,'ngridmx =',ngridmx |
---|
84 | STOP |
---|
85 | ENDIF |
---|
86 | |
---|
87 | if (nq.gt.nqmx) then |
---|
88 | write(*,*) 'stop in watercloud (nq.gt.nqmx)!' |
---|
89 | write(*,*) 'nq=',nq,' nqmx=',nqmx |
---|
90 | stop |
---|
91 | endif |
---|
92 | |
---|
93 | write(*,*) "watercloud: igcm_h2o_vap=",igcm_h2o_vap |
---|
94 | write(*,*) " igcm_h2o_ice=",igcm_h2o_ice |
---|
95 | |
---|
96 | firstcall=.false. |
---|
97 | ENDIF ! of IF (firstcall) |
---|
98 | |
---|
99 | c Main call to the different cloud schemes: |
---|
100 | IF (microphys) THEN |
---|
101 | CALL improvedclouds(ngrid,nlay,ptimestep, |
---|
102 | & pplev,pplay,pt,pdt, |
---|
103 | & pq,pdq,pdqcloud,pdqscloud,pdtcloud, |
---|
104 | & nq,tauscaling,rdust,rice,nuice, |
---|
105 | & rsedcloud,rhocloud) |
---|
106 | ELSE |
---|
107 | CALL simpleclouds(ngrid,nlay,ptimestep, |
---|
108 | & pplev,pplay,pzlev,pzlay,pt,pdt, |
---|
109 | & pq,pdq,pdqcloud,pdqscloud,pdtcloud, |
---|
110 | & nq,tau,rice,nuice,rsedcloud) |
---|
111 | ENDIF |
---|
112 | |
---|
113 | c A correction if a lot of subliming CO2 fills the 1st layer FF04/2005 |
---|
114 | c ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
115 | c Then that should not affect the ice particle radius |
---|
116 | do ig=1,ngridmx |
---|
117 | if(pdpsrf(ig)*ptimestep.gt.0.9*(pplev(ig,1)-pplev(ig,2)))then |
---|
118 | if(pdpsrf(ig)*ptimestep.gt.0.9*(pplev(ig,1)-pplev(ig,3))) |
---|
119 | & rice(ig,2)=rice(ig,3) |
---|
120 | rice(ig,1)=rice(ig,2) |
---|
121 | end if |
---|
122 | end do |
---|
123 | |
---|
124 | c======================================================================= |
---|
125 | |
---|
126 | !!!!!!!!!! FOR PHOTOCHEMISTRY, REIMPLEMENT output of surfdust/surfice |
---|
127 | !! if (photochem) then |
---|
128 | !!c computation of dust and ice surface area (micron2/cm3) |
---|
129 | !!c for heterogeneous chemistry |
---|
130 | !! |
---|
131 | !! do l = 1,nlay |
---|
132 | !! do ig = 1,ngrid |
---|
133 | !!c |
---|
134 | !!c npart: number density of ccn in #/cm3 |
---|
135 | !!c |
---|
136 | !! npart(ig,l) = 1.e-6*ccn(ig,l) |
---|
137 | !! $ *masse(ig,l)/epaisseur(ig,l) |
---|
138 | !!c |
---|
139 | !!c dust and ice surface area |
---|
140 | !!c |
---|
141 | !! surfdust(ig,l) = npart(ig,l)*4.*pi*1.e12*rdust(ig,l)**2 |
---|
142 | !!c |
---|
143 | !! if (rice(ig,l) .ge. rdust(ig,l)) then |
---|
144 | !! surfice(ig,l) = npart(ig,l)*4.*pi*1.e12*rice(ig,l)**2 |
---|
145 | !! surfdust(ig,l) = 0. |
---|
146 | !! else |
---|
147 | !! surfice(ig,l) = 0. |
---|
148 | !! end if |
---|
149 | !! end do ! of do ig=1,ngrid |
---|
150 | !! end do ! of do l=1,nlay |
---|
151 | !! end if ! of photochem |
---|
152 | |
---|
153 | |
---|
154 | RETURN |
---|
155 | END |
---|
156 | |
---|