/[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.1 - (show annotations) (download)
Tue Dec 10 02:35:27 2002 UTC (21 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint47e_post, checkpoint50c_post, checkpoint48e_post, checkpoint50c_pre, checkpoint48i_post, checkpoint50d_pre, checkpoint50, checkpoint50d_post, checkpoint50b_pre, checkpoint48b_post, checkpoint48c_pre, checkpoint47d_pre, checkpoint48d_pre, checkpoint47i_post, checkpoint47d_post, checkpoint48d_post, checkpoint48f_post, checkpoint48h_post, checkpoint47g_post, checkpoint48a_post, checkpoint50f_post, checkpoint50a_post, checkpoint50f_pre, checkpoint47j_post, branch-exfmods-tag, checkpoint48c_post, checkpoint50g_post, checkpoint50e_pre, checkpoint47f_post, checkpoint50e_post, checkpoint48, checkpoint49, checkpoint47h_post, checkpoint50b_post, checkpoint48g_post
Branch point for: branch-exfmods-curt
allow to use AIM physics with SPEEDY input files (from Franco Molteni):
 surface Boundary-Conditions are computed in (new) S/R aim_surf_bc.F.
can still use monthly mean (NCEP) surface forcing (with surface
 Temperature or surface Pot.Temp)

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 c #include "GRID.h"
29 c #include "SURFACE.h"
30 #include "AIM_PARAMS.h"
31
32 C-- Physics package
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 == Routine arguments ==
40 C tYear - Fraction into year
41 C myTime - Current time of simulation ( s )
42 C myIter - Current iteration number in simulation
43 C bi,bj - Tile index
44 C myThid - Number of this instance of the routine
45 INTEGER myIter, bi, bj, myThid
46 _RL tYear, myTime
47
48 #ifdef ALLOW_AIM
49 C == Local variables ==
50 C i,j,k,I2 - Loop counters
51 INTEGER i,j,I2
52 _RL SDEP1, IDEP2, SDEP2, SWWIL2, RSW, soilw_0, soilw_1
53 _RL DALB, RSD, alb_sea, alb_land
54
55 IF (aim_useFMsurfBC) THEN
56 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
57
58 C-- Compute surface forcing at present time (linear Interp in time)
59 C using F.Molteni surface BC form ; fields needed are:
60 C 1. Land sea mask
61 C 2. Sea Surface temperatures (in situ Temp. [K])
62 C 3. Land Surface temperatures (in situ Temp. [K])
63 C 4. Soil moisture (between 0-1)
64 C 5. Snow depth, Sea Ice : used to compute albedo (=> local arrays)
65 C 6. Albedo (between 0-1)
66
67 C- Set Land-sea mask (in [0,1]) from aim_landFr to fMask1:
68 DO j=1,sNy
69 DO i=1,sNx
70 I2 = i+(j-1)*sNx
71 fMask1(I2,myThid) = aim_landFr(i,j,bi,bj)
72 ENDDO
73 ENDDO
74
75 C- Surface Temperature:
76 DO j=1,sNy
77 DO i=1,sNx
78 I2 = i+(j-1)*sNx
79 sst1(I2,myThid) = aim_sWght0*aim_sst0(i,j,bi,bj)
80 & + aim_sWght1*aim_sst1(i,j,bi,bj)
81 stl1(I2,myThid) = aim_sWght0*aim_lst0(i,j,bi,bj)
82 & + aim_sWght1*aim_lst1(i,j,bi,bj)
83 ENDDO
84 ENDDO
85
86 C- Soil Water availability : (from F.M. INFORC S/R)
87 SDEP1 = 70. _d 0
88 IDEP2 = 3. _d 0
89 SDEP2 = IDEP2*SDEP1
90
91 SWWIL2= SDEP2*SWWIL
92 RSW = 1. _d 0/(SDEP1*SWCAP+SDEP2*(SWCAP-SWWIL))
93
94 DO j=1,sNy
95 DO i=1,sNx
96 I2 = i+(j-1)*sNx
97 soilw_0 = ( aim_sw10(i,j,bi,bj)
98 & +aim_veget(i,j,bi,bj)*
99 & MAX(IDEP2*aim_sw20(i,j,bi,bj)-SWWIL2, 0. _d 0)
100 & )*RSW
101 soilw_1 = ( aim_sw11(i,j,bi,bj)
102 & +aim_veget(i,j,bi,bj)*
103 & MAX(IDEP2*aim_sw21(i,j,bi,bj)-SWWIL2, 0. _d 0)
104 & )*RSW
105 soilw1(I2,myThid) = aim_sWght0*soilw_0
106 & + aim_sWght1*soilw_1
107 soilw1(I2,myThid) = MIN(1. _d 0, soilw1(I2,myThid) )
108 ENDDO
109 ENDDO
110
111 C- Set snow depth & sea-ice fraction :
112 DO j=1,sNy
113 DO i=1,sNx
114 I2 = i+(j-1)*sNx
115 snow1(I2) = aim_sWght0*aim_snw0(i,j,bi,bj)
116 & + aim_sWght1*aim_snw1(i,j,bi,bj)
117 oice1(I2) = aim_sWght0*aim_oic0(i,j,bi,bj)
118 & + aim_sWght1*aim_oic1(i,j,bi,bj)
119 ENDDO
120 ENDDO
121
122 C- Surface Albedo : (from F.M. FORDATE S/R)
123 DALB=ALBICE-ALBSEA
124 RSD=1. _d 0/SDALB
125 DO j=1,sNy
126 DO i=1,sNx
127 c_FM SNOWC=MIN(1.,RSD*SNOW1(I,J))
128 c_FM ALBL=ALB0(I,J)+MAX(ALBSN-ALB0(I,J),0.0)*SNOWC
129 c_FM ALBS=ALBSEA+DALB*OICE1(I,J)
130 c_FM ALB1(I,J)=FMASK1(I,J)*ALBL+FMASK0(I,J)*ALBS
131 I2 = i+(j-1)*sNx
132 alb_land = aim_albedo(i,j,bi,bj)
133 & + MAX( 0. _d 0, ALBSN-aim_albedo(i,j,bi,bj) )
134 & *MIN( 1. _d 0, RSD*snow1(I2))
135 alb_sea = ALBSEA + DALB*oice1(I2)
136 alb1(I2,myThid) = alb_sea
137 & + (alb_land - alb_sea)*fMask1(I2,myThid)
138 ENDDO
139 ENDDO
140
141 C-- else aim_useFMsurfBC
142 ELSE
143 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
144
145 C- Set surface forcing fields needed by atmos. physics package
146 C 1. Albedo (between 0-1)
147 C 2. Sea Surface temperatures (in situ Temp. [K])
148 C 3. Land Surface temperatures (in situ Temp. [K])
149 C 4. Soil moisture (between 0-1)
150 C 5. Land sea mask (infer from exact zeros in soil moisture)
151 C Snow depth, Sea Ice (<- no need for now)
152
153 C Set surface albedo data (in [0,1]) from aim_albedo to alb1 :
154 IF (aim_useMMsurfFc) THEN
155 DO j=1,sNy
156 DO i=1,sNx
157 I2 = i+(j-1)*sNx
158 alb1(I2,myThid) = aim_albedo(i,j,bi,bj)
159 ENDDO
160 ENDDO
161 ELSE
162 DO j=1,sNy
163 DO i=1,sNx
164 I2 = i+(j-1)*sNx
165 alb1(I2,myThid) = 0.
166 ENDDO
167 ENDDO
168 ENDIF
169 C Set surface temperature data from aim_S/LSurfTemp to sst1 & stl1 :
170 IF (aim_useMMsurfFc) THEN
171 DO j=1,sNy
172 DO i=1,sNx
173 I2 = i+(j-1)*sNx
174 sst1(I2,myThid) = aim_surfTemp(i,j,bi,bj)
175 stl1(I2,myThid) = aim_surfTemp(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 sst1(I2,myThid) = 300.
183 stl1(I2,myThid) = 300.
184 ENDDO
185 ENDDO
186 ENDIF
187
188 C- Set soil water availability (in [0,1]) from aim_soilWater to soilw1 :
189 IF (aim_useMMsurfFc) THEN
190 DO j=1,sNy
191 DO i=1,sNx
192 I2 = i+(j-1)*sNx
193 soilw1(I2,myThid) = aim_soilWater(i,j,bi,bj)
194 ENDDO
195 ENDDO
196 ELSE
197 DO j=1,sNy
198 DO i=1,sNx
199 I2 = i+(j-1)*sNx
200 soilw1(I2,myThid) = 0.
201 ENDDO
202 ENDDO
203 ENDIF
204
205 C- Set Land-sea mask (in [0,1])
206 C from aim_landFr to fMask1 (aim_useFMsurfBC)
207 C or from where soil moisture is exactly zero (aim_useMMsurfFc)
208 IF (aim_useMMsurfFc) THEN
209 DO j=1,sNy
210 DO i=1,sNx
211 I2 = i+(j-1)*sNx
212 fMask1(I2,myThid) = 1.
213 IF ( soilw1(I2,myThid).EQ.0. ) fMask1(I2,myThid) = 0.
214 ENDDO
215 ENDDO
216 ELSE
217 DO j=1,sNy
218 DO i=1,sNx
219 I2 = i+(j-1)*sNx
220 fMask1(I2,myThid) = 0.
221 ENDDO
222 ENDDO
223 ENDIF
224
225 C- Set Snow depth and Sea Ice
226 C (not needed here since albedo is loaded from file)
227 c DO j=1,sNy
228 c DO i=1,sNx
229 c I2 = i+(j-1)*sNx
230 c oice1(I2,myThid) = 0.
231 c snow1(I2,myThid) = 0.
232 c ENDDO
233 c ENDDO
234
235 C-- endif/else aim_useFMsurfBC
236 ENDIF
237
238 #endif /* ALLOW_AIM */
239
240 RETURN
241 END

  ViewVC Help
Powered by ViewVC 1.1.22