/[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.1 - (show annotations) (download)
Sat Jan 24 20:41:25 2004 UTC (20 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52l_pre, checkpoint52j_post, checkpoint52l_post, checkpoint52k_post, checkpoint52j_pre
update AIM Equatorial Channel experiment:
 * use standard aim_v23 pkg (instead of the old pkg/aim).
 * change the forcing (including a more a realistic SST field)
   to be symetric relatively to the Eq.

1 C $Header: $
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 DALB, RSD, alb_sea, alb_land
60
61 C_EqCh: start
62 CHARACTER*(MAX_LEN_MBUF) suff
63 _RL xBump, yBump, dxBump, dyBump
64 xBump = thetaMin + delX(1)*64.
65 yBump = phiMin + delY(1)*11.5
66 dxBump= delX(1)*12.
67 dyBump= delY(1)*6.
68 C_EqCh: Fix solar insolation with Sun directly overhead on Equator
69 tYear = 0.25 _d 0 - 10. _d 0/365. _d 0
70 C_EqCh: end
71
72 IF (aim_useFMsurfBC) THEN
73 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
74
75 C-- Compute surface forcing at present time (linear Interp in time)
76 C using F.Molteni surface BC form ; fields needed are:
77 C 1. Land sea mask
78 C 2. Sea Surface temperatures (in situ Temp. [K])
79 C 3. Land Surface temperatures (in situ Temp. [K])
80 C 4. Soil moisture (between 0-1)
81 C 5. Snow depth, Sea Ice : used to compute albedo (=> local arrays)
82 C 6. Albedo (between 0-1)
83
84 C- Set Land-sea mask (in [0,1]) from aim_landFr to fMask1:
85 DO j=1,sNy
86 DO i=1,sNx
87 I2 = i+(j-1)*sNx
88 fMask1(I2,myThid) = aim_landFr(i,j,bi,bj)
89 ENDDO
90 ENDDO
91
92 C- Surface Temperature:
93 DO j=1,sNy
94 DO i=1,sNx
95 I2 = i+(j-1)*sNx
96 sst1(I2,myThid) = aim_sWght0*aim_sst0(i,j,bi,bj)
97 & + aim_sWght1*aim_sst1(i,j,bi,bj)
98 stl1(I2,myThid) = aim_sWght0*aim_lst0(i,j,bi,bj)
99 & + aim_sWght1*aim_lst1(i,j,bi,bj)
100 ENDDO
101 ENDDO
102
103 C- Soil Water availability : (from F.M. INFORC S/R)
104 SDEP1 = 70. _d 0
105 IDEP2 = 3. _d 0
106 SDEP2 = IDEP2*SDEP1
107
108 SWWIL2= SDEP2*SWWIL
109 RSW = 1. _d 0/(SDEP1*SWCAP+SDEP2*(SWCAP-SWWIL))
110
111 DO j=1,sNy
112 DO i=1,sNx
113 I2 = i+(j-1)*sNx
114 soilw_0 = ( aim_sw10(i,j,bi,bj)
115 & +aim_veget(i,j,bi,bj)*
116 & MAX(IDEP2*aim_sw20(i,j,bi,bj)-SWWIL2, 0. _d 0)
117 & )*RSW
118 soilw_1 = ( aim_sw11(i,j,bi,bj)
119 & +aim_veget(i,j,bi,bj)*
120 & MAX(IDEP2*aim_sw21(i,j,bi,bj)-SWWIL2, 0. _d 0)
121 & )*RSW
122 soilw1(I2,myThid) = aim_sWght0*soilw_0
123 & + aim_sWght1*soilw_1
124 soilw1(I2,myThid) = MIN(1. _d 0, soilw1(I2,myThid) )
125 ENDDO
126 ENDDO
127
128 C- Set snow depth & sea-ice fraction :
129 DO j=1,sNy
130 DO i=1,sNx
131 I2 = i+(j-1)*sNx
132 snow1(I2) = aim_sWght0*aim_snw0(i,j,bi,bj)
133 & + aim_sWght1*aim_snw1(i,j,bi,bj)
134 oice1(I2) = aim_sWght0*aim_oic0(i,j,bi,bj)
135 & + aim_sWght1*aim_oic1(i,j,bi,bj)
136 ENDDO
137 ENDDO
138
139 C- Surface Albedo : (from F.M. FORDATE S/R)
140 DALB=ALBICE-ALBSEA
141 RSD=1. _d 0/SDALB
142 DO j=1,sNy
143 DO i=1,sNx
144 c_FM SNOWC=MIN(1.,RSD*SNOW1(I,J))
145 c_FM ALBL=ALB0(I,J)+MAX(ALBSN-ALB0(I,J),0.0)*SNOWC
146 c_FM ALBS=ALBSEA+DALB*OICE1(I,J)
147 c_FM ALB1(I,J)=FMASK1(I,J)*ALBL+FMASK0(I,J)*ALBS
148 I2 = i+(j-1)*sNx
149 alb_land = aim_albedo(i,j,bi,bj)
150 & + MAX( 0. _d 0, ALBSN-aim_albedo(i,j,bi,bj) )
151 & *MIN( 1. _d 0, RSD*snow1(I2))
152 alb_sea = ALBSEA + DALB*oice1(I2)
153 alb1(I2,myThid) = alb_sea
154 & + (alb_land - alb_sea)*fMask1(I2,myThid)
155 ENDDO
156 ENDDO
157
158 C-- else aim_useFMsurfBC
159 ELSE
160 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
161
162 C- Set surface forcing fields needed by atmos. physics package
163 C 1. Albedo (between 0-1)
164 C 2. Sea Surface temperatures (in situ Temp. [K])
165 C 3. Land Surface temperatures (in situ Temp. [K])
166 C 4. Soil moisture (between 0-1)
167 C 5. Land sea mask (infer from exact zeros in soil moisture)
168 C Snow depth, Sea Ice (<- no need for now)
169
170 C Set surface albedo data (in [0,1]) from aim_albedo to alb1 :
171 IF (aim_useMMsurfFc) THEN
172 DO j=1,sNy
173 DO i=1,sNx
174 I2 = i+(j-1)*sNx
175 alb1(I2,myThid) = aim_albedo(i,j,bi,bj)
176 ENDDO
177 ENDDO
178 ELSE
179 DO j=1,sNy
180 DO i=1,sNx
181 I2 = i+(j-1)*sNx
182 alb1(I2,myThid) = 0.
183 ENDDO
184 ENDDO
185 ENDIF
186 C Set surface temperature data from aim_S/LSurfTemp to sst1 & stl1 :
187 IF (aim_useMMsurfFc) THEN
188 DO j=1,sNy
189 DO i=1,sNx
190 I2 = i+(j-1)*sNx
191 sst1(I2,myThid) = aim_surfTemp(i,j,bi,bj)
192 stl1(I2,myThid) = aim_surfTemp(i,j,bi,bj)
193 ENDDO
194 ENDDO
195 ELSE
196 DO j=1,sNy
197 DO i=1,sNx
198 I2 = i+(j-1)*sNx
199 sst1(I2,myThid) = 300.
200 stl1(I2,myThid) = 300.
201 C_EqCh: start
202 sst1(I2,myThid) = 280.
203 & +20. _d 0 *exp( -((xC(i,j,bi,bj)-xBump)/dxBump)**2
204 & -((yC(i,j,bi,bj)-yBump)/dyBump)**2 )
205 stl1(I2,myThid) = sst1(I2,myThid)
206 C_EqCh: end
207 ENDDO
208 ENDDO
209 C_EqCh: start
210 IF (myIter.EQ.nIter0) THEN
211 WRITE(suff,'(I10.10)') myIter
212 CALL AIM_WRITE_LOCAL('aim_SST.',suff,1,sst1(1,myThid),
213 & bi,bj,1,myIter,myThid)
214 ENDIF
215 C_EqCh: end
216 ENDIF
217
218 C- Set soil water availability (in [0,1]) from aim_soilWater to soilw1 :
219 IF (aim_useMMsurfFc) THEN
220 DO j=1,sNy
221 DO i=1,sNx
222 I2 = i+(j-1)*sNx
223 soilw1(I2,myThid) = aim_soilWater(i,j,bi,bj)
224 ENDDO
225 ENDDO
226 ELSE
227 DO j=1,sNy
228 DO i=1,sNx
229 I2 = i+(j-1)*sNx
230 soilw1(I2,myThid) = 0.
231 ENDDO
232 ENDDO
233 ENDIF
234
235 C- Set Land-sea mask (in [0,1])
236 C from aim_landFr to fMask1 (aim_useFMsurfBC)
237 C or from where soil moisture is exactly zero (aim_useMMsurfFc)
238 IF (aim_useMMsurfFc) THEN
239 DO j=1,sNy
240 DO i=1,sNx
241 I2 = i+(j-1)*sNx
242 fMask1(I2,myThid) = 1.
243 IF ( soilw1(I2,myThid).EQ.0. ) fMask1(I2,myThid) = 0.
244 ENDDO
245 ENDDO
246 ELSE
247 DO j=1,sNy
248 DO i=1,sNx
249 I2 = i+(j-1)*sNx
250 fMask1(I2,myThid) = 0.
251 ENDDO
252 ENDDO
253 ENDIF
254
255 C- Set Snow depth and Sea Ice
256 C (not needed here since albedo is loaded from file)
257 c DO j=1,sNy
258 c DO i=1,sNx
259 c I2 = i+(j-1)*sNx
260 c oice1(I2,myThid) = 0.
261 c snow1(I2,myThid) = 0.
262 c ENDDO
263 c ENDDO
264
265 C-- endif/else aim_useFMsurfBC
266 ENDIF
267
268 #ifdef COMPONENT_MODULE
269 IF ( useCoupler ) THEN
270 IF ( useImportSST ) THEN
271 DO J=1,sNy
272 DO I=1,sNx
273
274 c IF ( SSTocn(I,J,bi,bj) .NE. 0. ) THEN
275 IF ( aim_landFr(i,j,bi,bj) .LT. 1. ) THEN
276 I2 = (sNx)*(J-1)+I
277 C-- take SST from the ocean compon. where Sea-Ice fraction is zero
278 IF ( oice1(I2).EQ.0. ) THEN
279 sst1(I2,myThid) = SSTocn(i,j,bi,bj)+celsius2K
280 C-- take SST from the ocean compon. if clearly warmer than freezing
281 C and reset sea-ice fraction & albedo
282 ELSEIF ( SSTocn(i,j,bi,bj).GE. -1. _d 0) THEN
283 sst1(I2,myThid) = SSTocn(i,j,bi,bj)+celsius2K
284 IF (aim_useFMsurfBC) THEN
285 oice1(I2) = 0.
286 IF (aim_landFr(i,j,bi,bj).EQ. 0.) THEN
287 alb1(I2,myThid) = ALBSEA
288 ELSE
289 C- note: this part never used with current coupled set-up (only full cell
290 C land / sea)
291 alb_land = aim_albedo(i,j,bi,bj)
292 & + MAX( 0. _d 0, ALBSN-aim_albedo(i,j,bi,bj) )
293 & *MIN( 1. _d 0, RSD*snow1(I2))
294 alb_sea = ALBSEA + DALB*oice1(I2)
295 alb1(I2,myThid) = alb_sea
296 & + (alb_land - alb_sea)*fMask1(I2,myThid)
297 ENDIF
298 ENDIF
299 ENDIF
300 ENDIF
301
302 ENDDO
303 ENDDO
304 ENDIF
305 ENDIF
306 #endif /* COMPONENT_MODULE */
307
308 #ifdef ALLOW_LAND
309 IF (useLand) THEN
310 C- Use land model output instead of prescribed Temp & moisture
311 CALL AIM_LAND2AIM( myTime, myIter, bi, bj, myThid )
312 ENDIF
313 #endif /* ALLOW_LAND */
314
315 #endif /* ALLOW_AIM */
316
317 RETURN
318 END

  ViewVC Help
Powered by ViewVC 1.1.22