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

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

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


Revision 1.15 - (hide annotations) (download)
Mon Aug 13 02:29:40 2007 UTC (16 years, 10 months ago) by dfer
Branch: MAIN
Changes since 1.14: +2 -2 lines
fix USE_PLOAD (pLoad from atm. model is an anomaly)

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

  ViewVC Help
Powered by ViewVC 1.1.22