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

Annotation of /MITgcm/pkg/aim/phy_driver.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: checkpoint35, pre38tag1, c37_adj, pre38-close, checkpoint37, checkpoint39, checkpoint38, checkpoint36
Branch point for: pre38
Changes since 1.1: +224 -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/phy_driver.F,v 1.1.2.2 2001/01/26 17:54:25 adcroft Exp $
2     C $Name: branch-atmos-merge-freeze $
3    
4     SUBROUTINE PDRIVER (TYEAR)
5     C--
6     C-- SUBROUTINE PDRIVER (TYEAR)
7     C--
8     C-- Purpose: stand-alone driver for physical parametrization routines
9     C-- Input : TYEAR : fraction of year (0 = 1jan.00, 1 = 31dec.24)
10     C-- grid-point model fields in common block: PHYGR1
11     C-- forcing fields in common blocks : LSMASK, FORFIX, FORCIN
12     C-- Output : Diagnosed upper-air variables in common block: PHYGR2
13     C-- Diagnosed surface variables in common block: PHYGR3
14     C-- Physical param. tendencies in common block: PHYTEN
15     C-- Surface and upper boundary fluxes in common block: FLUXES
16     C--
17    
18    
19     IMPLICIT rEAL*8 ( A-H,O-Z)
20    
21    
22     C Resolution parameters
23     C
24     #include "atparam.h"
25     #include "atparam1.h"
26     C
27     PARAMETER ( NLON=IX, NLAT=IL, NLEV=KX, NGP=NLON*NLAT )
28     C
29     C Constants + functions of sigma and latitude
30     C
31     #include "Lev_def.h"
32     #include "com_physcon.h"
33     C
34     C Model variables, tendencies and fluxes on gaussian grid
35     C
36     #include "com_physvar.h"
37     C
38     C Surface forcing fields (time-inv. or functions of seasonal cycle)
39     C
40     #include "com_forcing1.h"
41     #include "com_forcon.h"
42     #include "com_sflcon.h"
43    
44     REAL TYEAR
45    
46     INTEGER IDEPTH(NGP)
47     REAL RPS(NGP), ALB1(NGP), FSOL1(NGP), OZONE1(NGP)
48     CcnhDebugStarts
49     LOGICAL CALL1
50     DATA CALL1 /.TRUE./
51     SAVE CALL1
52     REAL AUX(NGP)
53     REAL Phymask(NGP,NLEV)
54     real xminim
55     REAL UT_VDI(NGP,NLEV), VT_VDI(NGP,NLEV), TT_VDI(NGP,NLEV)
56     REAL QT_VDI(NGP,NLEV)
57     CcnhDebugEnds
58    
59    
60     C-- 1. Compute surface variables
61    
62     C 1.1 Surface pressure (ps), 1/ps and surface temperature
63     C
64     DO J=1,NGP
65     PSG(J)=EXP(PSLG1(J))
66     RPS(J)=1./PSG(J)
67     TS(J) =SST1(J)+FMASK1(J)*(STL1(J)-SST1(J))
68     ENDDO
69    
70     C 1.2 Surface albedo:
71     C defined as a weighed average of land and ocean albedos, where
72     C land albedo depends linearly on snow depth (up to the SDALB
73     C threshold) and sea albedo depends linearly on sea-ice fraction.
74     C
75     DALB=ALBICE-ALBSEA
76     RSD=1./SDALB
77     C
78     CmoltBegin
79     DO J=1,NGP
80     ALB1(J)=ALB0(J)
81     ENDDO
82     CmoltEnd
83    
84     C-- 2. Compute thermodynamic variables
85    
86     C 2.1 Dry static energy
87    
88     DO K=1,NLEV
89     DO J=1,NGP
90     SE(J,K)=CP*TG1(J,K)+PHIG1(J,K)
91     ENDDO
92     ENDDO
93     C
94     C 2.2 Relative humidity and saturation spec. humidity
95     C
96     DO K=1,NLEV
97     CALL SHTORH (1,NGP,TG1(1,K),PSG,SIG(K),QG1(1,K),
98     * RH(1,K),QSAT(1,K))
99     ENDDO
100     C
101     DO K=1,NLEV
102     DO J=1,NGP
103     phymask(J,K)=0.
104     IF (Tg1(J,K).ne.0.) THEN
105     phymask(J,K)=1.
106     ENDIF
107     QSAT(J,K)=QSAT(J,K)*Phymask(J,K)
108     QG1(J,K)=QG1(J,K)*Phymask(J,K)
109     RH(J,K)=RH(J,K)*Phymask(J,K)
110     ENDDO
111     ENDDO
112     cdbgch
113     C
114     C-- 3. Precipitation
115    
116     C 3.1 Deep convection
117     C
118     cch CALL CONVMF (PSG,SE,QG1,QSAT,
119     CALL CONVMF (PSG,TG1,QG1,QSAT,
120     * IDEPTH,CBMF,PRECNV,TT_CNV,QT_CNV)
121     C
122     DO K=2,NLEV
123     DO J=1,NGP
124     TT_CNV(J,K)=TT_CNV(J,K)*RPS(J)*GRDSCP(K)
125     QT_CNV(J,K)=QT_CNV(J,K)*RPS(J)*GRDSIG(K)
126     ENDDO
127     ENDDO
128    
129     C 3.2 Large-scale condensation
130    
131     CALL LSCOND (PSG,QG1,QSAT,
132     * PRECLS,TT_LSC,QT_LSC)
133    
134     C
135     C-- 4. Radiation (shortwave and longwave)
136    
137     C 4.1 Compute climatological forcing
138    
139     CALL SOL_OZ (SOLC,TYEAR,FSOL1,OZONE1)
140    
141     C 4.2 Compute shortwave tendencies and initialize lw transmissivity
142     C (The sw radiation may be called at selected time steps)
143    
144     CALL RADSW (PSG,QG1,RH,
145     * FSOL1,OZONE1,ALB1,
146     * CLOUDC,TSR,SSR,TT_RSW)
147    
148     C 4.3 Compute longwave fluxes
149    
150     CALL RADLW (1,TG1,TS,ST4S,
151     * OLR,SLR,TT_RLW,SLR_DOWN)
152    
153     DO K=1,NLEV
154     DO J=1,NGP
155     TT_RSW(J,K)=TT_RSW(J,K)*RPS(J)*GRDSCP(K)
156     TT_RLW(J,K)=TT_RLW(J,K)*RPS(J)*GRDSCP(K)
157     ENDDO
158     ENDDO
159     C
160     C-- 5. PBL interactions with lower troposphere and surface
161    
162     C 5.1. Surface fluxes (from climatological surface temperature)
163    
164     cch Attention the pressure used is a the last T level and
165     Cch not at the last W level
166     C --------------------------------
167     CALL SUFLUX (PNLEVW,UG1,VG1,TG1,QG1,RH,QSAT,PHIG1,
168     * PHI0,FMASK1,STL1,SST1,SOILQ1,SSR,SLR,
169     * USTR,VSTR,SHF,EVAP,T0,Q0,QSAT0,SPEED0)
170    
171     C
172     C remove when vdifsc is implemented
173     DO K=1,NLEV
174     DO J=1,NGP
175     UT_PBL(J,K)=0.
176     VT_PBL(J,K)=0.
177     TT_PBL(J,K)=0.
178     QT_PBL(J,K)=0.
179     ENDDO
180     ENDDO
181     c
182     C
183     c
184     C 5.3 Add surface fluxes and convert fluxes to tendencies
185    
186     DO J=1,NGP
187     IF ( NLEVxy(J) .GT. 0 ) THEN
188     UT_PBL(J,NLEVxy(J))=UT_PBL(J,NLEVxy(J))+ USTR(J,3)
189     VT_PBL(J,NLEVxy(J))=VT_PBL(J,NLEVxy(J))+ VSTR(J,3)
190     TT_PBL(J,NLEVxy(J))=TT_PBL(J,NLEVxy(J))+ SHF(J,3)
191     QT_PBL(J,NLEVxy(J))=QT_PBL(J,NLEVxy(J))+ EVAP(J,3)
192     ENDIF
193     ENDDO
194     C
195     Cdbgch
196     DO J=1,NGP
197     IF ( NLEVxy(J) .GT. 0 ) THEN
198     DO K=NLEVxy(J)-1,NLEVxy(J)
199     UT_PBL(J,K)=UT_PBL(J,K)*GRDSIG(K)
200     VT_PBL(J,K)=VT_PBL(J,K)*GRDSIG(K)
201     TT_PBL(J,K)=TT_PBL(J,K)*GRDSCP(K)
202     QT_PBL(J,K)=QT_PBL(J,K)*GRDSIG(K)
203     ENDDO
204     ENDIF
205     ENDDO
206     C
207     C 5.2 Vertical diffusion and shallow convection (not yet implemented)
208     C
209     CALL VDIFSC (UG1,VG1,TG1,RH, QG1, QSAT,
210     * UT_VDI,VT_VDI,TT_VDI,QT_VDI)
211     C
212     DO K=1,NLEV
213     DO J=1,NGP
214     UT_PBL(J,K)=UT_PBL(J,K)+ UT_VDI(J,K)
215     VT_PBL(J,K)=VT_PBL(J,K)+ VT_VDI(J,K)
216     TT_PBL(J,K)=TT_PBL(J,K)+ TT_VDI(J,K)
217     QT_PBL(J,K)=QT_PBL(J,K)+ QT_VDI(J,K)
218     ENDDO
219     ENDDO
220     C
221    
222     CdbgC--
223     RETURN
224     END

  ViewVC Help
Powered by ViewVC 1.1.22