/[MITgcm]/MITgcm/pkg/streamice/streamice_fields_load.F
ViewVC logotype

Contents of /MITgcm/pkg/streamice/streamice_fields_load.F

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


Revision 1.5 - (show annotations) (download)
Wed Sep 2 12:07:29 2015 UTC (8 years, 8 months ago) by dgoldberg
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65o, HEAD
Changes since 1.4: +18 -1 lines
OL update of modified fields

1 C $Header: /u/gcmpack/MITgcm/pkg/streamice/streamice_fields_load.F,v 1.4 2015/01/30 22:42:37 heimbach Exp $
2 C $Name: $
3
4 #include "STREAMICE_OPTIONS.h"
5
6 CStartOfInterface
7 SUBROUTINE STREAMICE_FIELDS_LOAD(
8 I myTime, myIter, myThid )
9 C *==========================================================*
10 C | SUBROUTINE AIM_FIELDS_LOAD
11 C | o Control reading of AIM fields from external source.
12 C *==========================================================*
13 C | Loads surface boundary condition datasets for AIM.
14 C | The routine is called every timetep and periodically
15 C | loads a set of external fields.
16 C | Monthly climatology files are read either for
17 C | a) a direct use (useMMsurfFc):
18 C | Albedo, Soil moisture, Surface Temperature
19 C | b) time interpolation (useFMsurfBC):
20 C | Sea & Land surf. Temp, snow, sea-ice, soil-water (2-lev)
21 C | + (1rst.iter) ground albedo, vegetation, land-sea fraction
22 C | Most of the work is done by the master thread while
23 C | the other threads spin (but all inside MDSIO S/R).
24 C *==========================================================*
25 IMPLICIT NONE
26
27 C === Global variables ===
28 #include "SIZE.h"
29 #include "EEPARAMS.h"
30 #include "PARAMS.h"
31 #include "GRID.h"
32 #include "STREAMICE.h"
33
34
35
36 C === Routine arguments ===
37 C myTime :: Simulation time
38 C myIter :: Simulation timestep number
39 C myThid :: Thread no. that called this routine.
40 _RL myTime
41 INTEGER myIter
42 INTEGER myThid
43 CEndOfInterface
44
45 C === Functions ===
46
47 #ifdef ALLOW_STREAMICE
48 #ifdef ALLOW_STREAMICE_TIMEDEP_FORCING
49 C === Local variables ===
50 C bi,bj, i,j :: Loop counters
51 C tYear :: Fraction within year of myTime
52 C mnthIndex :: Current time in whole months
53 C prevMnthIndex
54 C fNam :: Strings used in constructing file names
55 C mnthNam
56 C pfact :: used to convert Pot.Temp. to in-situ Temp.
57 C loadNewData :: true when need to load new data from file
58 INTEGER bi,bj,i,j
59 c _RL pfact
60 LOGICAL first, changed
61 C-- for use with useMMsurfFc:
62 CHARACTER*(MAX_LEN_FNAM) fNam
63
64 INTEGER nm0, nm1, nmP
65 _RL myRelTime, fac, tmpFac
66
67 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
68
69 C-- find which month to use for surface BC
70 C aim_surfForc_TimePeriod :: Length of forcing time period (e.g. 1 month)
71 C aim_surfForc_NppCycle :: Number of time period per Cycle (e.g. 12)
72
73 myRelTime = myTime - startTime
74 first = (myRelTime .lt. 0.5*deltaTClock)
75 if ( streamice_forcing_period .eq. 0.D0 ) THEN
76 ! & .or. externForcingCycle .eq. 0.D0 ) then
77 C control parameter is constant in time and only needs to be updated
78 C once in the beginning
79 changed = .false.
80 nm0 = 1
81 nm1 = 1
82 fac = 1.D0
83 else
84
85 C-- Now calculate whether it is time to update the forcing arrays
86 if (externForcingCycle .eq. 0.0 ) THEN
87 CALL GET_PERIODIC_INTERVAL(
88 O nmP, nm0, nm1, tmpFac, fac,
89 I externForcingCycle, streamice_forcing_period,
90 I deltaTclock,
91 I myTime+0.5*streamice_forcing_period,
92 I myThid )
93 fac = 1.D0 - fac
94 else
95 CALL GET_PERIODIC_INTERVAL(
96 O nmP, nm0, nm1, tmpFac, fac,
97 I externForcingCycle, streamice_forcing_period,
98 I deltaTclock, myTime,
99 I myThid )
100 endif
101
102 IF ( nm0.NE.nmP ) THEN
103 changed = .true.
104 ELSE
105 changed = .false.
106 ENDIF
107 IF ( first ) changed = .false.
108 endif
109
110
111
112 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
113
114 C- Load new data:
115
116
117 C- Only one thread updates parameter in common block
118 C- Wait for everyone to set loadNewData before Master updates prevMnthIndex
119 _BARRIER
120
121 IF ( first ) THEN
122
123 #ifdef STREAMICE_STRESS_BOUNDARY_CONTROL
124
125 ! PRINT *, "GOT HERE FIELDS LOAD 1", first, changed,
126 ! & nm0,nm1,myTime,fac
127
128 IF ( STREAMICEuNormalTimeDepFile .NE. ' ' ) THEN
129 CALL READ_REC_XY_RL(STREAMICEuNormalTimeDepFile,
130 & streamice_u_normal_stress1,
131 & nm0,myIter,myThid)
132 ENDIF
133
134 IF ( STREAMICEvNormalTimeDepFile .NE. ' ' ) THEN
135 CALL READ_REC_XY_RL(STREAMICEvNormalTimeDepFile,
136 & streamice_v_normal_stress1,
137 & nm0,myIter,myThid)
138 ENDIF
139
140 IF ( STREAMICEuShearTimeDepFile .NE. ' ' ) THEN
141 CALL READ_REC_XY_RL(STREAMICEuShearTimeDepFile,
142 & streamice_u_shear_stress1,
143 & nm0,myIter,myThid)
144 ENDIF
145
146 IF ( STREAMICEvShearTimeDepFile .NE. ' ' ) THEN
147 CALL READ_REC_XY_RL(STREAMICEvShearTimeDepFile,
148 & streamice_v_shear_stress1,
149 & nm0,myIter,myThid)
150 ENDIF
151 ! PRINT *, "GOT HERE FIELDS LOAD 2"
152
153 #endif
154 #ifdef ALLOW_STREAMICE_FLUX_CONTROL
155 IF ( STREAMICEuFluxTimeDepFile .NE. ' ' ) THEN
156 CALL READ_REC_XY_RL(STREAMICEuFluxTimeDepFile,
157 & u_flux_bdry_SI_1,
158 & nm0,myIter,myThid)
159 ENDIF
160 IF ( STREAMICEvFluxTimeDepFile .NE. ' ' ) THEN
161 CALL READ_REC_XY_RL(STREAMICEvFluxTimeDepFile,
162 & u_flux_bdry_SI_1,
163 & nm0,myIter,myThid)
164 ENDIF
165 #endif
166
167 IF ( STREAMICEBdotTimeDepFile .NE. ' ' ) THEN
168 ! PRINT *, "GOT HERE FIELDS LOAD 3", STREAMICEBdotTimeDepFile
169 CALL READ_REC_XY_RL(STREAMICEBdotTimeDepFile,
170 & bdot_streamice1,
171 & nm0,myIter,myThid)
172 ENDIF
173
174 C- endif 1rst iter.
175 ENDIF
176
177 IF ( first .OR. changed) THEN
178
179 #ifdef STREAMICE_STRESS_BOUNDARY_CONTROL
180
181 DO bj=myByLo(myThid),myByHi(myThid)
182 DO bi=myBxLo(myThid),myBxHi(myThid)
183 DO j=1,sNy
184 DO i=1,sNx
185
186 streamice_u_normal_stress0(i,j,bi,bj) =
187 & streamice_u_normal_stress1(i,j,bi,bj)
188 streamice_v_normal_stress0(i,j,bi,bj) =
189 & streamice_v_normal_stress1(i,j,bi,bj)
190 streamice_u_shear_stress0(i,j,bi,bj) =
191 & streamice_u_shear_stress1(i,j,bi,bj)
192 streamice_v_shear_stress0(i,j,bi,bj) =
193 & streamice_v_shear_stress1(i,j,bi,bj)
194 ENDDO
195 ENDDO
196 ENDDO
197 ENDDO
198 ! PRINT *, "GOT HERE FIELDS LOAD 4"
199
200 IF ( STREAMICEuNormalTimeDepFile .NE. ' ' ) THEN
201 CALL READ_REC_XY_RL(STREAMICEuNormalTimeDepFile,
202 & streamice_u_normal_stress1,
203 & nm1,myIter,myThid)
204 ENDIF
205
206 IF ( STREAMICEvNormalTimeDepFile .NE. ' ' ) THEN
207 CALL READ_REC_XY_RL(STREAMICEvNormalTimeDepFile,
208 & streamice_v_normal_stress1,
209 & nm1,myIter,myThid)
210 ENDIF
211
212 IF ( STREAMICEuShearTimeDepFile .NE. ' ' ) THEN
213 CALL READ_REC_XY_RL(STREAMICEuShearTimeDepFile,
214 & streamice_u_shear_stress1,
215 & nm1,myIter,myThid)
216 ENDIF
217
218 IF ( STREAMICEvShearTimeDepFile .NE. ' ' ) THEN
219 CALL READ_REC_XY_RL(STREAMICEvShearTimeDepFile,
220 & streamice_v_shear_stress1,
221 & nm1,myIter,myThid)
222 ENDIF
223
224 #endif
225 #ifdef ALLOW_STREAMICE_FLUX_CONTROL
226
227 DO bj=myByLo(myThid),myByHi(myThid)
228 DO bi=myBxLo(myThid),myBxHi(myThid)
229 DO j=1,sNy
230 DO i=1,sNx
231
232 u_flux_bdry_SI_0(i,j,bi,bj) =
233 & u_flux_bdry_SI_1(i,j,bi,bj)
234 v_flux_bdry_SI_0(i,j,bi,bj) =
235 & v_flux_bdry_SI_1(i,j,bi,bj)
236
237 ENDDO
238 ENDDO
239 ENDDO
240 ENDDO
241 ! PRINT *, "GOT HERE FIELDS LOAD 4"
242
243
244 IF ( STREAMICEuFluxTimeDepFile .NE. ' ' ) THEN
245 CALL READ_REC_XY_RL(STREAMICEuFluxTimeDepFile,
246 & u_flux_bdry_SI_1,
247 & nm1,myIter,myThid)
248 ENDIF
249
250 IF ( STREAMICEuFluxTimeDepFile .NE. ' ' ) THEN
251 CALL READ_REC_XY_RL(STREAMICEvFluxTimeDepFile,
252 & v_flux_bdry_SI_1,
253 & nm1,myIter,myThid)
254 ENDIF
255
256 #endif
257
258
259 DO bj=myByLo(myThid),myByHi(myThid)
260 DO bi=myBxLo(myThid),myBxHi(myThid)
261 DO j=1,sNy
262 DO i=1,sNx
263 bdot_streamice0(i,j,bi,bj) =
264 & bdot_streamice1(i,j,bi,bj)
265 ENDDO
266 ENDDO
267 ENDDO
268 ENDDO
269
270 IF ( STREAMICEBdotTimeDepFile .NE. ' ' ) THEN
271 CALL READ_REC_XY_RL(STREAMICEBdotTimeDepFile,
272 & bdot_streamice1,
273 & nm1,myIter,myThid)
274 ENDIF
275
276 C- endif 1rst iter.
277 ENDIF
278
279 DO bj=myByLo(myThid),myByHi(myThid)
280 DO bi=myBxLo(myThid),myBxHi(myThid)
281 DO j=1,sNy
282 DO i=1,sNx
283 #ifdef STREAMICE_STRESS_BOUNDARY_CONTROL
284 streamice_u_normal_stress(i,j,bi,bj) =
285 & fac * streamice_u_normal_stress0(i,j,bi,bj)
286 & + (1-fac) * streamice_u_normal_stress1(i,j,bi,bj)
287 streamice_v_normal_stress(i,j,bi,bj) =
288 & fac * streamice_v_normal_stress0(i,j,bi,bj)
289 & + (1-fac) * streamice_v_normal_stress1(i,j,bi,bj)
290 streamice_u_shear_stress(i,j,bi,bj) =
291 & fac * streamice_u_shear_stress0(i,j,bi,bj)
292 & + (1-fac) * streamice_u_shear_stress1(i,j,bi,bj)
293 streamice_v_shear_stress(i,j,bi,bj) =
294 & fac * streamice_v_shear_stress0(i,j,bi,bj)
295 & + (1-fac) * streamice_v_shear_stress1(i,j,bi,bj)
296 #endif
297 #ifdef ALLOW_STREAMICE_FLUX_CONTROL
298 u_flux_bdry_pert(i,j,bi,bj) =
299 & fac * u_flux_bdry_SI_0(i,j,bi,bj)
300 & + (1-fac) * u_flux_bdry_SI_1(i,j,bi,bj)
301 v_flux_bdry_pert(i,j,bi,bj) =
302 & fac * v_flux_bdry_SI_0(i,j,bi,bj)
303 & + (1-fac) * v_flux_bdry_SI_1(i,j,bi,bj)
304 #endif
305
306 bdot_streamice (i,j,bi,bj) =
307 & fac * bdot_streamice0(i,j,bi,bj)
308 & + (1-fac) * bdot_streamice1(i,j,bi,bj)
309 ENDDO
310 ENDDO
311 ENDDO
312 ENDDO
313
314 CALL EXCH_XY_RL
315 & (streamice_v_shear_stress, myThid)
316 CALL EXCH_XY_RL
317 & (streamice_u_shear_stress, myThid)
318 CALL EXCH_XY_RL
319 & (streamice_v_normal_stress, myThid)
320 CALL EXCH_XY_RL
321 & (streamice_u_normal_stress, myThid)
322
323 _EXCH_XY_RL(bdot_streamice, mythid )
324 #ifdef ALLOW_STREAMICE_FLUX_CONTROL
325 CALL EXCH_XY_RL
326 & (u_flux_bdry_pert, myThid)
327 CALL EXCH_XY_RL
328 & (v_flux_bdry_pert, myThid)
329 #endif
330
331 ! print *, "GOT HERE STREAMICE FIELDS LOAD",
332 ! & first,changed,nm0,nm1,fac
333 #endif
334 #endif
335
336 RETURN
337 END

  ViewVC Help
Powered by ViewVC 1.1.22