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

Annotation of /MITgcm/pkg/aim_v23/aim_fields_load.F

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


Revision 1.5 - (hide annotations) (download)
Tue Aug 8 03:16:11 2006 UTC (17 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58o_post, checkpoint58p_post, checkpoint58n_post
Changes since 1.4: +108 -98 lines
all threads call READ S/R (which has BARRIER inside).

1 jmc 1.5 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_fields_load.F,v 1.4 2005/04/06 18:35:17 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "AIM_OPTIONS.h"
5 jmc 1.5
6 jmc 1.1 CStartOfInterface
7 jmc 1.5 SUBROUTINE AIM_FIELDS_LOAD(
8     I myTime, myIter, myThid )
9 jmc 1.1 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 jmc 1.5 C | a) a direct use (useMMsurfFc):
18 jmc 1.1 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 the thread while
23     C | the other threads spin.
24     C *==========================================================*
25     IMPLICIT NONE
26 jmc 1.5
27 jmc 1.1 C === Global variables ===
28     #include "SIZE.h"
29     #include "EEPARAMS.h"
30     #include "PARAMS.h"
31     #include "GRID.h"
32     #include "AIM_PARAMS.h"
33     c #include "AIM_GRID.h"
34     #include "AIM_FFIELDS.h"
35 jmc 1.5
36 jmc 1.1 C === Routine arguments ===
37     C myThid - Thread no. that called this routine.
38     C myTime - Simulation time
39     C myIter - Simulation timestep number
40     INTEGER myThid
41     _RL myTime
42     INTEGER myIter
43     CEndOfInterface
44 jmc 1.5
45 jmc 1.1 C === Functions ===
46    
47     #ifdef ALLOW_AIM
48     C === Local variables ===
49     C bi,bj, i,j - Loop counters
50     C tYear - Fraction within year of myTime
51     C mnthIndex - Current time in whole months
52     C prevMnthIndex
53     C fNam - Strings used in constructing file names
54     C mnthNam
55     C pfact - used to convert Pot.Temp. to in-situ Temp.
56     INTEGER bi,bj, i, j
57     c _RL pfact
58     INTEGER prevMnthIndex
59 jmc 1.5 COMMON / LOCAL_AIM_FIELDS_LOAD / prevMnthIndex
60     c DATA prevMnthIndex / 0 /
61     c SAVE prevMnthIndex
62 jmc 1.1 C-- for use with useMMsurfFc:
63     _RL tYear, yearLength
64     INTEGER mnthIndex
65     CHARACTER*(MAX_LEN_FNAM) fNam
66     CHARACTER*3 mnthNam(12)
67     DATA mnthNam /
68     & 'jan', 'feb', 'mar', 'apr', 'may', 'jun',
69     & 'jul', 'aug', 'sep', 'oct', 'nov', 'dec' /
70     SAVE mnthNam
71     C-- for use with useFMsurfBC:
72     INTEGER aim_surfForc_NppCycle, nm0, nm1, nm2, nm3
73     _RL aim_surfForc_TimePeriod, aim_surfForc_TransRatio
74     _RL t0prd, tNcyc, tmprd, dTprd
75    
76 jmc 1.5 C- Initialise local common block
77     IF ( myIter.EQ.nIter0 ) prevMnthIndex = 0
78    
79 jmc 1.1 IF (aim_useMMsurfFc) THEN
80     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
81     C-- Use Monthly Mean surface forcing fields:
82    
83     C- Calculate offset into a year
84     c tYear = myTime/(86400.*360.) -
85     c & FLOAT(INT(myTime/(86400.*360.)))
86     yearLength = 86400.*360.
87     tYear = MOD(myTime/yearLength, 1. _d 0)
88     mnthIndex = INT(tYear*12.)+1
89    
90     IF ( mnthIndex .NE. prevMnthIndex .OR.
91     & myIter.EQ.nIter0 ) THEN
92     C- New month so load in data
93    
94     C Prevent loading of new data before everyone has finished with it
95 jmc 1.5 CALL BAR2(myThid)
96 jmc 1.1
97     _BEGIN_MASTER( myThid )
98     prevMnthIndex = mnthIndex
99 jmc 1.5 _END_MASTER( myThid )
100    
101     C Master thread coordinates loading of AIM datasets
102     C note: with some I/O option (e.g.: SingleCpuIO) READ S/R contains
103     C multi-threaded tasks => let all threads call the READ S/R ;
104     C ( MASTER directives are inside S/R READ to do master-thread I/O)
105 jmc 1.1
106     C o Albedo ( convert % to fraction )
107     WRITE(fNam,'(A,A,A)' ) 'salb.',
108     & mnthNam(mnthIndex), aim_MMsufx(1:aim_MMsufxLength)
109 jmc 1.5 CALL READ_REC_XY_RS( fNam, aim_albedo, 1, myIter, myThid )
110 jmc 1.1
111     C o Surface temperature ( in kelvin )
112 jmc 1.5 IF (aim_surfPotTemp) THEN
113     WRITE(fNam,'(A,A,A)' )'stheta.',
114 jmc 1.1 & mnthNam(mnthIndex), aim_MMsufx(1:aim_MMsufxLength)
115 jmc 1.5 ELSE
116     WRITE(fNam,'(A,A,A)' )'sTemp.',
117 jmc 1.1 & mnthNam(mnthIndex), aim_MMsufx(1:aim_MMsufxLength)
118 jmc 1.5 ENDIF
119     CALL READ_REC_XY_RS( fNam, aim_surftemp, 1, myIter, myThid )
120 jmc 1.1
121 jmc 1.5 C o Soil moisture
122 jmc 1.1 WRITE(fNam,'(A,A,A)' ) 'smoist.',
123     & mnthNam(mnthIndex), aim_MMsufx(1:aim_MMsufxLength)
124 jmc 1.5 CALL READ_REC_XY_RS( fNam, aim_soilWater,1, myIter, myThid )
125    
126     C Stop anyone leaving until all data is read
127     CALL BAR2(myThid)
128 jmc 1.1
129     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
130    
131     C-- Converts fields for direct use in Atmos. Physics routine.
132     C better here rather than in "aim_do_atmos" since:
133     C a) change together conversion factor and input file name.
134 jmc 1.5 C b) conversion applied only 1 time / month ;
135 jmc 1.1 C c) easy to check here (variable in common).
136    
137 jmc 1.5 DO bj = myByLo(myThid), myByHi(myThid)
138     DO bi = myBxLo(myThid), myBxHi(myThid)
139 jmc 1.1
140     C- Converts surface albedo : input data is in % 0-100
141 adcroft 1.2 C and Franco s package needs a fraction between 0-1
142 jmc 1.1 DO j=1,sNy
143     DO i=1,sNx
144     aim_albedo(I,J,bi,bj) = aim_albedo(I,J,bi,bj)/100.
145     ENDDO
146     ENDDO
147    
148     C- Converts soil moisture (case input is in cm in bucket of depth 20cm.)
149     c DO j=1,sNy
150     c DO i=1,sNx
151     c aim_soilWater(I,J,bi,bj) = aim_soilWater(I,J,bi,bj)
152     c & /20.
153     c ENDDO
154     c ENDDO
155 jmc 1.5
156     C-- Correct for truncation (because of hFacMin) of surface reference
157 jmc 1.1 C pressure Ro_surf that affects Surf.Temp. :
158     DO j=1,sNy
159     DO i=1,sNx
160     c pfact = (Ro_surf(i,j,bi,bj)/atm_Po)**atm_kappa
161 jmc 1.5 aim_surftemp(i,j,bi,bj) = aim_surftemp(i,j,bi,bj)
162 jmc 1.1 & * truncSurfP(i,j,bi,bj)
163     ENDDO
164     ENDDO
165    
166     C-- end bi,bj loops
167     ENDDO
168     ENDDO
169    
170 jmc 1.5 IF (myIter.EQ.nIter0) THEN
171     CALL BAR2(myThid)
172     CALL WRITE_FLD_XY_RL('aim_Tsurf',' ',aim_surfTemp,0,myThid)
173     ENDIF
174 jmc 1.1
175    
176     C- endif New month - load in data
177     ENDIF
178    
179     ELSEIF (aim_useFMsurfBC) THEN
180     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
181     C-- Use Franco Molteni surface BC:
182 jmc 1.5 C take part of S/R INFORC + part of S/R FORDATE (albedo)
183 jmc 1.1 C of the F.Molteni SPEEDY code (ver23)
184    
185 jmc 1.5 IF ( myIter.EQ.nIter0 ) THEN
186 jmc 1.1 DO bj = myByLo(myThid), myByHi(myThid)
187 jmc 1.5 DO bi = myBxLo(myThid), myBxHi(myThid)
188 jmc 1.1 DO j=1-Oly,sNy+Oly
189     DO i=1-Olx,sNx+Olx
190 jmc 1.5 c aim_landFr(i,j,bi,bj)= 0.
191     aim_albedo(i,j,bi,bj)= 0.
192     aim_veget(i,j,bi,bj) = 0.
193 jmc 1.1 aim_sst0(i,j,bi,bj) =300.
194     aim_lst0(i,j,bi,bj) =300.
195     aim_oic0(i,j,bi,bj) = 0.
196     aim_snw0(i,j,bi,bj) = 0.
197     aim_sw10(i,j,bi,bj) = 0.
198     aim_sw20(i,j,bi,bj) = 0.
199     aim_sst1(i,j,bi,bj) =300.
200     aim_lst1(i,j,bi,bj) =300.
201     aim_oic1(i,j,bi,bj) = 0.
202     aim_snw1(i,j,bi,bj) = 0.
203     aim_sw11(i,j,bi,bj) = 0.
204     aim_sw21(i,j,bi,bj) = 0.
205     ENDDO
206     ENDDO
207     ENDDO
208     ENDDO
209     ENDIF
210    
211     C- Length (s) of one time period:
212     aim_surfForc_TimePeriod = 30.*86400.
213     C- Number of time period per Cycle:
214     aim_surfForc_NppCycle = 12
215     C- define how fast the (linear) transition is from one month to the next
216     C = 1 -> linear between 2 midle month
217     C > TimePeriod/deltaT -> jump from one month to the next one
218     aim_surfForc_TransRatio = 1.
219    
220     t0prd = myTime / aim_surfForc_TimePeriod
221     tNcyc = aim_surfForc_NppCycle
222     tmprd = t0prd - 0.5 _d 0 + tNcyc
223     tmprd = MOD(tmprd,tNcyc)
224     C- indices of previous month and next month:
225     nm0 = 1 + INT(tmprd)
226     nm1 = 1 + MOD(nm0,aim_surfForc_NppCycle)
227     C- interpolation weight:
228     dTprd = tmprd - (nm0 - 1)
229     aim_sWght1 = 0.5 _d 0+(dTprd-0.5 _d 0)*aim_surfForc_TransRatio
230     aim_sWght1 = MAX( 0. _d 0, MIN(1. _d 0, aim_sWght1) )
231     aim_sWght0 = 1. _d 0 - aim_sWght1
232    
233 jmc 1.5
234 jmc 1.1 IF (myIter.EQ.nIter0 .OR. nm0.NE.prevMnthIndex) THEN
235     C- Load new data:
236    
237 jmc 1.5 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
238 jmc 1.1 C Prevent loading of new data before everyone has finished with it
239 jmc 1.5 CALL BAR2(myThid)
240    
241     _BEGIN_MASTER( myThid )
242     C- only one thread updates parameter in common block
243     prevMnthIndex = nm0
244     _END_MASTER( myThid )
245 jmc 1.1
246     C Master thread coordinates loading of AIM datasets
247 jmc 1.5 C note: with some I/O option (e.g.: SingleCpuIO) READ S/R contains
248     C multi-threaded tasks => let all threads call the READ S/R ;
249     C ( MASTER directives are inside S/R READ to do master-thread I/O)
250 jmc 1.1
251 jmc 1.5 IF ( myIter.EQ.nIter0 ) THEN
252     C- Load Fixed Forcing only at the 1rst iter:
253 jmc 1.1
254 jmc 1.5 c IF ( aim_LandFile .NE. ' ' ) THEN
255 jmc 1.3 c CALL READ_REC_XY_RS(aim_LandFile,aim_landFr,1,myIter,myThid)
256     c ENDIF
257 jmc 1.5 IF ( aim_albFile .NE. ' ' ) THEN
258 jmc 1.1 CALL READ_REC_XY_RS(aim_albFile,aim_albedo, 1,myIter,myThid)
259     ENDIF
260     c alb0(i,j) = 0.01*r4inp(i,j)
261 jmc 1.5 IF ( aim_vegFile .NE. ' ' ) THEN
262 jmc 1.1 CALL READ_REC_XY_RS(aim_vegFile,aim_veget,1,myIter,myThid)
263     ENDIF
264    
265 jmc 1.5 C- endif 1rst iter.
266 jmc 1.1 ENDIF
267    
268 jmc 1.5 IF ( aim_sstFile .NE. ' ' ) THEN
269 jmc 1.1 CALL READ_REC_XY_RS(aim_sstFile,aim_sst0,nm0,myIter,myThid)
270     CALL READ_REC_XY_RS(aim_sstFile,aim_sst1,nm1,myIter,myThid)
271 jmc 1.5 ENDIF
272     IF ( aim_lstFile .NE. ' ' ) THEN
273 jmc 1.1 CALL READ_REC_XY_RS(aim_lstFile,aim_lst0,nm0,myIter,myThid)
274     CALL READ_REC_XY_RS(aim_lstFile,aim_lst1,nm1,myIter,myThid)
275 jmc 1.5 ENDIF
276     IF ( aim_oiceFile .NE. ' ' ) THEN
277 jmc 1.1 CALL READ_REC_XY_RS(aim_oiceFile,aim_oic0,nm0,myIter,myThid)
278     CALL READ_REC_XY_RS(aim_oiceFile,aim_oic1,nm1,myIter,myThid)
279 jmc 1.5 ENDIF
280     IF ( aim_snowFile .NE. ' ' ) THEN
281 jmc 1.1 CALL READ_REC_XY_RS(aim_snowFile,aim_snw0,nm0,myIter,myThid)
282     CALL READ_REC_XY_RS(aim_snowFile,aim_snw1,nm1,myIter,myThid)
283 jmc 1.5 ENDIF
284     IF ( aim_swcFile .NE. ' ' ) THEN
285 jmc 1.1 CALL READ_REC_XY_RS(aim_swcFile,aim_sw10,nm0,myIter,myThid)
286     CALL READ_REC_XY_RS(aim_swcFile,aim_sw11,nm1,myIter,myThid)
287     nm2 = nm0 + aim_surfForc_NppCycle
288     nm3 = nm1 + aim_surfForc_NppCycle
289     CALL READ_REC_XY_RS(aim_swcFile,aim_sw20,nm2,myIter,myThid)
290     CALL READ_REC_XY_RS(aim_swcFile,aim_sw21,nm3,myIter,myThid)
291 jmc 1.5 ENDIF
292    
293     C Stop anyone leaving until all data is read
294     CALL BAR2(myThid)
295 jmc 1.1
296     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
297    
298 jmc 1.5 DO bj = myByLo(myThid), myByHi(myThid)
299     DO bi = myBxLo(myThid), myBxHi(myThid)
300    
301     IF ( myIter.EQ.nIter0 ) THEN
302     C- Converts surface albedo : from % (input data) to a fraction [0-1}
303     c alb0(i,j) = 0.01*r4inp(i,j)
304     DO j=1,sNy
305     DO i=1,sNx
306     aim_albedo(i,j,bi,bj) = aim_albedo(I,J,bi,bj)/100. _d 0
307     ENDDO
308     ENDDO
309 jmc 1.1
310 jmc 1.5 C- Converts vegetation fraction: from % (input data) to a fraction [0-1]
311     c veg(i,j)=max(0.,0.01*veg(i,j))
312 jmc 1.1 DO j=1,sNy
313     DO i=1,sNx
314 jmc 1.5 aim_veget(i,j,bi,bj) =
315     & MAX(0. _d 0, aim_veget(i,j,bi,bj)/100. _d 0)
316     ENDDO
317     ENDDO
318     C- endif 1rst iter.
319     ENDIF
320    
321     C-- Correct for truncation (because of hFacMin) of surface reference
322     C pressure Ro_surf that affects Surf.Temp. :
323     DO j=1,sNy
324     DO i=1,sNx
325 jmc 1.1 c pfact = (Ro_surf(i,j,bi,bj)/atm_Po)**atm_kappa
326     aim_lst0(i,j,bi,bj) = aim_lst0(i,j,bi,bj)
327     & * truncSurfP(i,j,bi,bj)
328     aim_lst1(i,j,bi,bj) = aim_lst1(i,j,bi,bj)
329     & * truncSurfP(i,j,bi,bj)
330     ENDDO
331     ENDDO
332 jmc 1.5
333     C- end bi,bj loops
334 jmc 1.1 ENDDO
335 jmc 1.5 ENDDO
336 jmc 1.1
337 jmc 1.5 C-- endif load new data.
338 jmc 1.1 ENDIF
339    
340     ENDIF
341    
342     #endif /* ALLOW_AIM */
343    
344 jmc 1.5 RETURN
345 jmc 1.1 END

  ViewVC Help
Powered by ViewVC 1.1.22