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

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

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


Revision 1.16 - (show annotations) (download)
Tue Jun 30 16:03:44 2009 UTC (14 years, 11 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint62a, checkpoint62, checkpoint61z, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61s, checkpoint61x, checkpoint61y
Changes since 1.15: +2 -2 lines
Fix typo

1 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_surf_bc.F,v 1.15 2009/06/15 17:58:55 dfer Exp $
2 C $Name: $
3
4 #include "AIM_OPTIONS.h"
5
6 SUBROUTINE AIM_SURF_BC(
7 U tYear,
8 O aim_sWght0, aim_sWght1,
9 I bi, bj, myTime, myIter, myThid )
10 C *================================================================*
11 C | S/R AIM_SURF_BC
12 C | Set surface Boundary Conditions
13 C | for the atmospheric physics package
14 C *================================================================*
15 c | was part of S/R FORDATE in Franco Molteni SPEEDY code (ver23).
16 C | For now, surface BC are loaded from files (S/R AIM_FIELDS_LOAD)
17 C | and imposed (= surf. forcing).
18 C | In the future, will add
19 C | a land model and a coupling interface with an ocean GCM
20 C *================================================================*
21 IMPLICIT NONE
22
23 C -------------- Global variables --------------
24 C-- size for MITgcm & Physics package :
25 #include "AIM_SIZE.h"
26
27 C-- MITgcm
28 #include "EEPARAMS.h"
29 #include "PARAMS.h"
30 c #include "DYNVARS.h"
31 #include "GRID.h"
32 c #include "SURFACE.h"
33
34 C-- Physics package
35 #include "AIM_PARAMS.h"
36 #include "AIM_FFIELDS.h"
37 c #include "AIM_GRID.h"
38 #include "com_forcon.h"
39 #include "com_forcing.h"
40 c #include "com_physvar.h"
41 #include "AIM_CO2.h"
42
43 C-- Coupled to the Ocean :
44 #ifdef COMPONENT_MODULE
45 #include "CPL_PARAMS.h"
46 #include "ATMCPL.h"
47 #endif
48
49 C == Routine arguments ==
50 C tYear :: Fraction into year
51 C aim_sWght0 :: weight for time interpolation of surface BC
52 C aim_sWght1 :: 0/1 = time period before/after the current time
53 C bi,bj :: Tile indices
54 C myTime :: Current time of simulation ( s )
55 C myIter :: Current iteration number in simulation
56 C myThid :: my Thread number Id.
57 _RL tYear
58 _RL aim_sWght0, aim_sWght1
59 INTEGER bi, bj
60 _RL myTime
61 INTEGER myIter, myThid
62
63 #ifdef ALLOW_AIM
64 C == Local variables ==
65 C i,j,k,I2,k :: Loop counters
66 INTEGER i,j,I2,k, nm0
67 _RL t0prd, tNcyc, tmprd, dTprd
68 _RL SDEP1, IDEP2, SDEP2, SWWIL2, RSW, soilw_0, soilw_1
69 _RL RSD, alb_land, oceTfreez, ALBSEA1, ALPHA, CZEN, CZEN2
70 _RL RZEN, ZS, ZC, SJ, CJ, TMPA, TMPB, TMPL, hlim
71 c _RL DALB, alb_sea
72 #ifdef ALLOW_DIAGNOSTICS
73 _RL pCO2scl
74 LOGICAL DIAGNOSTICS_IS_ON
75 EXTERNAL DIAGNOSTICS_IS_ON
76 #endif
77
78 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
79 C- Set Land-sea mask (in [0,1]) from aim_landFr to fMask1:
80 DO j=1,sNy
81 DO i=1,sNx
82 I2 = i+(j-1)*sNx
83 fMask1(I2,1,myThid) = aim_landFr(i,j,bi,bj)
84 ENDDO
85 ENDDO
86
87 IF (aim_useFMsurfBC) THEN
88 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
89
90 C aim_surfForc_TimePeriod :: Length of forcing time period (e.g. 1 month)
91 C aim_surfForc_NppCycle :: Number of time period per Cycle (e.g. 12)
92 C aim_surfForc_TransRatio ::
93 C- define how fast the (linear) transition is from one month to the next
94 C = 1 -> linear between 2 midle month
95 C > TimePeriod/deltaT -> jump from one month to the next one
96
97 C-- Calculate weight for linear interpolation between 2 month centers
98 t0prd = myTime / aim_surfForc_TimePeriod
99 tNcyc = aim_surfForc_NppCycle
100 tmprd = t0prd - 0.5 _d 0 + tNcyc
101 tmprd = MOD(tmprd,tNcyc)
102 C- indices of previous month (nm0) and next month (nm1):
103 nm0 = 1 + INT(tmprd)
104 c nm1 = 1 + MOD(nm0,aim_surfForc_NppCycle)
105 C- interpolation weight:
106 dTprd = tmprd - (nm0 - 1)
107 aim_sWght1 = 0.5 _d 0+(dTprd-0.5 _d 0)*aim_surfForc_TransRatio
108 aim_sWght1 = MAX( 0. _d 0, MIN(1. _d 0, aim_sWght1) )
109 aim_sWght0 = 1. _d 0 - aim_sWght1
110
111 C-- Compute surface forcing at present time (linear Interp in time)
112 C using F.Molteni surface BC form ; fields needed are:
113 C 1. Sea Surface temperatures (in situ Temp. [K])
114 C 2. Land Surface temperatures (in situ Temp. [K])
115 C 3. Soil moisture (between 0-1)
116 C 4. Snow depth, Sea Ice : used to compute albedo (=> local arrays)
117 C 5. Albedo (between 0-1)
118
119 C- Surface Temperature:
120 DO j=1,sNy
121 DO i=1,sNx
122 I2 = i+(j-1)*sNx
123 sst1(I2,myThid) = aim_sWght0*aim_sst0(i,j,bi,bj)
124 & + aim_sWght1*aim_sst1(i,j,bi,bj)
125 stl1(I2,myThid) = aim_sWght0*aim_lst0(i,j,bi,bj)
126 & + aim_sWght1*aim_lst1(i,j,bi,bj)
127 ENDDO
128 ENDDO
129
130 C- Soil Water availability : (from F.M. INFORC S/R)
131 SDEP1 = 70. _d 0
132 IDEP2 = 3. _d 0
133 SDEP2 = IDEP2*SDEP1
134
135 SWWIL2= SDEP2*SWWIL
136 RSW = 1. _d 0/(SDEP1*SWCAP+SDEP2*(SWCAP-SWWIL))
137
138 DO j=1,sNy
139 DO i=1,sNx
140 I2 = i+(j-1)*sNx
141 soilw_0 = ( aim_sw10(i,j,bi,bj)
142 & +aim_veget(i,j,bi,bj)*
143 & MAX(IDEP2*aim_sw20(i,j,bi,bj)-SWWIL2, 0. _d 0)
144 & )*RSW
145 soilw_1 = ( aim_sw11(i,j,bi,bj)
146 & +aim_veget(i,j,bi,bj)*
147 & MAX(IDEP2*aim_sw21(i,j,bi,bj)-SWWIL2, 0. _d 0)
148 & )*RSW
149 soilw1(I2,myThid) = aim_sWght0*soilw_0
150 & + aim_sWght1*soilw_1
151 soilw1(I2,myThid) = MIN(1. _d 0, soilw1(I2,myThid) )
152 ENDDO
153 ENDDO
154
155 C- Set snow depth & sea-ice fraction :
156 DO j=1,sNy
157 DO i=1,sNx
158 I2 = i+(j-1)*sNx
159 snow1(I2) = aim_sWght0*aim_snw0(i,j,bi,bj)
160 & + aim_sWght1*aim_snw1(i,j,bi,bj)
161 oice1(I2) = aim_sWght0*aim_oic0(i,j,bi,bj)
162 & + aim_sWght1*aim_oic1(i,j,bi,bj)
163 ENDDO
164 ENDDO
165
166 IF (aim_splitSIOsFx) THEN
167 C- Split Ocean and Sea-Ice surf. temp. ; remove ice-fraction < 1 %
168 c oceTfreez = tFreeze - 1.9 _d 0
169 oceTfreez = celsius2K - 1.9 _d 0
170 DO J=1,NGP
171 sti1(J,myThid) = sst1(J,myThid)
172 IF ( oice1(J) .GT. 1. _d -2 ) THEN
173 sst1(J,myThid) = MAX(sst1(J,myThid),oceTfreez)
174 sti1(J,myThid) = sst1(J,myThid)
175 & +(sti1(J,myThid)-sst1(J,myThid))/oice1(J)
176 ELSE
177 oice1(J) = 0. _d 0
178 ENDIF
179 ENDDO
180 ELSE
181 DO J=1,NGP
182 sti1(J,myThid) = sst1(J,myThid)
183 ENDDO
184 ENDIF
185
186 C- Surface Albedo : (from F.M. FORDATE S/R)
187 c_FM DALB=ALBICE-ALBSEA
188 RSD=1. _d 0/SDALB
189 ALPHA= 2. _d 0*PI*(TYEAR+10. _d 0/365. _d 0)
190 RZEN = COS(ALPHA) * ( -23.45 _d 0 * deg2rad)
191 ZC = COS(RZEN)
192 ZS = SIN(RZEN)
193 DO j=1,sNy
194 DO i=1,sNx
195 c_FM SNOWC=MIN(1.,RSD*SNOW1(I,J))
196 c_FM ALBL=ALB0(I,J)+MAX(ALBSN-ALB0(I,J),0.0)*SNOWC
197 c_FM ALBS=ALBSEA+DALB*OICE1(I,J)
198 c_FM ALB1(I,J)=FMASK1(I,J)*ALBL+FMASK0(I,J)*ALBS
199 I2 = i+(j-1)*sNx
200 alb_land = aim_albedo(i,j,bi,bj)
201 & + MAX( 0. _d 0, ALBSN-aim_albedo(i,j,bi,bj) )
202 & *MIN( 1. _d 0, RSD*snow1(I2))
203 c alb_sea = ALBSEA + DALB*oice1(I2)
204 c alb1(I2,0,myThid) = alb_sea
205 c & + (alb_land - alb_sea)*fMask1(I2,1,myThid)
206 ALBSEA1 = ALBSEA
207 IF ( aim_selectOceAlbedo .EQ. 1) THEN
208 SJ = SIN(yC(i,j,bi,bj) * deg2rad)
209 CJ = COS(yC(i,j,bi,bj) * deg2rad)
210 TMPA = SJ*ZS
211 TMPB = CJ*ZC
212 TMPL = -TMPA/TMPB
213 IF (TMPL .GE. 1.0 _d 0) THEN
214 CZEN = 0.0 _d 0
215 ELSEIF (TMPL .LE. -1.0 _d 0) THEN
216 CZEN = (2.0 _d 0)*TMPA*PI
217 CZEN2= PI*((2.0 _d 0)*TMPA*TMPA + TMPB*TMPB)
218 CZEN = CZEN2/CZEN
219 ELSE
220 hlim = ACOS(TMPL)
221 CZEN = 2.0 _d 0*(TMPA*hlim + TMPB*SIN(hlim))
222 CZEN2= 2.0 _d 0*TMPA*TMPA*hlim
223 & + 4.0 _d 0*TMPA*TMPB*SIN(hlim)
224 & + TMPB*TMPB*( hlim + 0.5 _d 0*SIN(2.0 _d 0*hlim) )
225 CZEN = CZEN2/CZEN
226 ENDIF
227 ALBSEA1 = ( ( 2.6 _d 0 / (CZEN**(1.7 _d 0) + 0.065 _d 0) )
228 & + ( 15. _d 0 * (CZEN-0.1 _d 0) * (CZEN-0.5 _d 0)
229 & * (CZEN-1.0 _d 0) ) ) / 100.0 _d 0
230 ENDIF
231 alb1(I2,1,myThid) = alb_land
232 C_DE alb1(I2,2,myThid) = ALBSEA
233 alb1(I2,2,myThid) = 0.5 _d 0 * ALBSEA
234 & + 0.5 _d 0 * ALBSEA1
235 alb1(I2,3,myThid) = ALBICE
236 ENDDO
237 ENDDO
238
239 C-- else aim_useFMsurfBC
240 ELSE
241 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
242
243 C- safer to initialise output argument aim_sWght0,1
244 C even if they are not used when aim_useFMsurfBC=F
245 aim_sWght1 = 0. _d 0
246 aim_sWght0 = 1. _d 0
247
248 C- Set surface forcing fields needed by atmos. physics package
249 C 1. Albedo (between 0-1)
250 C 2. Sea Surface temperatures (in situ Temp. [K])
251 C 3. Land Surface temperatures (in situ Temp. [K])
252 C 4. Soil moisture (between 0-1)
253 C Snow depth, Sea Ice (<- no need for now)
254
255 C Set surface albedo data (in [0,1]) from aim_albedo to alb1 :
256 IF (aim_useMMsurfFc) THEN
257 DO j=1,sNy
258 DO i=1,sNx
259 I2 = i+(j-1)*sNx
260 alb1(I2,1,myThid) = aim_albedo(i,j,bi,bj)
261 alb1(I2,2,myThid) = aim_albedo(i,j,bi,bj)
262 alb1(I2,3,myThid) = aim_albedo(i,j,bi,bj)
263 ENDDO
264 ENDDO
265 ELSE
266 DO j=1,sNy
267 DO i=1,sNx
268 I2 = i+(j-1)*sNx
269 alb1(I2,1,myThid) = 0.
270 alb1(I2,2,myThid) = 0.
271 alb1(I2,3,myThid) = 0.
272 ENDDO
273 ENDDO
274 ENDIF
275 C Set surface temperature data from aim_S/LSurfTemp to sst1 & stl1 :
276 IF (aim_useMMsurfFc) THEN
277 DO j=1,sNy
278 DO i=1,sNx
279 I2 = i+(j-1)*sNx
280 sst1(I2,myThid) = aim_sst0(i,j,bi,bj)
281 stl1(I2,myThid) = aim_sst0(i,j,bi,bj)
282 sti1(I2,myThid) = aim_sst0(i,j,bi,bj)
283 ENDDO
284 ENDDO
285 ELSE
286 DO j=1,sNy
287 DO i=1,sNx
288 I2 = i+(j-1)*sNx
289 sst1(I2,myThid) = 300.
290 stl1(I2,myThid) = 300.
291 sti1(I2,myThid) = 300.
292 ENDDO
293 ENDDO
294 ENDIF
295
296 C- Set soil water availability (in [0,1]) from aim_sw10 to soilw1 :
297 IF (aim_useMMsurfFc) THEN
298 DO j=1,sNy
299 DO i=1,sNx
300 I2 = i+(j-1)*sNx
301 soilw1(I2,myThid) = aim_sw10(i,j,bi,bj)
302 ENDDO
303 ENDDO
304 ELSE
305 DO j=1,sNy
306 DO i=1,sNx
307 I2 = i+(j-1)*sNx
308 soilw1(I2,myThid) = 0.
309 ENDDO
310 ENDDO
311 ENDIF
312
313 C- Set Snow depth and Sea Ice
314 C (not needed here since albedo is loaded from file)
315 DO j=1,sNy
316 DO i=1,sNx
317 I2 = i+(j-1)*sNx
318 oice1(I2) = 0.
319 snow1(I2) = 0.
320 ENDDO
321 ENDDO
322
323 C-- endif/else aim_useFMsurfBC
324 ENDIF
325
326 #ifdef COMPONENT_MODULE
327 IF ( useCoupler ) THEN
328 C-- take surface data from the ocean component
329 C to replace MxL fields (if use sea-ice) or directly AIM SST
330 CALL ATM_APPLY_IMPORT(
331 I aim_landFr,
332 U sst1(1,myThid), oice1,
333 I myTime, myIter, bi, bj, myThid )
334 ENDIF
335 #endif /* COMPONENT_MODULE */
336
337 #ifdef ALLOW_AIM_CO2
338 DO j=1,sNy
339 DO i=1,sNx
340 I2 = i+(j-1)*sNx
341 aim_CO2(I2,myThid)= atm_pCO2
342 ENDDO
343 ENDDO
344
345 #ifdef ALLOW_DIAGNOSTICS
346 IF ( useDiagnostics ) THEN
347 pCO2scl = 1. _d 6
348 CALL DIAGNOSTICS_SCALE_FILL( aim_CO2(1,myThid), pCO2scl, 1,
349 & 'aim_pCO2', 1, 1, 3, bi, bj, myThid )
350 ENDIF
351 #endif /* ALLOW_DIAGNOSTICS */
352 #endif
353
354 #ifdef ALLOW_LAND
355 IF (useLand) THEN
356 C- Use land model output instead of prescribed Temp & moisture
357 CALL AIM_LAND2AIM(
358 I aim_landFr, aim_veget, aim_albedo, snow1,
359 U stl1(1,myThid), soilw1(1,myThid), alb1(1,1,myThid),
360 I myTime, myIter, bi, bj, myThid )
361 ENDIF
362 #endif /* ALLOW_LAND */
363
364 #ifdef ALLOW_THSICE
365 IF (useThSIce) THEN
366 C- Use thermo. sea-ice model output instead of prescribed Temp & albedo
367 CALL AIM_SICE2AIM(
368 I aim_landFr,
369 U sst1(1,myThid), oice1,
370 O sti1(1,myThid), alb1(1,3,myThid),
371 I myTime, myIter, bi, bj, myThid )
372 ENDIF
373 #endif /* ALLOW_THSICE */
374
375 C-- set the sea-ice & open ocean fraction :
376 DO J=1,NGP
377 fMask1(J,3,myThid) =(1. _d 0 - fMask1(J,1,myThid))
378 & *oice1(J)
379 fMask1(J,2,myThid) = 1. _d 0 - fMask1(J,1,myThid)
380 & - fMask1(J,3,myThid)
381 ENDDO
382
383 C-- set the mean albedo :
384 DO J=1,NGP
385 alb1(J,0,myThid) = fMask1(J,1,myThid)*alb1(J,1,myThid)
386 & + fMask1(J,2,myThid)*alb1(J,2,myThid)
387 & + fMask1(J,3,myThid)*alb1(J,3,myThid)
388 ENDDO
389
390 C-- initialize surf. temp. change to zero:
391 DO k=1,3
392 DO J=1,NGP
393 dTsurf(J,k,myThid) = 0.
394 ENDDO
395 ENDDO
396
397 IF (.NOT.aim_splitSIOsFx) THEN
398 DO J=1,NGP
399 fMask1(J,3,myThid) = 0. _d 0
400 fMask1(J,2,myThid) = 1. _d 0 - fMask1(J,1,myThid)
401 ENDDO
402 ENDIF
403
404 #endif /* ALLOW_AIM */
405
406 RETURN
407 END

  ViewVC Help
Powered by ViewVC 1.1.22