/[MITgcm]/MITgcm/verification/aim.5l_Equatorial_Channel/code/aim_surf_bc.F
ViewVC logotype

Contents of /MITgcm/verification/aim.5l_Equatorial_Channel/code/aim_surf_bc.F

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


Revision 1.4 - (show annotations) (download)
Sun Nov 14 20:25:04 2004 UTC (19 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, checkpoint57v_post, checkpoint57m_post, checkpoint57s_post, checkpoint57k_post, checkpoint57d_post, checkpoint57g_post, checkpoint57b_post, checkpoint57c_pre, checkpoint56b_post, checkpoint57i_post, checkpoint57y_post, checkpoint57e_post, checkpoint58n_post, checkpoint57g_pre, checkpoint58h_post, checkpoint56c_post, checkpoint57y_pre, checkpoint57f_pre, checkpoint57a_post, checkpoint58j_post, checkpoint57r_post, checkpoint58, checkpoint57a_pre, checkpoint57, checkpoint56, eckpoint57e_pre, checkpoint57h_done, checkpoint58f_post, checkpoint57x_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint57f_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint57c_post, checkpoint58k_post, checkpoint58p_post, checkpoint57j_post, checkpoint58b_post, checkpoint57h_pre, checkpoint58m_post, checkpoint57l_post, checkpoint57h_post, checkpoint56a_post
Changes since 1.3: +45 -59 lines
updated after changes in standard version (pkg/aim_v23/aim_surf_bc.F)

1 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_surf_bc.F,v 1.9 2004/11/14 19:54:01 jmc Exp $
2 C $Name: $
3
4 #include "AIM_OPTIONS.h"
5
6 SUBROUTINE AIM_SURF_BC( tYear, myTime, myIter, bi, bj, myThid )
7 C *================================================================*
8 C | S/R AIM_SURF_BC
9 C | Set surface Boundary Conditions
10 C | for the atmospheric physics package
11 C *================================================================*
12 c | was part of S/R FORDATE in Franco Molteni SPEEDY code (ver23).
13 C | For now, surface BC are loaded from files (S/R AIM_FIELDS_LOAD)
14 C | and imposed (= surf. forcing).
15 C | In the future, will add
16 C | a land model and a coupling interface with an ocean GCM
17 C *================================================================*
18 IMPLICIT NONE
19
20 C -------------- Global variables --------------
21 C-- size for MITgcm & Physics package :
22 #include "AIM_SIZE.h"
23
24 C-- MITgcm
25 #include "EEPARAMS.h"
26 #include "PARAMS.h"
27 c #include "DYNVARS.h"
28 #include "GRID.h"
29 c #include "SURFACE.h"
30
31 C-- Physics package
32 #include "AIM_PARAMS.h"
33 #include "AIM_FFIELDS.h"
34 c #include "AIM_GRID.h"
35 #include "com_forcon.h"
36 #include "com_forcing.h"
37 c #include "com_physvar.h"
38
39 C-- Coupled to the Ocean :
40 #ifdef COMPONENT_MODULE
41 #include "CPL_PARAMS.h"
42 #include "ATMCPL.h"
43 #endif
44
45 C == Routine arguments ==
46 C tYear - Fraction into year
47 C myTime - Current time of simulation ( s )
48 C myIter - Current iteration number in simulation
49 C bi,bj - Tile index
50 C myThid - Number of this instance of the routine
51 INTEGER myIter, bi, bj, myThid
52 _RL tYear, myTime
53
54 #ifdef ALLOW_AIM
55 C == Local variables ==
56 C i,j,k,I2,k - Loop counters
57 INTEGER i,j,I2,k
58 _RL SDEP1, IDEP2, SDEP2, SWWIL2, RSW, soilw_0, soilw_1
59 _RL RSD, alb_land, oceTfreez
60 c _RL DALB, alb_sea
61
62 C_EqCh: start
63 CHARACTER*(MAX_LEN_MBUF) suff
64 _RL xBump, yBump, dxBump, dyBump
65 xBump = thetaMin + delX(1)*64.
66 yBump = phiMin + delY(1)*11.5
67 dxBump= delX(1)*12.
68 dyBump= delY(1)*6.
69 C_EqCh: Fix solar insolation with Sun directly overhead on Equator
70 tYear = 0.25 _d 0 - 10. _d 0/365. _d 0
71 C_EqCh: end
72
73 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
74 C- Set Land-sea mask (in [0,1]) from aim_landFr to fMask1:
75 DO j=1,sNy
76 DO i=1,sNx
77 I2 = i+(j-1)*sNx
78 fMask1(I2,1,myThid) = aim_landFr(i,j,bi,bj)
79 ENDDO
80 ENDDO
81
82 IF (aim_useFMsurfBC) THEN
83 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
84
85 C-- Compute surface forcing at present time (linear Interp in time)
86 C using F.Molteni surface BC form ; fields needed are:
87 C 1. Sea Surface temperatures (in situ Temp. [K])
88 C 2. Land Surface temperatures (in situ Temp. [K])
89 C 3. Soil moisture (between 0-1)
90 C 4. Snow depth, Sea Ice : used to compute albedo (=> local arrays)
91 C 5. Albedo (between 0-1)
92
93 C- Surface Temperature:
94 DO j=1,sNy
95 DO i=1,sNx
96 I2 = i+(j-1)*sNx
97 sst1(I2,myThid) = aim_sWght0*aim_sst0(i,j,bi,bj)
98 & + aim_sWght1*aim_sst1(i,j,bi,bj)
99 stl1(I2,myThid) = aim_sWght0*aim_lst0(i,j,bi,bj)
100 & + aim_sWght1*aim_lst1(i,j,bi,bj)
101 ENDDO
102 ENDDO
103
104 C- Soil Water availability : (from F.M. INFORC S/R)
105 SDEP1 = 70. _d 0
106 IDEP2 = 3. _d 0
107 SDEP2 = IDEP2*SDEP1
108
109 SWWIL2= SDEP2*SWWIL
110 RSW = 1. _d 0/(SDEP1*SWCAP+SDEP2*(SWCAP-SWWIL))
111
112 DO j=1,sNy
113 DO i=1,sNx
114 I2 = i+(j-1)*sNx
115 soilw_0 = ( aim_sw10(i,j,bi,bj)
116 & +aim_veget(i,j,bi,bj)*
117 & MAX(IDEP2*aim_sw20(i,j,bi,bj)-SWWIL2, 0. _d 0)
118 & )*RSW
119 soilw_1 = ( aim_sw11(i,j,bi,bj)
120 & +aim_veget(i,j,bi,bj)*
121 & MAX(IDEP2*aim_sw21(i,j,bi,bj)-SWWIL2, 0. _d 0)
122 & )*RSW
123 soilw1(I2,myThid) = aim_sWght0*soilw_0
124 & + aim_sWght1*soilw_1
125 soilw1(I2,myThid) = MIN(1. _d 0, soilw1(I2,myThid) )
126 ENDDO
127 ENDDO
128
129 C- Set snow depth & sea-ice fraction :
130 DO j=1,sNy
131 DO i=1,sNx
132 I2 = i+(j-1)*sNx
133 snow1(I2) = aim_sWght0*aim_snw0(i,j,bi,bj)
134 & + aim_sWght1*aim_snw1(i,j,bi,bj)
135 oice1(I2) = aim_sWght0*aim_oic0(i,j,bi,bj)
136 & + aim_sWght1*aim_oic1(i,j,bi,bj)
137 ENDDO
138 ENDDO
139
140 IF (aim_splitSIOsFx) THEN
141 C- Split Ocean and Sea-Ice surf. temp. ; remove ice-fraction < 1 %
142 c oceTfreez = tFreeze - 1.9 _d 0
143 oceTfreez = celsius2K - 1.9 _d 0
144 DO J=1,NGP
145 sti1(J,myThid) = sst1(J,myThid)
146 IF ( oice1(J) .GT. 1. _d -2 ) THEN
147 sst1(J,myThid) = MAX(sst1(J,myThid),oceTfreez)
148 sti1(J,myThid) = sst1(J,myThid)
149 & +(sti1(J,myThid)-sst1(J,myThid))/oice1(J)
150 ELSE
151 oice1(J) = 0. _d 0
152 ENDIF
153 ENDDO
154 ELSE
155 DO J=1,NGP
156 sti1(J,myThid) = sst1(J,myThid)
157 ENDDO
158 ENDIF
159
160 C- Surface Albedo : (from F.M. FORDATE S/R)
161 c_FM DALB=ALBICE-ALBSEA
162 RSD=1. _d 0/SDALB
163 DO j=1,sNy
164 DO i=1,sNx
165 c_FM SNOWC=MIN(1.,RSD*SNOW1(I,J))
166 c_FM ALBL=ALB0(I,J)+MAX(ALBSN-ALB0(I,J),0.0)*SNOWC
167 c_FM ALBS=ALBSEA+DALB*OICE1(I,J)
168 c_FM ALB1(I,J)=FMASK1(I,J)*ALBL+FMASK0(I,J)*ALBS
169 I2 = i+(j-1)*sNx
170 alb_land = aim_albedo(i,j,bi,bj)
171 & + MAX( 0. _d 0, ALBSN-aim_albedo(i,j,bi,bj) )
172 & *MIN( 1. _d 0, RSD*snow1(I2))
173 c alb_sea = ALBSEA + DALB*oice1(I2)
174 c alb1(I2,0,myThid) = alb_sea
175 c & + (alb_land - alb_sea)*fMask1(I2,1,myThid)
176 alb1(I2,1,myThid) = alb_land
177 alb1(I2,2,myThid) = ALBSEA
178 alb1(I2,3,myThid) = ALBICE
179 ENDDO
180 ENDDO
181
182 C-- else aim_useFMsurfBC
183 ELSE
184 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
185
186 C- Set surface forcing fields needed by atmos. physics package
187 C 1. Albedo (between 0-1)
188 C 2. Sea Surface temperatures (in situ Temp. [K])
189 C 3. Land Surface temperatures (in situ Temp. [K])
190 C 4. Soil moisture (between 0-1)
191 C Snow depth, Sea Ice (<- no need for now)
192
193 C Set surface albedo data (in [0,1]) from aim_albedo to alb1 :
194 IF (aim_useMMsurfFc) THEN
195 DO j=1,sNy
196 DO i=1,sNx
197 I2 = i+(j-1)*sNx
198 alb1(I2,1,myThid) = aim_albedo(i,j,bi,bj)
199 alb1(I2,2,myThid) = aim_albedo(i,j,bi,bj)
200 alb1(I2,3,myThid) = aim_albedo(i,j,bi,bj)
201 ENDDO
202 ENDDO
203 ELSE
204 DO j=1,sNy
205 DO i=1,sNx
206 I2 = i+(j-1)*sNx
207 alb1(I2,1,myThid) = 0.
208 alb1(I2,2,myThid) = 0.
209 alb1(I2,3,myThid) = 0.
210 ENDDO
211 ENDDO
212 ENDIF
213 C Set surface temperature data from aim_S/LSurfTemp to sst1 & stl1 :
214 IF (aim_useMMsurfFc) THEN
215 DO j=1,sNy
216 DO i=1,sNx
217 I2 = i+(j-1)*sNx
218 sst1(I2,myThid) = aim_surfTemp(i,j,bi,bj)
219 stl1(I2,myThid) = aim_surfTemp(i,j,bi,bj)
220 sti1(I2,myThid) = aim_surfTemp(i,j,bi,bj)
221 ENDDO
222 ENDDO
223 ELSE
224 DO j=1,sNy
225 DO i=1,sNx
226 I2 = i+(j-1)*sNx
227 sst1(I2,myThid) = 300.
228 stl1(I2,myThid) = 300.
229 sti1(I2,myThid) = 300.
230 C_EqCh: start
231 sst1(I2,myThid) = 280.
232 & +20. _d 0 *exp( -((xC(i,j,bi,bj)-xBump)/dxBump)**2
233 & -((yC(i,j,bi,bj)-yBump)/dyBump)**2 )
234 stl1(I2,myThid) = sst1(I2,myThid)
235 sti1(I2,myThid) = sst1(I2,myThid)
236 C_EqCh: end
237 ENDDO
238 ENDDO
239 C_EqCh: start
240 IF (myIter.EQ.nIter0) THEN
241 WRITE(suff,'(I10.10)') myIter
242 CALL AIM_WRITE_LOCAL('aim_SST.',suff,1,sst1(1,myThid),
243 & bi,bj,1,myIter,myThid)
244 ENDIF
245 C_EqCh: end
246 ENDIF
247
248 C- Set soil water availability (in [0,1]) from aim_soilWater to soilw1 :
249 IF (aim_useMMsurfFc) THEN
250 DO j=1,sNy
251 DO i=1,sNx
252 I2 = i+(j-1)*sNx
253 soilw1(I2,myThid) = aim_soilWater(i,j,bi,bj)
254 ENDDO
255 ENDDO
256 ELSE
257 DO j=1,sNy
258 DO i=1,sNx
259 I2 = i+(j-1)*sNx
260 soilw1(I2,myThid) = 0.
261 ENDDO
262 ENDDO
263 ENDIF
264
265 C- Set Snow depth and Sea Ice
266 C (not needed here since albedo is loaded from file)
267 DO j=1,sNy
268 DO i=1,sNx
269 I2 = i+(j-1)*sNx
270 oice1(I2) = 0.
271 snow1(I2) = 0.
272 ENDDO
273 ENDDO
274
275 C-- endif/else aim_useFMsurfBC
276 ENDIF
277
278 #ifdef COMPONENT_MODULE
279 IF ( useCoupler ) THEN
280 C-- take surface data from the ocean component
281 C to replace MxL fields (if use sea-ice) or directly AIM SST
282 CALL ATM_APPLY_IMPORT(
283 I aim_landFr,
284 U sst1(1,mythid), oice1,
285 I myTime, myIter, bi, bj, myThid )
286 ENDIF
287 #endif /* COMPONENT_MODULE */
288
289 #ifdef ALLOW_LAND
290 IF (useLand) THEN
291 C- Use land model output instead of prescribed Temp & moisture
292 CALL AIM_LAND2AIM(
293 I aim_landFr, aim_veget, aim_albedo, snow1,
294 U stl1(1,mythid), soilw1(1,mythid), alb1(1,1,myThid),
295 I myTime, myIter, bi, bj, myThid )
296 ENDIF
297 #endif /* ALLOW_LAND */
298
299 #ifdef ALLOW_THSICE
300 IF (useThSIce) THEN
301 C- Use thermo. sea-ice model output instead of prescribed Temp & albedo
302 CALL AIM_SICE2AIM(
303 I aim_landFr,
304 U sst1(1,mythid), oice1,
305 O sti1(1,mythid), alb1(1,3,myThid),
306 I myTime, myIter, bi, bj, myThid )
307 ENDIF
308 #endif /* ALLOW_THSICE */
309
310 C-- set the sea-ice & open ocean fraction :
311 DO J=1,NGP
312 fMask1(J,3,myThid) =(1. _d 0 - fMask1(J,1,myThid))
313 & *oice1(J)
314 fMask1(J,2,myThid) = 1. _d 0 - fMask1(J,1,myThid)
315 & - fMask1(J,3,myThid)
316 ENDDO
317
318 C-- set the mean albedo :
319 DO J=1,NGP
320 alb1(J,0,myThid) = fMask1(J,1,myThid)*alb1(J,1,myThid)
321 & + fMask1(J,2,myThid)*alb1(J,2,myThid)
322 & + fMask1(J,3,myThid)*alb1(J,3,myThid)
323 ENDDO
324
325 C-- initialize surf. temp. change to zero:
326 DO k=1,3
327 DO J=1,NGP
328 dTsurf(J,k,myThid) = 0.
329 ENDDO
330 ENDDO
331
332 IF (.NOT.aim_splitSIOsFx) THEN
333 DO J=1,NGP
334 fMask1(J,3,myThid) = 0. _d 0
335 fMask1(J,2,myThid) = 1. _d 0 - fMask1(J,1,myThid)
336 ENDDO
337 ENDIF
338
339 #endif /* ALLOW_AIM */
340
341 RETURN
342 END

  ViewVC Help
Powered by ViewVC 1.1.22