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

Annotation of /MITgcm/pkg/aim_v23/phy_driver.F

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


Revision 1.2 - (hide annotations) (download)
Thu May 22 03:00:49 2003 UTC (20 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint51k_post, checkpoint52l_pre, hrcube4, hrcube5, checkpoint52d_pre, checkpoint52j_pre, checkpoint51o_pre, checkpoint51l_post, checkpoint52k_post, checkpoint51, checkpoint52, checkpoint52f_post, checkpoint51f_post, checkpoint51d_post, checkpoint51t_post, checkpoint51n_post, checkpoint52i_pre, hrcube_1, hrcube_2, hrcube_3, checkpoint51s_post, checkpoint51j_post, checkpoint52e_pre, checkpoint52e_post, checkpoint51n_pre, checkpoint52b_pre, checkpoint51l_pre, checkpoint51q_post, checkpoint51b_pre, checkpoint52b_post, checkpoint52c_post, checkpoint51h_pre, checkpoint50f_post, checkpoint50f_pre, checkpoint52f_pre, branchpoint-genmake2, checkpoint51r_post, checkpoint51i_post, checkpoint51b_post, checkpoint51c_post, checkpoint52d_post, checkpoint50g_post, checkpoint52a_pre, checkpoint50h_post, checkpoint52i_post, checkpoint50i_post, checkpoint51i_pre, checkpoint52h_pre, checkpoint52j_post, branch-netcdf, checkpoint51e_post, checkpoint51o_post, checkpoint51f_pre, checkpoint52a_post, checkpoint51g_post, ecco_c52_e35, checkpoint51m_post, checkpoint51a_post, checkpoint51p_post, checkpoint51u_post
Branch point for: branch-genmake2, branch-nonh, tg2-branch, netcdf-sm0, checkpoint51n_branch
Changes since 1.1: +2 -2 lines
o use Pot.Temp (new argument, S/R phy_suflux) to compute near ground temp (T1).
   ==> now also valid with Partal Cell.
o change Evap over land according to F.M. paper.

1 jmc 1.2 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/phy_driver.F,v 1.1 2002/11/22 17:17:03 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "AIM_OPTIONS.h"
5    
6     SUBROUTINE PHY_DRIVER (tYear, myTime, myIter, bi, bj, myThid )
7    
8     C------------------------
9     C from SPEDDY code: (part of original code left with c_FM)
10     C * S/R PHYPAR : except interp. dynamical Var. from Spectral of grid point
11     C here dynamical var. are loaded within S/R AIM_DYN2AIM.
12     C * S/R FORDATE: only the CALL SOL_OZ (done once / day in SPEEDY)
13     C------------------------
14     C-- SUBROUTINE PHYDRIVER (tYear, myTime, bi, bj, myThid )
15     C-- Purpose: stand-alone driver for physical parametrization routines
16     C-- Input : TYEAR : fraction of year (0 = 1jan.00, 1 = 31dec.24)
17     C-- grid-point model fields in common block: PHYGR1
18     C-- forcing fields in common blocks : LSMASK, FORFIX, FORCIN
19     C-- Output : Diagnosed upper-air variables in common block: PHYGR2
20     C-- Diagnosed surface variables in common block: PHYGR3
21     C-- Physical param. tendencies in common block: PHYTEN
22     C-- Surface and upper boundary fluxes in common block: FLUXES
23     C-------
24     C Note: tendencies are not /dpFac here but later in AIM_AIM2DYN
25     C-------
26    
27     IMPLICIT NONE
28    
29     C Resolution parameters
30    
31     C-- size for MITgcm & Physics package :
32     #include "AIM_SIZE.h"
33     #include "EEPARAMS.h"
34     #include "AIM_GRID.h"
35    
36     C Constants + functions of sigma and latitude
37     #include "com_physcon.h"
38    
39     C Model variables, tendencies and fluxes on gaussian grid
40     #include "com_physvar.h"
41    
42     C Surface forcing fields (time-inv. or functions of seasonal cycle)
43     #include "com_forcing.h"
44    
45     C Constants for forcing fields:
46     #include "com_forcon.h"
47    
48     C Radiation scheme variables
49     #include "com_radvar.h"
50    
51     c #include "com_sflcon.h"
52    
53     C Logical flags
54     c_FM include "com_lflags.h"
55    
56     C-- Routine arguments:
57     _RL tYear, myTime
58     INTEGER myIter, bi,bj, myThid
59    
60     #ifdef ALLOW_AIM
61    
62     C-- Local variables:
63     C kGrd = Ground level index (2-dim)
64     C dpFac = cell delta_P fraction (3-dim)
65     LOGICAL LRADSW
66     INTEGER ICLTOP(NGP)
67     INTEGER kGround(NGP)
68     _RL dpFac(NGP,NLEV)
69     c_FM REAL RPS(NGP), ST4S(NGP)
70     _RL ST4S(NGP)
71     _RL PSG_1(NGP), RPS_1
72    
73     INTEGER J, K
74    
75     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
76    
77     C-- 1. Compute grid-point fields
78    
79     C- 1.1 Convert model spectral variables to grid-point variables
80    
81     CALL AIM_DYN2AIM(
82     O TG1, QG1, SE, VsurfSq, PSG, dpFac, kGround,
83     I bi, bj, myTime, myIter, myThid )
84    
85     C- 1.2 Compute thermodynamic variables
86    
87     C- 1.2.a Surface pressure (ps), 1/ps and surface temperature
88     RPS_1 = 1. _d 0
89     DO J=1,NGP
90     PSG_1(J)=1. _d 0
91     c_FM PSG(J)=EXP(PSLG1(J))
92     c_FM RPS(J)=1./PSG(J)
93     ENDDO
94    
95     C 1.2.b Dry static energy
96     C <= replaced by Pot.Temp in aim_dyn2aim
97     c DO K=1,NLEV
98     c DO J=1,NGP
99     c_FM SE(J,K)=CP*TG1(J,K)+PHIG1(J,K)
100     c ENDDO
101     c ENDDO
102    
103     C 1.2.c Relative humidity and saturation spec. humidity
104    
105     DO K=1,NLEV
106     c_FM CALL SHTORH (1,NGP,TG1(1,K),PSG,SIG(K),QG1(1,K),
107     c_FM & RH(1,K),QSAT(1,K))
108     CALL SHTORH (1,NGP,TG1(1,K),PSG_1,SIG(K),QG1(1,K),
109     O RH(1,K,myThid),QSAT(1,K),
110     I myThid)
111     ENDDO
112    
113     C-- 2. Precipitation
114    
115     C 2.1 Deep convection
116    
117     c_FM CALL CONVMF (PSG,SE,QG1,QSAT,
118     c_FM & ICLTOP,CBMF,PRECNV,TT_CNV,QT_CNV)
119     CALL CONVMF (PSG,dpFac,SE,QG1,QSAT,
120     O ICLTOP,CBMF(1,myThid),PRECNV(1,myThid),
121     O TT_CNV(1,1,myThid),QT_CNV(1,1,myThid),
122     I kGround,bi,bj,myThid)
123    
124     DO K=2,NLEV
125     DO J=1,NGP
126     TT_CNV(J,K,myThid)=TT_CNV(J,K,myThid)*RPS_1*GRDSCP(K)
127     QT_CNV(J,K,myThid)=QT_CNV(J,K,myThid)*RPS_1*GRDSIG(K)
128     ENDDO
129     ENDDO
130    
131     C 2.2 Large-scale condensation
132    
133     c_FM CALL LSCOND (PSG,QG1,QSAT,
134     c_FM & PRECLS,TT_LSC,QT_LSC)
135     CALL LSCOND (PSG,dpFac,QG1,QSAT,
136     O PRECLS(1,myThid),TT_LSC(1,1,myThid),
137     O QT_LSC(1,1,myThid),
138     I kGround,bi,bj,myThid)
139    
140     C-- 3. Radiation (shortwave and longwave) and surface fluxes
141    
142     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
143     C --> from FORDATE (in SPEEDY) :
144    
145     C 3.0 Compute Incomming shortwave rad. (from FORDATE in SPEEDY)
146    
147     c_FM CALL SOL_OZ (SOLC,TYEAR)
148     CALL SOL_OZ (SOLC,tYear, snLat(1,myThid), csLat(1,myThid),
149     O FSOL, OZONE, OZUPP, ZENIT, STRATZ,
150     I bi,bj,myThid)
151    
152     C <-- from FORDATE (in SPEEDY).
153     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
154    
155     C 3.1 Compute shortwave tendencies and initialize lw transmissivity
156    
157     C The sw radiation may be called at selected time steps
158     LRADSW = .TRUE.
159    
160     IF (LRADSW) THEN
161    
162     c_FM CALL RADSW (PSG,QG1,RH,ALB1,
163     c_FM & ICLTOP,CLOUDC,TSR,SSR,TT_RSW)
164     CALL RADSW (PSG,dpFac,QG1,RH(1,1,myThid),ALB1(1,myThid),
165     I FSOL, OZONE, OZUPP, ZENIT, STRATZ,
166     O TAU2, STRATC,
167     O ICLTOP,CLOUDC(1,myThid),
168     O TSR(1,myThid),SSR(1,myThid),TT_RSW(1,1,myThid),
169     I kGround,bi,bj,myThid)
170    
171     DO J=1,NGP
172     CLTOP(J,myThid)=SIGH(ICLTOP(J)-1)*PSG_1(J)
173     ENDDO
174    
175     DO K=1,NLEV
176     DO J=1,NGP
177     TT_RSW(J,K,myThid)=TT_RSW(J,K,myThid)*RPS_1*GRDSCP(K)
178     ENDDO
179     ENDDO
180    
181     ENDIF
182    
183     C 3.2 Compute downward longwave fluxes
184    
185     c_FM CALL RADLW (-1,TG1,TS,ST4S,
186     c_FM & OLR,SLR,TT_RLW)
187     CALL RADLW (-1,TG1,TS(1,myThid),ST4S,
188     & OZUPP, STRATC, TAU2, FLUX, ST4A,
189     O OLR(1,myThid),SLR(1,myThid),TT_RLW(1,1,myThid),
190     I kGround,bi,bj,myThid)
191    
192     C 3.3. Compute surface fluxes and land skin temperature
193    
194     c_FM CALL SUFLUX (PSG,UG1,VG1,TG1,QG1,RH,PHIG1,
195     c_FM & PHIS0,FMASK1,STL1,SST1,SOILW1,SSR,SLR,
196     c_FM & USTR,VSTR,SHF,EVAP,ST4S,
197     c_FM & TS,TSKIN,U0,V0,T0,Q0)
198 jmc 1.2 CALL SUFLUX (PSG, TG1, QG1, RH(1,1,myThid), SE, VsurfSq,
199 jmc 1.1 I WVSurf(1,myThid),csLat(1,myThid),fOrogr(1,myThid),
200     I FMASK1(1,myThid),STL1(1,myThid),SST1(1,myThid),
201     I SOILW1(1,myThid), SSR(1,myThid),SLR(1,myThid),
202     O SPEED0(1,myThid),DRAG(1,1,myThid),
203     O SHF(1,1,myThid), EVAP(1,1,myThid),
204     O ST4S,TS(1,myThid),TSKIN(1,myThid),
205     O T0(1,myThid),Q0(1,myThid),
206     I kGround,bi,bj,myThid)
207    
208     C 3.4 Compute upward longwave fluxes, convert them to tendencies
209     C and add shortwave tendencies
210    
211     c_FM CALL RADLW (1,TG1,TS,ST4S,
212     c_FM & OLR,SLR,TT_RLW)
213     CALL RADLW (1,TG1,TS(1,myThid),ST4S,
214     & OZUPP, STRATC, TAU2, FLUX, ST4A,
215     O OLR(1,myThid),SLR(1,myThid),TT_RLW(1,1,myThid),
216     I kGround,bi,bj,myThid)
217    
218     DO K=1,NLEV
219     DO J=1,NGP
220     TT_RLW(J,K,myThid)=TT_RLW(J,K,myThid)*RPS_1*GRDSCP(K)
221     c_FM TTEND (J,K)=TTEND(J,K)+TT_RSW(J,K)+TT_RLW(J,K)
222     ENDDO
223     ENDDO
224    
225     C-- 4. PBL interactions with lower troposphere
226    
227     C 4.1 Vertical diffusion and shallow convection
228    
229     c_FM CALL VDIFSC (UG1,VG1,SE,RH,QG1,QSAT,PHIG1,
230     c_FM & UT_PBL,VT_PBL,TT_PBL,QT_PBL)
231     CALL VDIFSC (dpFac, SE, RH(1,1,myThid), QG1, QSAT,
232     O TT_PBL(1,1,myThid),QT_PBL(1,1,myThid),
233     I kGround,bi,bj,myThid)
234    
235     C 4.2 Add tendencies due to surface fluxes
236    
237     DO J=1,NGP
238     c_FM UT_PBL(J,NLEV)=UT_PBL(J,NLEV)+USTR(J,3)*RPS(J)*GRDSIG(NLEV)
239     c_FM VT_PBL(J,NLEV)=VT_PBL(J,NLEV)+VSTR(J,3)*RPS(J)*GRDSIG(NLEV)
240     c_FM TT_PBL(J,NLEV)=TT_PBL(J,NLEV)+ SHF(J,3)*RPS(J)*GRDSCP(NLEV)
241     c_FM QT_PBL(J,NLEV)=QT_PBL(J,NLEV)+EVAP(J,3)*RPS(J)*GRDSIG(NLEV)
242     K = kGround(J)
243     IF ( K.GT.0 ) THEN
244     TT_PBL(J,K,myThid) = TT_PBL(J,K,myThid)
245     & + SHF(J,3,myThid) *RPS_1*GRDSCP(K)
246     QT_PBL(J,K,myThid) = QT_PBL(J,K,myThid)
247     & + EVAP(J,3,myThid)*RPS_1*GRDSIG(K)
248     ENDIF
249     ENDDO
250    
251     c_FM DO K=1,NLEV
252     c_FM DO J=1,NGP
253     c_FM UTEND(J,K)=UTEND(J,K)+UT_PBL(J,K)
254     c_FM VTEND(J,K)=VTEND(J,K)+VT_PBL(J,K)
255     c_FM TTEND(J,K)=TTEND(J,K)+TT_PBL(J,K)
256     c_FM QTEND(J,K)=QTEND(J,K)+QT_PBL(J,K)
257     c_FM ENDDO
258     c_FM ENDDO
259    
260     #endif /* ALLOW_AIM */
261    
262     RETURN
263     END

  ViewVC Help
Powered by ViewVC 1.1.22