/[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.17 - (show annotations) (download)
Mon Nov 5 19:02:08 2007 UTC (16 years, 7 months ago) by jmc
Branch: MAIN
Changes since 1.16: +4 -3 lines
split PTRACERS.h in 2 header files: PTRACERS_FIELDS.h & PTRACERS_PARAMS.h ;
comment out some #include PTRACERS_* that don't seem necessary.

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

  ViewVC Help
Powered by ViewVC 1.1.22