/[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.2 - (show annotations) (download)
Thu Mar 11 15:36:49 2004 UTC (20 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52n_post, checkpoint52m_post, checkpoint53
Changes since 1.1: +85 -47 lines
oups! forgot to update this one.

1 C $Header: /u/gcmpack/MITgcm/verification/aim.5l_Equatorial_Channel/code/aim_surf_bc.F,v 1.1 2004/01/24 20:41:25 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 - Loop counters
57 INTEGER i,j,I2
58 _RL SDEP1, IDEP2, SDEP2, SWWIL2, RSW, soilw_0, soilw_1
59 _RL RSD, alb_land, tFreez
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 IF (aim_useFMsurfBC) THEN
74 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
75
76 C-- Compute surface forcing at present time (linear Interp in time)
77 C using F.Molteni surface BC form ; fields needed are:
78 C 1. Land sea mask
79 C 2. Sea Surface temperatures (in situ Temp. [K])
80 C 3. Land Surface temperatures (in situ Temp. [K])
81 C 4. Soil moisture (between 0-1)
82 C 5. Snow depth, Sea Ice : used to compute albedo (=> local arrays)
83 C 6. Albedo (between 0-1)
84
85 C- Set Land-sea mask (in [0,1]) from aim_landFr to fMask1:
86 DO j=1,sNy
87 DO i=1,sNx
88 I2 = i+(j-1)*sNx
89 fMask1(I2,1,myThid) = aim_landFr(i,j,bi,bj)
90 ENDDO
91 ENDDO
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 tFreez = celsius2K - 1.9 _d 0
143 DO J=1,NGP
144 sti1(J,myThid) = sst1(J,myThid)
145 IF ( oice1(J) .GT. 1. _d -2 ) THEN
146 sst1(J,myThid) = MAX(sst1(J,myThid),tFreez);
147 sti1(J,myThid) = sst1(J,myThid)
148 & +(sti1(J,myThid)-sst1(J,myThid))/oice1(J)
149 ELSE
150 oice1(J) = 0. _d 0
151 ENDIF
152 ENDDO
153 ELSE
154 DO J=1,NGP
155 sti1(J,myThid) = sst1(J,myThid)
156 ENDDO
157 ENDIF
158
159 C- Surface Albedo : (from F.M. FORDATE S/R)
160 c_FM DALB=ALBICE-ALBSEA
161 RSD=1. _d 0/SDALB
162 DO j=1,sNy
163 DO i=1,sNx
164 c_FM SNOWC=MIN(1.,RSD*SNOW1(I,J))
165 c_FM ALBL=ALB0(I,J)+MAX(ALBSN-ALB0(I,J),0.0)*SNOWC
166 c_FM ALBS=ALBSEA+DALB*OICE1(I,J)
167 c_FM ALB1(I,J)=FMASK1(I,J)*ALBL+FMASK0(I,J)*ALBS
168 I2 = i+(j-1)*sNx
169 alb_land = aim_albedo(i,j,bi,bj)
170 & + MAX( 0. _d 0, ALBSN-aim_albedo(i,j,bi,bj) )
171 & *MIN( 1. _d 0, RSD*snow1(I2))
172 c alb_sea = ALBSEA + DALB*oice1(I2)
173 c alb1(I2,0,myThid) = alb_sea
174 c & + (alb_land - alb_sea)*fMask1(I2,1,myThid)
175 alb1(I2,1,myThid) = alb_land
176 alb1(I2,2,myThid) = ALBSEA
177 alb1(I2,3,myThid) = ALBICE
178 ENDDO
179 ENDDO
180
181 C-- else aim_useFMsurfBC
182 ELSE
183 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
184
185 C- Set surface forcing fields needed by atmos. physics package
186 C 1. Albedo (between 0-1)
187 C 2. Sea Surface temperatures (in situ Temp. [K])
188 C 3. Land Surface temperatures (in situ Temp. [K])
189 C 4. Soil moisture (between 0-1)
190 C 5. Land sea mask (infer from exact zeros in soil moisture)
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 Land-sea mask (in [0,1])
266 C from aim_landFr to fMask1 (aim_useFMsurfBC)
267 C or from where soil moisture is exactly zero (aim_useMMsurfFc)
268 IF (aim_useMMsurfFc) THEN
269 DO J=1,NGP
270 fMask1(J,1,myThid) = 1.
271 IF ( soilw1(J,myThid).EQ.0. ) fMask1(J,1,myThid) = 0.
272 ENDDO
273 ELSE
274 DO j=1,sNy
275 DO i=1,sNx
276 I2 = i+(j-1)*sNx
277 fMask1(I2,1,myThid) = 0.
278 ENDDO
279 ENDDO
280 ENDIF
281
282 C- Set Snow depth and Sea Ice
283 C (not needed here since albedo is loaded from file)
284 DO j=1,sNy
285 DO i=1,sNx
286 I2 = i+(j-1)*sNx
287 oice1(I2) = 0.
288 snow1(I2) = 0.
289 ENDDO
290 ENDDO
291
292 C-- endif/else aim_useFMsurfBC
293 ENDIF
294
295 #ifdef COMPONENT_MODULE
296 IF ( useCoupler ) THEN
297 IF ( useImportSST ) THEN
298 DO j=1,sNy
299 DO i=1,sNx
300
301 c IF ( SSTocn(I,J,bi,bj) .NE. 0. ) THEN
302 IF ( aim_landFr(i,j,bi,bj) .LT. 1. ) THEN
303 I2 = i+(j-1)*sNx
304 C-- take SST from the ocean compon where Sea-Ice fraction is zero
305 IF ( oice1(I2).EQ.0. ) THEN
306 sst1(I2,myThid) = SSTocn(i,j,bi,bj)+celsius2K
307 ELSEIF ( SSTocn(i,j,bi,bj).GE. -1. _d 0) THEN
308 C-- take SST from the ocean compon if clearly warmer than freezing
309 C then reset sea-ice fraction
310 sst1(I2,myThid) = SSTocn(i,j,bi,bj)+celsius2K
311 oice1(I2) = 0.
312 ENDIF
313 ENDIF
314
315 ENDDO
316 ENDDO
317 ENDIF
318 ENDIF
319 #endif /* COMPONENT_MODULE */
320
321 #ifdef ALLOW_LAND
322 IF (useLand) THEN
323 C- Use land model output instead of prescribed Temp & moisture
324 CALL AIM_LAND2AIM(
325 I aim_landFr, aim_veget, aim_albedo, snow1,
326 U stl1(1,mythid), soilw1(1,mythid), alb1(1,1,myThid),
327 I myTime, myIter, bi, bj, myThid )
328 ENDIF
329 #endif /* ALLOW_LAND */
330
331 C-- set the sea-ice & open ocean fraction :
332 DO J=1,NGP
333 fMask1(J,3,myThid) =(1. _d 0 - fMask1(J,1,myThid))
334 & *oice1(J)
335 fMask1(J,2,myThid) = 1. _d 0 - fMask1(J,1,myThid)
336 & - fMask1(J,3,myThid)
337 ENDDO
338
339 C-- set the mean albedo :
340 DO J=1,NGP
341 alb1(J,0,myThid) = fMask1(J,1,myThid)*alb1(J,1,myThid)
342 & + fMask1(J,2,myThid)*alb1(J,2,myThid)
343 & + fMask1(J,3,myThid)*alb1(J,3,myThid)
344 ENDDO
345
346 IF (.NOT.aim_splitSIOsFx) THEN
347 DO J=1,NGP
348 fMask1(J,3,myThid) = 0. _d 0
349 fMask1(J,2,myThid) = 1. _d 0 - fMask1(J,1,myThid)
350 ENDDO
351 ENDIF
352
353 #endif /* ALLOW_AIM */
354
355 RETURN
356 END

  ViewVC Help
Powered by ViewVC 1.1.22