/[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.7 - (hide annotations) (download)
Thu Feb 12 16:11:46 2004 UTC (20 years, 4 months ago) by stephd
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube4, checkpoint52n_post, checkpoint52j_post, checkpoint53d_post, checkpoint54a_pre, checkpoint54a_post, checkpoint53c_post, checkpoint52l_post, checkpoint52k_post, checkpoint54b_post, checkpoint53b_pre, checkpoint52m_post, checkpoint53a_post, checkpoint54, checkpoint53b_post, checkpoint53, checkpoint53g_post, hrcube5, checkpoint52j_pre, checkpoint53f_post, checkpoint53d_pre
Changes since 1.6: +16 -9 lines
o clean up and add extra documentation

1 edhill 1.4 #include "DIC_OPTIONS.h"
2 stephd 1.1 #include "GCHEM_OPTIONS.h"
3    
4 stephd 1.7 CBOP
5     C !ROUTINE: DIC_FIELDS_LOAD
6    
7     C !INTERFACE: ==========================================================
8 stephd 1.1 SUBROUTINE DIC_FIELDS_LOAD (
9     I myIter,myTime,myThid)
10    
11 stephd 1.7 C !DESCRIPTION:
12     C Read in fields needed for CO2,O2 fluxterms, silica for pH calculation
13    
14     C !USES: ===============================================================
15 stephd 1.1 IMPLICIT NONE
16     #include "SIZE.h"
17     #include "DYNVARS.h"
18     #include "EEPARAMS.h"
19     #include "PARAMS.h"
20     #include "GRID.h"
21     #include "PTRACERS.h"
22     #include "GCHEM.h"
23     #include "DIC_ABIOTIC.h"
24     #ifdef DIC_BIOTIC
25     #include "DIC_BIOTIC.h"
26 stephd 1.3 #include "DIC_LOAD.h"
27 stephd 1.1 #endif
28    
29 stephd 1.7 C !INPUT PARAMETERS: ===================================================
30     C myThid :: thread number
31     C myIter :: current timestep
32     C myTime :: current time
33 stephd 1.1 INTEGER myIter
34     _RL myTime
35     INTEGER myThid
36    
37     #ifdef ALLOW_PTRACERS
38 stephd 1.7
39     c !LOCAL VARIABLES: ===================================================
40 stephd 1.1 INTEGER bi,bj,i,j,intime0,intime1
41     _RL aWght,bWght,rdt
42     INTEGER nForcingPeriods,Imytm,Ifprd,Ifcyc,Iftm
43 stephd 1.7 CEOP
44    
45 stephd 1.1 c
46 stephd 1.3 IF ( periodicExternalForcing ) THEN
47 stephd 1.1
48    
49     C Now calculate whether it is time to update the forcing arrays
50     rdt=1. _d 0 / deltaTclock
51     nForcingPeriods=
52     & int(externForcingCycle/externForcingPeriod+0.5)
53     cswd QQ change for placement of chem forcing (ie. after timestep)
54 stephd 1.5 Imytm=int(myTime*rdt+0.5)
55 stephd 1.1 Ifprd=int(externForcingPeriod*rdt+0.5)
56     Ifcyc=int(externForcingCycle*rdt+0.5)
57     Iftm=mod( Imytm+Ifcyc-Ifprd/2 ,Ifcyc)
58    
59    
60     intime0=int(Iftm/Ifprd)
61     intime1=mod(intime0+1,nForcingPeriods)
62     aWght=float( Iftm-Ifprd*intime0 )/float( Ifprd )
63     bWght=1.-aWght
64    
65     intime0=intime0+1
66     intime1=intime1+1
67    
68    
69     IF (
70     & Iftm-Ifprd*(intime0-1).EQ. 0
71 stephd 1.3 & .OR. myIter .EQ. nIter0
72 stephd 1.1 & ) THEN
73    
74    
75     _BEGIN_MASTER(myThid)
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     WRITE(*,*)
80     & 'S/R EXTERNAL_FIELDS_LOAD: Reading new dic data',
81     & myTime,myIter
82    
83     IF ( WindFile .NE. ' ' ) THEN
84     CALL READ_REC_XY_RS( WindFile,wspeed0,intime0,
85     & myIter,myThid )
86     CALL READ_REC_XY_RS( WindFile,wspeed1,intime1,
87     & myIter,myThid )
88     ENDIF
89     IF ( AtmospFile .NE. ' ' ) THEN
90     CALL READ_REC_XY_RS( AtmospFile,atmosp0,intime0,
91     & myIter,myThid )
92     CALL READ_REC_XY_RS( AtmospFile,atmosp1,intime1,
93     & myIter,myThid )
94     ENDIF
95 stephd 1.2 IF ( SilicaFile .NE. ' ' ) THEN
96     CALL READ_REC_XY_RS( SilicaFile,silica0,intime0,
97     & myIter,myThid )
98     CALL READ_REC_XY_RS( SilicaFile,silica1,intime1,
99     & myIter,myThid )
100     ENDIF
101 stephd 1.1 IF ( IceFile .NE. ' ' ) THEN
102     CALL READ_REC_XY_RS( IceFile,ice0,intime0,
103     & myIter,myThid )
104     CALL READ_REC_XY_RS( IceFile,ice1,intime1,
105     & myIter,myThid )
106     ENDIF
107 stephd 1.3 #ifdef ALLOW_FE
108 stephd 1.1 IF ( IronFile .NE. ' ' ) THEN
109     CALL READ_REC_XY_RS( IronFile,feinput0,intime0,
110     & myIter,myThid )
111     CALL READ_REC_XY_RS( IronFile,feinput1,intime1,
112     & myIter,myThid )
113     ENDIF
114     #endif
115    
116    
117     _END_MASTER(myThid)
118     C
119     _EXCH_XY_R4(wspeed0, myThid )
120     _EXCH_XY_R4(wspeed1, myThid )
121     _EXCH_XY_R4(atmosp0, myThid )
122     _EXCH_XY_R4(atmosp1, myThid )
123 stephd 1.2 _EXCH_XY_R4(silica0, myThid )
124     _EXCH_XY_R4(silica1, myThid )
125 stephd 1.1 _EXCH_XY_R4(ice0, myThid )
126     _EXCH_XY_R4(ice1, myThid )
127 stephd 1.3 #ifdef ALLOW_FE
128 stephd 1.1 _EXCH_XY_R4(feinput0, myThid )
129     _EXCH_XY_R4(feinput1, myThid )
130     #endif
131    
132     C
133     ENDIF
134    
135     DO bj = myByLo(myThid), myByHi(myThid)
136     DO bi = myBxLo(myThid), myBxHi(myThid)
137     DO j=1-Oly,sNy+Oly
138     DO i=1-Olx,sNx+Olx
139     IF ( WindFile .NE. ' ' ) THEN
140     WIND(i,j,bi,bj) = bWght*wspeed0(i,j,bi,bj)
141     & +aWght*wspeed1(i,j,bi,bj)
142     ELSE
143     WIND(i,j,bi,bj) = 5.d0*maskC(i,j,1,bi,bj)
144     ENDIF
145     c calculate piston velocity
146     c QQ: note - we should have wind speed variance in here
147     c QQ also need to check units, and conversion factors
148     pisvel(i,j,bi,bj) =0.337*wind(i,j,bi,bj)**2/3.6d5 !QQQQ
149     IF ( AtmospFile .NE. ' ' ) THEN
150     ATMOSP(i,j,bi,bj) = bWght*atmosp0(i,j,bi,bj)
151     & +aWght*atmosp1(i,j,bi,bj)
152     ELSE
153     ATMOSP(i,j,bi,bj) =1.d0*maskC(i,j,1,bi,bj)
154 stephd 1.2 ENDIF
155     IF ( SilicaFile .NE. ' ' ) THEN
156     SILICA(i,j,bi,bj) = bWght*silica0(i,j,bi,bj)
157     & +aWght*silica1(i,j,bi,bj)
158     ELSE
159     SILICA(i,j,bi,bj) =7.6838e-3*maskC(i,j,1,bi,bj)
160 stephd 1.1 ENDIF
161     IF ( IceFile .NE. ' ' ) THEN
162     FIce(i,j,bi,bj) = bWght*ice0(i,j,bi,bj)
163     & +aWght*ice1(i,j,bi,bj)
164     ELSE
165     FIce(i,j,bi,bj) =0.d0
166     ENDIF
167     if (FIce(i,j,bi,bj).lt.1d-2) then
168     FIce(i,j,bi,bj) = 0.d0
169     endif
170 stephd 1.3 #ifdef ALLOW_FE
171 stephd 1.1 IF ( IronFile .NE. ' ' ) THEN
172     InputFe(i,j,bi,bj) = bWght*feinput0(i,j,bi,bj)
173     & +aWght*feinput1(i,j,bi,bj)
174     ELSE
175     InputFe(i,j,bi,bj) = 0.d0*maskC(i,j,1,bi,bj)
176     ENDIF
177     #endif
178     ENDDO
179     ENDDO
180     ENDDO
181     ENDDO
182    
183     C endif for periodicForcing
184     ENDIF
185    
186     #endif
187     RETURN
188     END

  ViewVC Help
Powered by ViewVC 1.1.22