/[MITgcm]/MITgcm/pkg/dic/dic_fields_load.F
ViewVC logotype

Contents of /MITgcm/pkg/dic/dic_fields_load.F

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


Revision 1.27 - (show annotations) (download)
Thu Apr 24 21:35:53 2008 UTC (16 years, 2 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59r, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.26: +5 -5 lines
pkg/dic avoiding recomputations, avoiding conflict with exf (wspeed0,1 were defined twice)

1 C $Header: /u/gcmpack/MITgcm/pkg/dic/dic_fields_load.F,v 1.26 2008/04/09 22:13:15 jmc Exp $
2 C $Name: $
3
4 #include "DIC_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: DIC_FIELDS_LOAD
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE DIC_FIELDS_LOAD (
11 I myIter,myTime,myThid)
12
13 C !DESCRIPTION:
14 C Read in fields needed for CO2,O2 fluxterms, silica for pH calculation
15
16 C !USES: ===============================================================
17 IMPLICIT NONE
18 #include "SIZE.h"
19 #include "EEPARAMS.h"
20 #include "PARAMS.h"
21 #include "GRID.h"
22 #include "DIC_VARS.h"
23 #include "DIC_LOAD.h"
24 #ifdef ALLOW_THSICE
25 #include "THSICE_VARS.h"
26 #endif
27 #ifdef ALLOW_SEAICE
28 #include "SEAICE.h"
29 #endif
30
31 C !INPUT PARAMETERS: ===================================================
32 C myThid :: thread number
33 C myIter :: current timestep
34 C myTime :: current time
35 INTEGER myIter
36 _RL myTime
37 INTEGER myThid
38
39 #ifdef ALLOW_PTRACERS
40
41 c !LOCAL VARIABLES: ===================================================
42 INTEGER bi,bj,i,j,intime0,intime1
43 _RL aWght,bWght,rdt
44 INTEGER nForcingPeriods,Imytm,Ifprd,Ifcyc,Iftm
45 CHARACTER*(MAX_LEN_MBUF) msgBuf
46 CEOP
47
48 c
49 IF ( DIC_forcingCycle.gt.0. _d 0 ) THEN
50
51
52 C Now calculate whether it is time to update the forcing arrays
53 rdt = 1. _d 0 / deltaTclock
54 nForcingPeriods = NINT(DIC_forcingCycle/DIC_forcingPeriod)
55 cswd QQ change for placement of chem forcing (ie. after timestep)
56 Imytm = NINT(myTime*rdt)
57 Ifprd = NINT(DIC_forcingPeriod*rdt)
58 Ifcyc = NINT(DIC_forcingCycle*rdt)
59 Iftm = MOD( Imytm+Ifcyc-Ifprd/2, Ifcyc)
60
61 intime0 = 1 + INT(Iftm/Ifprd)
62 intime1 = 1 + MOD(intime0,nForcingPeriods)
63 c aWght = DFLOAT( Iftm-Ifprd*(intime0 - 1) ) / DFLOAT( Ifprd )
64 aWght = FLOAT( Iftm-Ifprd*(intime0 - 1) )
65 bWght = FLOAT( Ifprd )
66 aWght = aWght / bWght
67 bWght = 1. _d 0 - aWght
68
69 IF (
70 & Iftm-Ifprd*(intime0-1).EQ. 0
71 & .OR. myIter .EQ. nIter0
72 & ) THEN
73 C- this is time to load new fields
74
75 _BARRIER
76
77 C If the above condition is met then we need to read in
78 C data for the period ahead and the period behind myTime.
79 _BEGIN_MASTER(myThid)
80 WRITE(standardMessageUnit,'(A,2I5,I10,1P1E20.12)')
81 & 'S/R DIC_FIELDS_LOAD: Reading new dic data:',
82 & intime0, intime1, myIter, myTime
83 _END_MASTER(myThid)
84
85
86 IF ( DIC_windFile .NE. ' ' ) THEN
87 CALL READ_REC_XY_RS( DIC_windFile,dicwind0,intime0,
88 & myIter,myThid )
89 CALL READ_REC_XY_RS( DIC_windFile,dicwind1,intime1,
90 & myIter,myThid )
91 ENDIF
92 IF ( DIC_atmospFile .NE. ' ' ) THEN
93 CALL READ_REC_XY_RS( DIC_atmospFile,atmosp0,intime0,
94 & myIter,myThid )
95 CALL READ_REC_XY_RS( DIC_atmospFile,atmosp1,intime1,
96 & myIter,myThid )
97 ENDIF
98 IF ( DIC_silicaFile .NE. ' ' ) THEN
99 CALL READ_REC_XY_RS( DIC_silicaFile,silica0,intime0,
100 & myIter,myThid )
101 CALL READ_REC_XY_RS( DIC_silicaFile,silica1,intime1,
102 & myIter,myThid )
103 ENDIF
104 IF ( DIC_iceFile .NE. ' ' ) THEN
105 CALL READ_REC_XY_RS( DIC_iceFile,ice0,intime0,
106 & myIter,myThid )
107 CALL READ_REC_XY_RS( DIC_iceFile,ice1,intime1,
108 & myIter,myThid )
109 ENDIF
110 #ifdef READ_PAR
111 IF ( Filename1 .NE. ' ' ) THEN
112 CALL READ_REC_XY_RS( Filename1,par0,intime0,
113 & myIter,myThid )
114 CALL READ_REC_XY_RS( Filename1,par1,intime1,
115 & myIter,myThid )
116 ENDIF
117 #endif
118 #ifdef ALLOW_FE
119 IF ( DIC_ironFile .NE. ' ' ) THEN
120 CALL READ_REC_XY_RS( DIC_ironFile,feinput0,intime0,
121 & myIter,myThid )
122 CALL READ_REC_XY_RS( DIC_ironFile,feinput1,intime1,
123 & myIter,myThid )
124 ENDIF
125 #endif
126 _BARRIER
127
128 C- end if-bloc (time to load new fields)
129 ENDIF
130
131 DO bj = myByLo(myThid), myByHi(myThid)
132 DO bi = myBxLo(myThid), myBxHi(myThid)
133 IF ( DIC_windFile .NE. ' ' ) THEN
134 DO j=1-Oly,sNy+Oly
135 DO i=1-Olx,sNx+Olx
136 WIND(i,j,bi,bj) = bWght*dicwind0(i,j,bi,bj)
137 & + aWght*dicwind1(i,j,bi,bj)
138 ENDDO
139 ENDDO
140 C calculate piston velocity
141 C QQ: note - we should have wind speed variance in here
142 C QQ also need to check units, and conversion factors
143 c pisvel(i,j,bi,bj) =0.337*wind(i,j,bi,bj)**2/3.6d5 !QQQQ
144 ENDIF
145 #ifndef USE_PLOAD
146 IF ( DIC_atmospFile .NE. ' ' ) THEN
147 DO j=1-Oly,sNy+Oly
148 DO i=1-Olx,sNx+Olx
149 AtmosP(i,j,bi,bj) = bWght*atmosp0(i,j,bi,bj)
150 & + aWght*atmosp1(i,j,bi,bj)
151 ENDDO
152 ENDDO
153 ENDIF
154 #endif
155 IF ( DIC_silicaFile .NE. ' ' ) THEN
156 DO j=1-Oly,sNy+Oly
157 DO i=1-Olx,sNx+Olx
158 SILICA(i,j,bi,bj) = bWght*silica0(i,j,bi,bj)
159 & + aWght*silica1(i,j,bi,bj)
160 ENDDO
161 ENDDO
162 ENDIF
163 IF ( DIC_iceFile .NE. ' ' ) THEN
164 DO j=1-Oly,sNy+Oly
165 DO i=1-Olx,sNx+Olx
166 FIce(i,j,bi,bj) = bWght*ice0(i,j,bi,bj)
167 & + aWght*ice1(i,j,bi,bj)
168 ENDDO
169 ENDDO
170 ENDIF
171
172 #ifdef READ_PAR
173 IF ( Filename1 .NE. ' ' ) THEN
174 DO j=1-Oly,sNy+Oly
175 DO i=1-Olx,sNx+Olx
176 PAR(i,j,bi,bj) = bWght*par0(i,j,bi,bj)
177 & + aWght*par1(i,j,bi,bj)
178 ENDDO
179 ENDDO
180 ELSE
181 WRITE(msgBuf,'(2A)')
182 & ' DIC_FIELDS_LOAD: You need to provide ',
183 & ' a file if you want to use READ_PAR'
184 CALL PRINT_ERROR( msgBuf, myThid )
185 STOP 'ABNORMAL END: S/R DIC_FIELDS_LOAD'
186 ENDIF
187 #endif
188 #ifdef ALLOW_FE
189 IF ( DIC_ironFile .NE. ' ' ) THEN
190 DO j=1-Oly,sNy+Oly
191 DO i=1-Olx,sNx+Olx
192 InputFe(i,j,bi,bj) = bWght*feinput0(i,j,bi,bj)
193 & + aWght*feinput1(i,j,bi,bj)
194 ENDDO
195 ENDDO
196 ENDIF
197 #endif
198 ENDDO
199 ENDDO
200
201 C endif for DIC_forcingCycle
202 ENDIF
203
204 DO bj = myByLo(myThid), myByHi(myThid)
205 DO bi = myBxLo(myThid), myBxHi(myThid)
206 #ifdef ALLOW_SEAICE
207 IF ( useSEAICE ) THEN
208 DO j=1-Oly,sNy+Oly
209 DO i=1-Olx,sNx+Olx
210 FIce(i,j,bi,bj) = AREA(i,j,1,bi,bj)
211 ENDDO
212 ENDDO
213 ENDIF
214 #endif
215 #ifdef ALLOW_THSICE
216 IF ( useThSIce ) THEN
217 DO j=1-Oly,sNy+Oly
218 DO i=1-Olx,sNx+Olx
219 FIce(i,j,bi,bj) = iceMask(i,j,bi,bj)
220 ENDDO
221 ENDDO
222 ENDIF
223 #endif
224 ENDDO
225 ENDDO
226
227 #endif /* ALLOW_PTRACERS */
228 RETURN
229 END

  ViewVC Help
Powered by ViewVC 1.1.22