/[MITgcm]/MITgcm_contrib/dgoldberg/streamice/streamice_fields_load.F
ViewVC logotype

Annotation of /MITgcm_contrib/dgoldberg/streamice/streamice_fields_load.F

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


Revision 1.1 - (hide annotations) (download)
Wed Aug 27 19:29:13 2014 UTC (10 years, 10 months ago) by dgoldberg
Branch: MAIN
CVS Tags: HEAD
updating contrib streamice repo with latest files, and separated out convergence checks; and parameterised maximum iteration counts and interface w shelfice for coupling

1 dgoldberg 1.1 C $Header: /u/gcmpack/MITgcm/pkg/streamice/streamice_fields_load.F,v 1.1 2014/06/04 12:58:26 dgoldberg 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    
155     IF ( STREAMICEBdotTimeDepFile .NE. ' ' ) THEN
156     PRINT *, "GOT HERE FIELDS LOAD 3", STREAMICEBdotTimeDepFile
157     CALL READ_REC_XY_RL(STREAMICEBdotTimeDepFile,
158     & bdot_streamice1,
159     & nm0,myIter,myThid)
160     ENDIF
161    
162     C- endif 1rst iter.
163     ENDIF
164    
165     IF ( first .OR. changed) THEN
166    
167     #ifdef STREAMICE_STRESS_BOUNDARY_CONTROL
168    
169     DO bj=myByLo(myThid),myByHi(myThid)
170     DO bi=myBxLo(myThid),myBxHi(myThid)
171     DO j=1,sNy
172     DO i=1,sNx
173    
174     streamice_u_normal_stress0(i,j,bi,bj) =
175     & streamice_u_normal_stress1(i,j,bi,bj)
176     streamice_v_normal_stress0(i,j,bi,bj) =
177     & streamice_v_normal_stress1(i,j,bi,bj)
178     streamice_u_shear_stress0(i,j,bi,bj) =
179     & streamice_u_shear_stress1(i,j,bi,bj)
180     streamice_v_shear_stress0(i,j,bi,bj) =
181     & streamice_v_shear_stress1(i,j,bi,bj)
182     ENDDO
183     ENDDO
184     ENDDO
185     ENDDO
186     PRINT *, "GOT HERE FIELDS LOAD 4"
187    
188     IF ( STREAMICEuNormalTimeDepFile .NE. ' ' ) THEN
189     CALL READ_REC_XY_RL(STREAMICEuNormalTimeDepFile,
190     & streamice_u_normal_stress1,
191     & nm1,myIter,myThid)
192     ENDIF
193    
194     IF ( STREAMICEvNormalTimeDepFile .NE. ' ' ) THEN
195     CALL READ_REC_XY_RL(STREAMICEvNormalTimeDepFile,
196     & streamice_v_normal_stress1,
197     & nm1,myIter,myThid)
198     ENDIF
199    
200     IF ( STREAMICEuShearTimeDepFile .NE. ' ' ) THEN
201     CALL READ_REC_XY_RL(STREAMICEuShearTimeDepFile,
202     & streamice_u_shear_stress1,
203     & nm1,myIter,myThid)
204     ENDIF
205    
206     IF ( STREAMICEvShearTimeDepFile .NE. ' ' ) THEN
207     CALL READ_REC_XY_RL(STREAMICEvShearTimeDepFile,
208     & streamice_v_shear_stress1,
209     & nm1,myIter,myThid)
210     ENDIF
211    
212     #endif
213    
214     DO bj=myByLo(myThid),myByHi(myThid)
215     DO bi=myBxLo(myThid),myBxHi(myThid)
216     DO j=1,sNy
217     DO i=1,sNx
218     bdot_streamice0(i,j,bi,bj) =
219     & bdot_streamice1(i,j,bi,bj)
220     ENDDO
221     ENDDO
222     ENDDO
223     ENDDO
224    
225     IF ( STREAMICEBdotTimeDepFile .NE. ' ' ) THEN
226     CALL READ_REC_XY_RL(STREAMICEBdotTimeDepFile,
227     & bdot_streamice1,
228     & nm1,myIter,myThid)
229     ENDIF
230    
231     C- endif 1rst iter.
232     ENDIF
233    
234     DO bj=myByLo(myThid),myByHi(myThid)
235     DO bi=myBxLo(myThid),myBxHi(myThid)
236     DO j=1,sNy
237     DO i=1,sNx
238     #ifdef STREAMICE_STRESS_BOUNDARY_CONTROL
239     streamice_u_normal_stress(i,j,bi,bj) =
240     & fac * streamice_u_normal_stress0(i,j,bi,bj)
241     & + (1-fac) * streamice_u_normal_stress1(i,j,bi,bj)
242     streamice_v_normal_stress(i,j,bi,bj) =
243     & fac * streamice_v_normal_stress0(i,j,bi,bj)
244     & + (1-fac) * streamice_v_normal_stress1(i,j,bi,bj)
245     streamice_u_shear_stress(i,j,bi,bj) =
246     & fac * streamice_u_shear_stress0(i,j,bi,bj)
247     & + (1-fac) * streamice_u_shear_stress1(i,j,bi,bj)
248     streamice_v_shear_stress(i,j,bi,bj) =
249     & fac * streamice_v_shear_stress0(i,j,bi,bj)
250     & + (1-fac) * streamice_v_shear_stress1(i,j,bi,bj)
251     #endif
252     bdot_streamice (i,j,bi,bj) =
253     & fac * bdot_streamice0(i,j,bi,bj)
254     & + (1-fac) * bdot_streamice1(i,j,bi,bj)
255     ENDDO
256     ENDDO
257     ENDDO
258     ENDDO
259    
260     print *, "GOT HERE STREAMICE FIELDS LOAD",
261     & first,changed,nm0,nm1,fac
262     #endif
263     #endif
264    
265     RETURN
266     END

  ViewVC Help
Powered by ViewVC 1.1.22