/[MITgcm]/MITgcm/pkg/aim/ini_inphys.F
ViewVC logotype

Annotation of /MITgcm/pkg/aim/ini_inphys.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.2 - (hide annotations) (download)
Fri Feb 2 21:36:29 2001 UTC (23 years, 4 months ago) by adcroft
Branch: MAIN
CVS Tags: pre38tag1, c37_adj, pre38-close, checkpoint39, checkpoint38, checkpoint37, checkpoint36, checkpoint35
Branch point for: pre38
Changes since 1.1: +246 -0 lines
Merged changes from branch "branch-atmos-merge" into MAIN (checkpoint34)
 - substantial modifications to algorithm sequence (dynamics.F)
 - packaged OBCS, Shapiro filter, Zonal filter, Atmospheric Physics

1 adcroft 1.2 C $Header: /u/gcmpack/models/MITgcmUV/pkg/aim/Attic/ini_inphys.F,v 1.1.2.2 2001/01/26 17:53:55 adcroft Exp $
2     C $Name: branch-atmos-merge-freeze $
3    
4     #include "CPP_OPTIONS.h"
5    
6     SUBROUTINE INPHYS (FSG,HSG,RLAT)
7    
8     IMPLICIT rEAL*8 ( A-H,O-Z)
9    
10     C--
11     C-- SUBROUTINE INPHYS (FSG,HSG,RLAT)
12     C--
13     C-- Purpose: Initialize common blocks for physical parametrization routines
14     C-- Input : FSG : sigma at full levels
15     C-- HSG : sigma at half levels
16     C-- RLAT : gaussian-grid latitudes
17     C-- Initialized common blocks: PHYCON, FSIGMU, VDICON,
18     C-- FORCON, SFLCON, CNVCON, LSCCON, RADCON
19     C--
20     C Resolution parameters
21     C
22     C
23     #include "atparam.h"
24     #include "atparam1.h"
25     C
26     PARAMETER ( NLON=IX, NLAT=IL, NLEV=KX, NGP=NLON*NLAT )
27     C
28     C
29     #include "Lev_def.h"
30    
31     #include "GRID.h"
32     #include "EEPARAMS.h"
33     #include "PARAMS.h"
34     C
35     C Physical constants + functions of sigma and latitude
36     C
37     #include "com_physcon.h"
38     C
39     C Constants for sub-grid-scale physics
40     C
41     #include "com_forcon.h"
42     #include "com_sflcon.h"
43     #include "com_cnvcon.h"
44     #include "com_lsccon.h"
45     #include "com_radcon.h"
46     #include "com_vdicon.h"
47     C
48     C == Routine Arguments ==
49     REAL FSG(NLEV), HSG(0:NLEV), RLAT(NLAT)
50    
51     C == Local Variables ==
52     INTEGER I2
53     INTEGER bi, bj
54     DATA Pground /1. _d +5/
55    
56     C == Set for a single tile per proc. for now
57     bi = 1
58     bj = 1
59     C
60     C--- 1. Time independent parameters and arrays
61     C
62     C 1.1 Physical constants
63     C
64     P0 = 1. _d +5
65     GG = 9.81 _d 0
66     RD = 287. _d 0
67     CP = 1004. _d 0
68     C Latent heat is in J/g for consistency with spec.hum. in g/Kg
69     ALHC = 2501. _d 0
70     SBC = 5.67 _d -8
71     C
72     C 1.2 Functions of sigma and latitude
73     C
74     SIGH(0)=HSG(0)
75     C
76     DO K=1,NLEV
77     SIG(K) = FSG(K)
78     Cg77 SIGL(K) = DLOG(FSG(K))
79     SIGL(K) = LOG(FSG(K))
80     SIGH(K) = HSG(K)
81     DSIG(K) = HSG(K)-HSG(K-1)
82     C POUT(K) = PRLEV(FSG(K))
83     GRDSIG(K) = GG/(DSIG(K)*P0)
84     GRDSCP(K) = GRDSIG(K)/CP
85     ENDDO
86     C
87     C Weights for vertical interpolation at half-levels(1,nlev) and surface
88     C Note that for phys.par. half-lev(k) is between full-lev k and k+1
89     C Fhalf(k) = Ffull(k)+WVI(K,2)*(Ffull(k+1)-Ffull(k))
90     C Fsurf = Ffull(nlev)+WVI(nlev,2)*(Ffull(nlev)-Ffull(nlev-1))
91     C
92     DO K=1,NLEV-1
93     WVI(K,1)=1./(SIGL(K+1)-SIGL(K))
94     WVI(K,2)=(DLOG(SIGH(K))-SIGL(K))*WVI(K,1)
95     ENDDO
96     C
97     WVI(NLEV,1)=0.
98     WVI(NLEV,2)=-SIGL(NLEV)*WVI(NLEV-1,2)
99     cchdbg
100     WVI(NLEV,2)=-SIGL(NLEV)*WVI(NLEV-1,1)
101     cchdbg
102     C
103     DO J=1,NLAT
104     FMU(J,1)=SIN(RLAT(J))
105     FMU(J,2)=1.5 _d 0*FMU(J,1)**2-0.5 _d 0
106     ENDDO
107     C
108     C--- 2. Constants for boundary forcing (common FORCON):
109     C
110     SOLC = 342. _d 0
111    
112     ALBSEA = 0.07 _d 0
113     ALBICE = 0.60 _d 0
114     ALBSN = 0.60 _d 0
115     SDALB = 60. _d 0
116     SWCAP = 75. _d 0
117     SWWIL = 0. _d 0
118     C
119     C--- 3. Constants for surface fluxes (common SFLCON):
120     C
121     FWIND0 = 0.6 _d 0
122     cchdbg *****************************************************
123     FWIND0 = 0.6 _d 0*0.7 _d 0
124     cchdbg ******************************************************
125     cchdbg FTEMP0 = 1.
126     cchdbg FHUM0 = 1.
127     FTEMP0 = 0. _d 0
128     FHUM0 = 0.5 _d 0
129     FHUM0 = 1. _d 0
130    
131     c CDL = 3.0E-3
132     c CDS = 1.2E-3
133     c CHL = 1.2E-3
134     c CHS = 1.2E-3
135     CDL = 1.8 _d -3
136     CDS = 0.8 _d -3
137     CHL = 2.0 _d -3
138     CHS = 0.9 _d -3
139     C
140     VGUST = 4. _d 0
141     DTHETAF = 3. _d 0
142     FSTAB = 0.67 _d 0
143     C
144     C--- 4. Constants for convection (common CNVCON):
145     C
146     RHBL = 0.8 _d 0
147     TRCNV = 6. _d 0
148     ENTMAX = 0.5 _d 0
149     C
150     C--- 5. Constants for large-scale condensation (common LSCCON):
151     C
152     RHLSC = 0.9 _d 0
153     TRLSC = 4. _d 0
154     C
155     C--- 6. Constants for radiation (common RADCON):
156     C
157     ABSSW = 0.06 _d 0
158     cchdbg ********************
159     ABSSW = 0.04 _d 0
160     ABSSW = 0.06 _d 0
161     cchdbg *********************
162     ABSLW = 1.40 _d 0
163     cchdbg ****************************************************
164     cch ABSLW = 1.00
165     cchdbg ****************************************************
166    
167     ABWSW = 0.06 _d 0
168     ABWLW = 0.55 _d 0
169     cchdbg ****************************************************
170     ABWLW = 0.60 _d 0
171     cchdbg ABWLW = 0.65
172     cchdbg ABWLW = 0.90
173     cchdbg ****************************************************
174    
175     ABCSW = 0.0 _d 0
176     ABCLW = 0.15 _d 0
177     ABCLW = 0.15 _d 0
178     cchdbg *******************************************
179     c ABCLW = 3.0
180     c ABCLW = 2.0
181     cch ABCLW = 3.5
182     cch ABCLW = 2.5
183     cch ABCLW = 2.8
184     cchdbg ********************************************
185    
186     EPSSW = 0.03 _d 0
187     EPSLW = 0.05 _d 0
188    
189     ALBCL = 0.50 _d 0
190     cchdbg *******************************************
191     ALBCL = 0.49 _d 0
192     ALBCL = 0.47 _d 0
193     ALBCL = 0.40 _d 0
194     ALBCL = 0.35 _d 0
195     ALBCL = 0.33 _d 0
196     ALBCL = 0.36 _d 0
197     ALBCL = 0.34 _d 0
198     cchdbg ********************************************
199     cchdbg RHCL1 = 0.45
200     cchdbg RHCL2 = 0.85
201     cchdbg QACL = 1.00
202     cchdbg *******************************************
203     RHCL1 = 0.50 _d 0
204     RHCL2 = 0.90 _d 0
205     QACL = 0.50 _d 0
206     cchdbg *******************************************
207     C
208     C 2.6 Constants for vertical diffusion and sh. conv. (common VDICON):
209     C
210     TRVDI = 48. _d 0
211     TRSHC = 24. _d 0
212     cchdbg *******************************************
213     TRSHC = 12. _d 0
214     cchdbg *******************************************
215     C
216     C Computation of the last air-level
217     C ---------------------------------
218     I2=0
219     DO J=1,NLAT
220     DO I=1,NLON
221     I2=I2+1
222     NLEVxy(I2) =0
223     NLEVxyU(I2)=0
224     NLEVxyV(I2)=0
225     DO k=1,NLEV
226     NLEVxy(I2) = NLEVxy(I2) +int( hFacC(I,J,K,bi,bj) )
227     NLEVxyU(I2)= NLEVxyU(I2) +int( hFacW(I,J,K,bi,bj) )
228     NLEVxyV(I2)= NLEVxyV(I2) +int( hFacS(I,J,K,bi,bj) )
229     ENDDO
230     ENDDO
231     ENDDO
232     CcnhDebugStarts
233     UT_PBL = 0.
234     VT_PBL = 0.
235     CcnhDebugEnds
236     C DO I=1,NLON
237     C NLEVxyV(I)=1
238     C ENDDO
239    
240     CcnhDebugStarts
241     C write(0,*) 'MAXVAL(NLEVxy)=',MAXVAL(NLEVxy)
242     C write(0,*) 'MINVAL(NLEVxy)=',MINVAL(NLEVxy)
243     CcnhDebugEnds
244     C
245     RETURN
246     END

  ViewVC Help
Powered by ViewVC 1.1.22