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

Contents of /MITgcm/pkg/aim_v23/aim_dyn2aim.F

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


Revision 1.6 - (show annotations) (download)
Mon May 12 01:32:41 2014 UTC (10 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65o, checkpoint64y, checkpoint64x, checkpoint64z, HEAD
Changes since 1.5: +98 -85 lines
- Acount for true p* correction in theta <-> T conversion in pkg/aim_v23

1 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_dyn2aim.F,v 1.5 2006/08/04 22:27:46 jmc Exp $
2 C $Name: $
3
4 #include "AIM_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: AIM_DYN2AIM
8 C !INTERFACE:
9 SUBROUTINE AIM_DYN2AIM(
10 O TA, QA, ThA, Vsurf2, PSA, dpFac,
11 O kGrd,
12 I bi,bj, myTime, myIter, myThid)
13 C !DESCRIPTION: \bv
14 C *==========================================================*
15 C | S/R AIM_DYN2AIM
16 C | o Map dynamics conforming arrays to AIM internal arrays.
17 C *==========================================================*
18 C | this routine transfers grid information
19 C | and all dynamical variables (T,Q, ...) to AIM physics
20 C *==========================================================*
21 C \ev
22
23 C !USES:
24 IMPLICIT NONE
25 C === Global variables ===
26 C-- size for MITgcm & Physics package :
27 #include "AIM_SIZE.h"
28
29 #include "EEPARAMS.h"
30 #include "PARAMS.h"
31 #include "GRID.h"
32 #include "SURFACE.h"
33 #include "DYNVARS.h"
34
35 #include "AIM_GRID.h"
36 #include "com_physcon.h"
37
38 C !INPUT/OUTPUT PARAMETERS:
39 C-- Input:
40 C bi,bj :: Tile index
41 C myTime :: Current time of simulation ( s )
42 C myIter :: Current iteration number in simulation
43 C myThid :: Number of this instance of the routine
44 C-- Output: TA :: temperature [K} (3-dim)
45 C QA :: specific humidity [g/kg] (3-dim)
46 C ThA :: Pot.Temp. [K] (replace dry stat. energy)(3-dim)
47 C Vsurf2 :: square of surface wind speed (2-dim)
48 C PSA :: norm. surface pressure [p/p0] (2-dim)
49 C dpFac :: cell delta_P fraction (3-dim)
50 C kGrd :: Ground level index (2-dim)
51 C-- Updated common blocks: AIM_GRID_R
52 C WVSurf :: weights for near surf interpolation (2-dim)
53 C fOrogr :: orographic factor (for surface drag) (2-dim)
54 C snLat,csLat :: sin(Lat) & cos(Lat) (2-dim)
55 _RL TA(NGP,NLEV), QA(NGP,NLEV), ThA(NGP,NLEV)
56 _RL Vsurf2(NGP), PSA(NGP), dpFac(NGP,NLEV)
57 INTEGER kGrd(NGP)
58 INTEGER bi, bj, myIter, myThid
59 _RL myTime
60 CEOP
61
62 #ifdef ALLOW_AIM
63 C !LOCAL VARIABLES:
64 C i, j, I2 :: Loop counters
65 C k, Katm :: Loop counters
66 C msgBuf :: Informational/error message buffer
67 CHARACTER*(MAX_LEN_MBUF) msgBuf
68 INTEGER i, j, I2, k, Katm
69 _RL conv_theta2T, temp1, temp2
70
71 c _RL hInitC(5), hInitF(5)
72 c DATA hInitC / 17338.0,10090.02,5296.88,2038.54,418.038/
73 c DATA hInitF / 15090.4, 8050.96, 4087.75, 1657.54, 0. /
74
75 C- Compute Sin & Cos (Latitude) :
76 DO j = 1,sNy
77 DO i = 1,sNx
78 I2 = i+(j-1)*sNx
79 snLat(I2,myThid) = SIN(yC(i,j,bi,bj)*deg2rad)
80 csLat(I2,myThid) = COS(yC(i,j,bi,bj)*deg2rad)
81 ENDDO
82 ENDDO
83
84 C- Set surface level index :
85 DO j = 1,sNy
86 DO i = 1,sNx
87 I2 = i+(j-1)*sNx
88 kGrd(I2) = (Nr+1) - kSurfC(i,j,bi,bj)
89 ENDDO
90 ENDDO
91
92 C- Set (normalized) surface pressure :
93 DO j=1,sNy
94 DO i=1,sNx
95 I2 = i+(j-1)*sNx
96 k = kSurfC(i,j,bi,bj)
97 IF ( k.LE.Nr ) THEN
98 c PSA(I2) = rF(k)/atm_Po
99 PSA(I2) = Ro_surf(i,j,bi,bj)/atm_Po
100 ELSE
101 PSA(I2) = 1.
102 ENDIF
103 ENDDO
104 ENDDO
105
106 C- Set cell delta_P fraction (of the full delta.P = drF_k):
107 #ifdef NONLIN_FRSURF
108 IF ( staggerTimeStep .AND. nonlinFreeSurf.GT.0 ) THEN
109 IF ( select_rStar.GT.0 ) THEN
110 DO k = 1,Nr
111 Katm = _KD2KA( k )
112 DO j = 1,sNy
113 DO i = 1,sNx
114 I2 = i+(j-1)*sNx
115 dpFac(I2,Katm) = h0FacC(i,j,k,bi,bj)*rStarFacC(i,j,bi,bj)
116 c dpFac(I2,Katm) = 1. _d 0
117 ENDDO
118 ENDDO
119 ENDDO
120 ELSE
121 DO k = 1,Nr
122 Katm = _KD2KA( k )
123 DO j = 1,sNy
124 DO i = 1,sNx
125 I2 = i+(j-1)*sNx
126 IF ( k.EQ.kSurfC(i,j,bi,bj) ) THEN
127 dpFac(I2,Katm) = hFac_surfC(i,j,bi,bj)
128 ELSE
129 dpFac(I2,Katm) = hFacC(i,j,k,bi,bj)
130 ENDIF
131 c dpFac(I2,Katm) = 1. _d 0
132 ENDDO
133 ENDDO
134 ENDDO
135 ENDIF
136 ELSE
137 #else /* ndef NONLIN_FRSURF */
138 IF (.TRUE.) THEN
139 #endif /* NONLIN_FRSURF */
140 DO k = 1,Nr
141 Katm = _KD2KA( k )
142 DO j = 1,sNy
143 DO i = 1,sNx
144 I2 = i+(j-1)*sNx
145 dpFac(I2,Katm) = hFacC(i,j,k,bi,bj)
146 c dpFac(I2,Katm) = 1. _d 0
147 ENDDO
148 ENDDO
149 ENDDO
150 ENDIF
151
152 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
153
154 C Physics package works with sub-domains 1:sNx,1:sNy,1:Nr.
155 C Internal index mapping is linear in X and Y with a second
156 C dimension for the vertical.
157
158 C- Dynamical var --> AIM var :
159 C note: UA & VA are not used => removed
160 temp1 = lwTemp1
161 temp2 = lwTemp2
162 DO k = 1,Nr
163 conv_theta2T = (rC(k)/atm_Po)**atm_kappa
164 Katm = _KD2KA( k )
165 DO j = 1,sNy
166 DO i = 1,sNx
167 I2 = i+(j-1)*sNx
168 IF ( maskC(i,j,k,bi,bj).EQ.oneRS ) THEN
169 c UA(I2,Katm) = uVel(i,j,k,bi,bj)
170 c VA(I2,Katm) = vVel(i,j,k,bi,bj)
171 C Physics works with temperature - not potential temp.
172 TA(I2,Katm) = theta(i,j,k,bi,bj)*conv_theta2T
173 c TA(I2,Katm) = max(temp1,min(temp2,
174 c & theta(i,j,k,bi,bj)*conv_theta2T ))
175 C In atm.Phys, water vapor must be > 0 :
176 QA(I2,Katm) = MAX( salt(i,j,k,bi,bj), zeroRL )
177 C Dry static energy replaced by Pot.Temp:
178 ThA(I2,Katm) = theta(i,j,k,bi,bj)
179 ELSE
180 TA(I2,Katm) = 300. _d 0
181 QA(I2,Katm) = 0. _d 0
182 ThA(I2,Katm) = 300. _d 0
183 ENDIF
184 ENDDO
185 ENDDO
186 #ifdef NONLIN_FRSURF
187 IF ( select_rStar.GE.1 ) THEN
188 DO j = 1,sNy
189 DO i = 1,sNx
190 I2 = i+(j-1)*sNx
191 TA(I2,Katm) = TA(I2,Katm)*pStarFacK(i,j,bi,bj)
192 ENDDO
193 ENDDO
194 ENDIF
195 #endif /* NONLIN_FRSURF */
196 ENDDO
197
198 C_jmc: add square of surface wind speed (center of C grid) = 2 * KE_surf
199 DO j = 1,sNy
200 DO i = 1,sNx
201 I2 = i+(j-1)*sNx
202 k = kSurfC(i,j,bi,bj)
203 IF (k.LE.Nr) THEN
204 Vsurf2(I2) = 0.5 * (
205 & uVel(i,j,k,bi,bj)*uVel(i,j,k,bi,bj)
206 & + uVel(i+1,j,k,bi,bj)*uVel(i+1,j,k,bi,bj)
207 & + vVel(i,j,k,bi,bj)*vVel(i,j,k,bi,bj)
208 & + vVel(i,j+1,k,bi,bj)*vVel(i,j+1,k,bi,bj)
209 & )
210 ELSE
211 Vsurf2(I2) = 0.
212 ENDIF
213 ENDDO
214 ENDDO
215
216 C- Check that Temp is OK for LW Radiation scheme :
217 DO k = 1,Nr
218 Katm = _KD2KA( k )
219 DO I2=1,NGP
220 IF ( TA(I2,Katm).LT.lwTemp1 .OR.
221 & TA(I2,Katm).GT.lwTemp2 ) THEN
222 i = 1 + mod((I2-1),sNx)
223 j = 1 + int((I2-1)/sNx)
224 WRITE(msgBuf,'(A,1PE20.13,A,2I4)')
225 & 'AIM_DYN2AIM: Temp=', TA(I2,Katm),
226 & ' out of range ',lwTemp1,lwTemp2
227 CALL PRINT_ERROR( msgBuf , myThid)
228 WRITE(msgBuf,'(A,3I4,3I3,I6,2F9.3)')
229 & 'AIM_DYN2AIM: Pb in i,j,k,bi,bj,myThid,I2,X,Y=',
230 & i,j,k,bi,bj,myThid,I2,xC(i,j,bi,bj),yC(i,j,bi,bj)
231 CALL PRINT_ERROR( msgBuf , myThid)
232 STOP 'ABNORMAL END: S/R AIM_DYN2AIM'
233 ENDIF
234 ENDDO
235 ENDDO
236
237 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
238
239 C- Set geopotential surfaces
240 c DO Katm=1,NLEV
241 c DO I2=1,NGP
242 c PHIG1(I2,Katm) = gravity*HinitC(Katm)
243 c ENDDO
244 c ENDDO
245
246 C- Weights for vertical interpolation down to the surface
247 C Fsurf = Ffull(nlev)+WVS*(Ffull(nlev)-Ffull(nlev-1))
248 DO j = 1,sNy
249 DO i = 1,sNx
250 I2 = i+(j-1)*sNx
251 WVSurf(I2,myThid) = 0.
252 k = kGrd(I2)
253 IF (k.GT.1) THEN
254 C- full cell version of Franco Molteni formula:
255 c WVSurf(I2,myThid) = (LOG(SIGH(k))-SIGL(k))*WVI(k-1,2)
256 C- partial cell version using true log-P extrapolation:
257 WVSurf(I2,myThid) = (LOG(PSA(I2))-SIGL(k))*WVI(k-1,1)
258 C- like in the old code:
259 c WVSurf(I2,myThid) = WVI(k,2)
260 ENDIF
261 ENDDO
262 ENDDO
263 IF (myIter.EQ.nIter0)
264 & CALL AIM_WRITE_PHYS( 'aim_WeightSurf', '', 1, WVSurf,
265 & 1, bi, bj, 1, myIter, myThid )
266
267 #endif /* ALLOW_AIM */
268
269 RETURN
270 END

  ViewVC Help
Powered by ViewVC 1.1.22