/[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.4 - (show annotations) (download)
Thu Jul 8 15:51:19 2004 UTC (19 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57m_post, checkpoint57g_pre, checkpoint57s_post, checkpoint58b_post, checkpoint57b_post, checkpoint57g_post, checkpoint56b_post, checkpoint57y_post, checkpoint54d_post, checkpoint54e_post, checkpoint57r_post, checkpoint57d_post, checkpoint57i_post, checkpoint58, checkpoint55, checkpoint57, checkpoint56, checkpoint58f_post, checkpoint57n_post, checkpoint58d_post, checkpoint58a_post, checkpoint57z_post, checkpoint54f_post, checkpoint55i_post, checkpoint58m_post, checkpoint57l_post, checkpoint57t_post, checkpoint55c_post, checkpoint57v_post, checkpoint57f_post, checkpoint57a_post, checkpoint57h_pre, checkpoint54b_post, checkpoint57h_post, checkpoint57y_pre, checkpoint55g_post, checkpoint57c_post, checkpoint55d_post, checkpoint58e_post, checkpoint55d_pre, checkpoint57c_pre, checkpoint55j_post, checkpoint55h_post, checkpoint57e_post, checkpoint55b_post, checkpoint55f_post, checkpoint57p_post, checkpint57u_post, checkpoint57q_post, eckpoint57e_pre, checkpoint58k_post, checkpoint56a_post, checkpoint58l_post, checkpoint57h_done, checkpoint57j_post, checkpoint57f_pre, checkpoint58g_post, checkpoint58h_post, checkpoint56c_post, checkpoint58j_post, checkpoint57a_pre, checkpoint55a_post, checkpoint57o_post, checkpoint57k_post, checkpoint57w_post, checkpoint58i_post, checkpoint57x_post, checkpoint58c_post, checkpoint55e_post, checkpoint54c_post
Changes since 1.3: +43 -14 lines
o staggerTimeStep & NLFS: update physical pkg aim_v23

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

  ViewVC Help
Powered by ViewVC 1.1.22