/[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.20 - (show annotations) (download)
Mon Jan 21 21:49:33 2013 UTC (11 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65o, checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, HEAD
Changes since 1.19: +6 -7 lines
change aim_CO2 array (add  nSx,nSy dims to replace MAX_NO_THREADS).

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

  ViewVC Help
Powered by ViewVC 1.1.22