/[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.1 - (show annotations) (download)
Fri Nov 22 17:17:03 2002 UTC (21 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint47e_post, checkpoint50c_post, checkpoint48e_post, checkpoint50c_pre, checkpoint48i_post, checkpoint50d_pre, checkpoint50, checkpoint50d_post, checkpoint50b_pre, checkpoint48b_post, checkpoint48c_pre, checkpoint47d_pre, checkpoint47a_post, checkpoint48d_pre, checkpoint47i_post, checkpoint47d_post, checkpoint48d_post, checkpoint48f_post, checkpoint48h_post, checkpoint47g_post, checkpoint48a_post, checkpoint50f_post, checkpoint50a_post, checkpoint50f_pre, checkpoint47j_post, branch-exfmods-tag, checkpoint48c_post, checkpoint47b_post, checkpoint50g_post, checkpoint50e_pre, checkpoint47f_post, checkpoint50e_post, checkpoint48, checkpoint49, checkpoint47h_post, checkpoint50b_post, checkpoint48g_post
Branch point for: branch-exfmods-curt
new aim pkg: adapted from Franco Molteni SPEEDY code, ver23

1 C $Header: $
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 meesage 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 DO K = 1,Nr
105 Katm = _KD2KA( K )
106 DO J = 1,sNy
107 DO I = 1,sNx
108 I2 = I+(J-1)*sNx
109 c dpFac(I2,Katm) = 1. _d 0
110 dpFac(I2,Katm) = hFacC(I,J,K,bi,bj)
111 c IF (hFacC(I,J,K,bi,bj).GT.0. _d 0) THEN
112 c dpFac(I2,Katm) = hFacC(I,J,K,bi,bj)
113 c ELSE
114 c dpFac(I2,Katm) = 1. _d 0
115 c ENDIF
116 ENDDO
117 ENDDO
118 ENDDO
119
120 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
121
122 C Physics package works with sub-domains 1:sNx,1:sNy,1:Nr.
123 C Internal index mapping is linear in X and Y with a second
124 C dimension for the vertical.
125
126 C- Dynamical var --> AIM var :
127 C note: UA & VA are not used => removed
128 temp1 = lwTemp1
129 temp2 = lwTemp2
130 DO K = 1,Nr
131 conv_theta2T = (rC(K)/atm_po)**atm_kappa
132 Katm = _KD2KA( K )
133 DO J = 1,sNy
134 DO I = 1,sNx
135 I2 = I+(J-1)*sNx
136 IF (maskC(i,j,k,bi,bj).EQ.1. _d 0) THEN
137 c UA(I2,Katm) = uVel(I,J,K,bi,bj)
138 c VA(I2,Katm) = vVel(I,J,K,bi,bj)
139 C Physics works with temperature - not potential temp.
140 TA(I2,Katm) = theta(I,J,K,bi,bj)*conv_theta2T
141 c TA(I2,Katm) = max(temp1,min(temp2,
142 c & theta(I,J,K,bi,bj)*conv_theta2T ))
143 C In atm.Phys, water vapor must be > 0 :
144 QA(I2,Katm) = MAX(salt(I,J,K,bi,bj), 0. _d 0)
145 C Dry static energy replaced by Pot.Temp:
146 ThA(I2,Katm) = theta(I,J,K,bi,bj)
147 ELSE
148 TA(I2,Katm) = 300. _d 0
149 QA(I2,Katm) = 0. _d 0
150 ThA(I2,Katm) = 300. _d 0
151 ENDIF
152 ENDDO
153 ENDDO
154 ENDDO
155
156 C_jmc: add square of surface wind speed (center of C grid) = 2 * KE_surf
157 DO J = 1,sNy
158 DO I = 1,sNx
159 I2 = I+(J-1)*sNx
160 K = ksurfC(i,j,bi,bj)
161 IF (K.LE.Nr) THEN
162 Vsurf2(I2) = 0.5 * (
163 & uVel(I,J,K,bi,bj)*uVel(I,J,K,bi,bj)
164 & + uVel(I+1,J,K,bi,bj)*uVel(I+1,J,K,bi,bj)
165 & + vVel(I,J,K,bi,bj)*vVel(I,J,K,bi,bj)
166 & + vVel(I,J+1,K,bi,bj)*vVel(I,J+1,K,bi,bj)
167 & )
168 ELSE
169 Vsurf2(I2) = 0.
170 ENDIF
171 ENDDO
172 ENDDO
173
174 C- Check that Temp is OK for LW Radiation scheme :
175 DO K = 1,Nr
176 Katm = _KD2KA( K )
177 DO I2=1,NGP
178 IF ( TA(I2,Katm).LT.lwTemp1 .OR.
179 & TA(I2,Katm).GT.lwTemp2 ) THEN
180 i = 1 + mod((I2-1),sNx)
181 j = 1 + int((I2-1)/sNx)
182 WRITE(msgBuf,'(A,1PE20.13,A,2I4)')
183 & 'AIM_DYN2AIM: Temp=', TA(I2,Katm),
184 & ' out of range ',lwTemp1,lwTemp2
185 CALL PRINT_ERROR( msgBuf , myThid)
186 WRITE(msgBuf,'(A,3I4,3I3,I6,2F9.3)')
187 & 'AIM_DYN2AIM: Pb in i,j,k,bi,bj,myThid,I2,X,Y=',
188 & i,j,k,bi,bj,myThid,I2,xC(i,j,bi,bj),yC(i,j,bi,bj)
189 CALL PRINT_ERROR( msgBuf , myThid)
190 STOP 'ABNORMAL END: S/R AIM_DYN2AIM'
191 ENDIF
192 ENDDO
193 ENDDO
194
195 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
196
197 C- Set geopotential surfaces
198 c DO Katm=1,NLEV
199 c DO I2=1,NGP
200 c PHIG1(I2,Katm) = gravity*HinitC(Katm)
201 c ENDDO
202 c ENDDO
203
204 C- Weights for vertical interpolation down to the surface
205 C Fsurf = Ffull(nlev)+WVS*(Ffull(nlev)-Ffull(nlev-1))
206 DO J = 1,sNy
207 DO I = 1,sNx
208 I2 = I+(J-1)*sNx
209 WVSurf(I2,myThid) = 0.
210 K = kGrd(I2)
211 IF (K.GT.1) THEN
212 WVSurf(I2,myThid) = (LOG(SIGH(K))-SIGL(K))*WVI(K-1,2)
213 C- like in the old code:
214 c WVSurf(I2,myThid) = WVI(K,2)
215 ENDIF
216 ENDDO
217 ENDDO
218 IF (myIter.EQ.nIter0)
219 & CALL AIM_WRITE_LOCAL('aim_WeightSurf','',1,WVSurf(1,myThid),
220 & bi,bj,1,myIter,myThid)
221
222 #endif /* ALLOW_AIM */
223
224 RETURN
225 END

  ViewVC Help
Powered by ViewVC 1.1.22