/[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.8 - (show annotations) (download)
Tue Jul 13 18:03:31 2004 UTC (19 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint57o_post, checkpoint57m_post, checkpoint55c_post, checkpoint54e_post, checkpoint57s_post, checkpoint57k_post, checkpoint55d_pre, checkpoint57d_post, checkpoint57g_post, checkpoint57b_post, checkpoint57c_pre, checkpoint55j_post, checkpoint56b_post, checkpoint57i_post, checkpoint57e_post, checkpoint55h_post, checkpoint57g_pre, checkpoint55b_post, checkpoint54d_post, checkpoint56c_post, checkpoint55, checkpoint57f_pre, checkpoint57a_post, checkpoint54f_post, checkpoint55g_post, checkpoint55f_post, checkpoint57r_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, eckpoint57e_pre, checkpoint57h_done, checkpoint57n_post, checkpoint57p_post, checkpint57u_post, checkpoint57f_post, checkpoint57q_post, checkpoint57c_post, checkpoint55e_post, checkpoint55a_post, checkpoint54c_post, checkpoint57j_post, checkpoint57h_pre, checkpoint57l_post, checkpoint57h_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.7: +4 -0 lines
max number of passive tracers is now defined in PTRACERS_SIZE.h

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

  ViewVC Help
Powered by ViewVC 1.1.22