/[MITgcm]/MITgcm/verification/aim.5l_cs/code/external_fields_load.F
ViewVC logotype

Annotation of /MITgcm/verification/aim.5l_cs/code/external_fields_load.F

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


Revision 1.1 - (hide annotations) (download)
Mon Jun 18 17:40:07 2001 UTC (22 years, 11 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint40pre1, checkpoint44b_post, checkpoint43a-release1mods, checkpoint44h_pre, checkpoint44e_post, release1_p12, release1_p13, release1_p10, release1_p11, release1_p16, release1_p17, release1_p14, release1_p15, checkpoint40pre9, release1_p13_pre, checkpoint46i_post, checkpoint40pre3, checkpoint44f_pre, checkpoint46f_post, checkpoint46l_pre, checkpoint46d_pre, release1_beta1, checkpoint46e_post, release1-branch_tutorials, checkpoint46c_post, checkpoint44g_post, checkpoint44h_post, checkpoint46l_post, checkpoint46k_post, checkpoint46e_pre, checkpoint45d_post, checkpoint46j_pre, checkpoint45b_post, checkpoint46b_pre, checkpoint40pre7, chkpt44a_pre, release1-branch-end, release1_final_v1, release1_p12_pre, checkpoint46c_pre, checkpoint43, checkpoint40, checkpoint41, checkpoint44, checkpoint45, checkpoint44f_post, checkpoint40pre2, checkpoint40pre5, checkpoint40pre6, checkpoint40pre8, release1_b1, chkpt44d_post, checkpoint46h_pre, release1_p8, release1_p9, checkpoint46g_pre, release1_p2, release1_p3, release1_p4, release1_p6, checkpoint46a_post, chkpt44a_post, checkpoint44b_pre, release1_p1, checkpoint46m_post, checkpoint46j_post, checkpoint40pre4, checkpoint46a_pre, checkpoint45c_post, release1_p5, checkpoint44e_pre, release1_p7, checkpoint46b_post, checkpoint46d_post, checkpoint46g_post, checkpoint45a_post, checkpoint42, release1-branch_branchpoint, checkpoint46, checkpoint46h_post, release1_chkpt44d_post, chkpt44c_pre, chkpt44c_post
Branch point for: release1_final, release1, release1_coupled, release1-branch, release1_50yr
Add to main branch of
  o CS atmos with AIM physics
  o Multi-threaded AIM physics for LatLon and CS tests
  o Tidied up monitor() output

1 cnh 1.1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/external_fields_load.F,v 1.5 2001/02/04 14:38:47 cnh Exp $
2     C $Name: $
3    
4     #include "CPP_OPTIONS.h"
5    
6     CStartOfInterface
7     SUBROUTINE EXTERNAL_FIELDS_LOAD( myTime, myIter, myThid )
8     C /==========================================================\
9     C | SUBROUTINE EXTERNAL_FIELDS_LOAD |
10     C | o Control reading of fields from external source. |
11     C |==========================================================|
12     C | External source field loading routine. |
13     C | This routine is called every time we want to |
14     C | load a a set of external fields. The routine decides |
15     C | which fields to load and then reads them in. |
16     C | This routine needs to be customised for particular |
17     C | experiments. |
18     C | Notes |
19     C | ===== |
20     C | Two-dimensional and three-dimensional I/O are handled in |
21     C | the following way under MITgcmUV. A master thread |
22     C | performs I/O using system calls. This threads reads data |
23     C | into a temporary buffer. At present the buffer is loaded |
24     C | with the entire model domain. This is probably OK for now|
25     C | Each thread then copies data from the buffer to the |
26     C | region of the proper array it is responsible for. |
27     C | ===== |
28     C | Conversion of flux fields are described in FFIELDS.h |
29     C \==========================================================/
30     IMPLICIT NONE
31    
32     C === Global variables ===
33     #include "SIZE.h"
34     #include "EEPARAMS.h"
35     #include "PARAMS.h"
36     #include "FFIELDS.h"
37     #include "GRID.h"
38     #include "DYNVARS.h"
39    
40     C === Routine arguments ===
41     C myThid - Thread no. that called this routine.
42     C myTime - Simulation time
43     C myIter - Simulation timestep number
44     INTEGER myThid
45     _RL myTime
46     INTEGER myIter
47     CEndOfInterface
48    
49     C === Functions ===
50     LOGICAL DIFFERENT_MULTIPLE
51     EXTERNAL DIFFERENT_MULTIPLE
52    
53     C === Local arrays ===
54     COMMON /TDFIELDS/
55     & taux0, tauy0, Qnet0, EmPmR0, SST0, SSS0, Qsw0,
56     & taux1, tauy1, Qnet1, EmPmR1, SST1, SSS1, Qsw1
57     _RS taux0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
58     _RS tauy0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
59     _RS Qnet0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
60     _RS EmPmR0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
61     _RS SST0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
62     _RS SSS0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
63     _RS Qsw0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
64     _RS taux1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
65     _RS tauy1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
66     _RS Qnet1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
67     _RS EmPmR1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
68     _RS SST1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
69     _RS SSS1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
70     _RS Qsw1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
71    
72     C === Local variables ===
73     INTEGER bi,bj,i,j,intime0,intime1
74     CHARACTER*(MAX_LEN_MBUF) msgBuf
75    
76     _RL aWght,bWght,rdt
77     INTEGER nForcingPeriods,Imytm,Ifprd,Ifcyc,Iftm
78    
79     IF ( periodicExternalForcing ) THEN
80    
81     C First call requires that we initialize everything to zero for safety
82     IF ( myIter .EQ. nIter0 ) THEN
83     CALL LEF_ZERO( taux0 ,myThid )
84     CALL LEF_ZERO( tauy0 ,myThid )
85     CALL LEF_ZERO( Qnet0 ,myThid )
86     CALL LEF_ZERO( EmPmR0 ,myThid )
87     CALL LEF_ZERO( SST0 ,myThid )
88     CALL LEF_ZERO( SSS0 ,myThid )
89     CALL LEF_ZERO( Qsw0 ,myThid )
90     CALL LEF_ZERO( taux1 ,myThid )
91     CALL LEF_ZERO( tauy1 ,myThid )
92     CALL LEF_ZERO( Qnet1 ,myThid )
93     CALL LEF_ZERO( EmPmR1 ,myThid )
94     CALL LEF_ZERO( SST1 ,myThid )
95     CALL LEF_ZERO( SSS1 ,myThid )
96     CALL LEF_ZERO( Qsw1 ,myThid )
97     ENDIF
98    
99     C Now calculate whether it is time to update the forcing arrays
100     rdt=1. _d 0 / deltaTclock
101     nForcingPeriods=int(externForcingCycle/externForcingPeriod+0.5)
102     Imytm=int(myTime*rdt+0.5)
103     Ifprd=int(externForcingPeriod*rdt+0.5)
104     Ifcyc=int(externForcingCycle*rdt+0.5)
105     Iftm=mod( Imytm+Ifcyc-Ifprd/2 ,Ifcyc)
106    
107     intime0=int(Iftm/Ifprd)
108     intime1=mod(intime0+1,nForcingPeriods)
109     aWght=float( Iftm-Ifprd*intime0 )/float( Ifprd )
110     bWght=1.-aWght
111    
112     intime0=intime0+1
113     intime1=intime1+1
114    
115     IF (
116     & Iftm-Ifprd*(intime0-1) .EQ. 0
117     & .OR. myIter .EQ. nIter0
118     & ) THEN
119    
120     _BEGIN_MASTER(myThid)
121    
122     C If the above condition is met then we need to read in
123     C data for the period ahead and the period behind myTime.
124     WRITE(msgBuf,'(A,I,I)')
125     & 'S/R EXTERNAL_FIELDS_LOAD: Reading new data',myTime,myIter
126     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
127     & SQUEEZE_RIGHT , 1)
128    
129    
130     IF ( zonalWindFile .NE. ' ' ) THEN
131     CALL READ_REC_XY_RS( zonalWindFile,taux0,intime0,myIter,myThid )
132     CALL READ_REC_XY_RS( zonalWindFile,taux1,intime1,myIter,myThid )
133     ENDIF
134     IF ( meridWindFile .NE. ' ' ) THEN
135     CALL READ_REC_XY_RS( meridWindFile,tauy0,intime0,myIter,myThid )
136     CALL READ_REC_XY_RS( meridWindFile,tauy1,intime1,myIter,myThid )
137     ENDIF
138     IF ( surfQFile .NE. ' ' ) THEN
139     CALL READ_REC_XY_RS( surfQFile,Qnet0,intime0,myIter,myThid )
140     CALL READ_REC_XY_RS( surfQFile,Qnet1,intime1,myIter,myThid )
141     ENDIF
142     IF ( EmPmRfile .NE. ' ' ) THEN
143     Cfixed CALL READ_REC_XY_RS( EmPmRfile,EmPmR0,intime0,myIter,myThid )
144     Cfixed CALL READ_REC_XY_RS( EmPmRfile,EmPmR1,intime1,myIter,myThid )
145     CALL READ_REC_XY_RS( EmPmRfile,EmPmR0,1,myIter,myThid )
146     CALL READ_REC_XY_RS( EmPmRfile,EmPmR1,1,myIter,myThid )
147     ENDIF
148     IF ( thetaClimFile .NE. ' ' ) THEN
149     CALL READ_REC_XY_RS( thetaClimFile,SST0,intime0,myIter,myThid )
150     CALL READ_REC_XY_RS( thetaClimFile,SST1,intime1,myIter,myThid )
151     ENDIF
152     IF ( saltClimFile .NE. ' ' ) THEN
153     CALL READ_REC_XY_RS( saltClimFile,SSS0,intime0,myIter,myThid )
154     CALL READ_REC_XY_RS( saltClimFile,SSS1,intime1,myIter,myThid )
155     ENDIF
156     #ifdef SHORTWAVE_HEATING
157     IF ( surfQswFile .NE. ' ' ) THEN
158     CALL READ_REC_XY_RS( surfQswFile,Qsw0,intime0,myIter,myThid )
159     CALL READ_REC_XY_RS( surfQswFile,Qsw1,intime1,myIter,myThid )
160     ENDIF
161     #endif
162    
163     _END_MASTER(myThid)
164     C
165     _EXCH_XY_R4(SST0 , myThid )
166     _EXCH_XY_R4(SST1 , myThid )
167     _EXCH_XY_R4(SSS0 , myThid )
168     _EXCH_XY_R4(SSS1 , myThid )
169     _EXCH_XY_R4(taux0 , myThid )
170     _EXCH_XY_R4(taux1 , myThid )
171     _EXCH_XY_R4(tauy0 , myThid )
172     _EXCH_XY_R4(tauy1 , myThid )
173     _EXCH_XY_R4(Qnet0, myThid )
174     _EXCH_XY_R4(Qnet1, myThid )
175     _EXCH_XY_R4(EmPmR0, myThid )
176     _EXCH_XY_R4(EmPmR1, myThid )
177     #ifdef SHORTWAVE_HEATING
178     _EXCH_XY_R4(Qsw0, myThid )
179     _EXCH_XY_R4(Qsw1, myThid )
180     #endif
181     C
182     ENDIF
183    
184     C-- Interpolate fu,fv,Qnet,EmPmR,SST,SSS,Qsw
185     DO bj = myByLo(myThid), myByHi(myThid)
186     DO bi = myBxLo(myThid), myBxHi(myThid)
187     DO j=1-Oly,sNy+Oly
188     DO i=1-Olx,sNx+Olx
189     SST(i,j,bi,bj) = bWght*SST0(i,j,bi,bj)
190     & +aWght*SST1(i,j,bi,bj)
191     SSS(i,j,bi,bj) = bWght*SSS0(i,j,bi,bj)
192     & +aWght*SSS1(i,j,bi,bj)
193     fu(i,j,bi,bj) = bWght*taux0(i,j,bi,bj)
194     & +aWght*taux1(i,j,bi,bj)
195     fv(i,j,bi,bj) = bWght*tauy0(i,j,bi,bj)
196     & +aWght*tauy1(i,j,bi,bj)
197     Qnet(i,j,bi,bj) = bWght*Qnet0(i,j,bi,bj)
198     & +aWght*Qnet1(i,j,bi,bj)
199     EmPmR(i,j,bi,bj) = bWght*EmPmR0(i,j,bi,bj)
200     & +aWght*EmPmR1(i,j,bi,bj)
201     #ifdef SHORTWAVE_HEATING
202     Qsw(i,j,bi,bj) = bWght*Qsw0(i,j,bi,bj)
203     & +aWght*Qsw1(i,j,bi,bj)
204     #endif
205     ENDDO
206     ENDDO
207     ENDDO
208     ENDDO
209    
210     C-- Diagnostics
211     IF (myThid.EQ.1 .AND. myTime.LT.62208000.) THEN
212     write(0,'(a,1p7e12.4,2i6,2e12.4)')
213     & 'time,SST,SSS,fu,fv,Q,E-P,i0,i1,a,b = ',
214     & myTime,
215     & SST(1,sNy,1,1),SSS(1,sNy,1,1),
216     & fu(1,sNy,1,1),fv(1,sNy,1,1),
217     & Qnet(1,sNy,1,1),EmPmR(1,sNy,1,1),
218     & intime0,intime1,aWght,bWght
219     write(0,'(a,1p7e12.4)')
220     & 'time,fu0,fu1,fu = ',
221     & myTime,
222     & taux0(1,sNy,1,1),taux1(1,sNy,1,1),fu(1,sNy,1,1),
223     & aWght,bWght
224     ENDIF
225    
226     C endif for periodicForcing
227     ENDIF
228    
229     #ifdef ALLOW_AIM
230     IF ( useAIM ) THEN
231     C Update AIM bottom boundary data
232     CALL AIM_EXTERNAL_FIELDS_LOAD( myTime, myIter, myThid )
233     ENDIF
234     #endif
235    
236     RETURN
237     END
238    
239     SUBROUTINE LEF_ZERO( arr ,myThid )
240     C This routine simply sets the argument array to zero
241     C Used only by EXTERNAL_FIELDS_LOAD
242     IMPLICIT NONE
243     C === Global variables ===
244     #include "SIZE.h"
245     #include "EEPARAMS.h"
246     C === Arguments ===
247     _RS arr (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
248     INTEGER myThid
249     C === Local variables ===
250     INTEGER i,j,bi,bj
251    
252     DO bj = myByLo(myThid), myByHi(myThid)
253     DO bi = myBxLo(myThid), myBxHi(myThid)
254     DO j=1-Oly,sNy+Oly
255     DO i=1-Olx,sNx+Olx
256     arr(i,j,bi,bj)=0.
257     ENDDO
258     ENDDO
259     ENDDO
260     ENDDO
261    
262     RETURN
263     END

  ViewVC Help
Powered by ViewVC 1.1.22