/[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.6 - (show annotations) (download)
Thu Dec 4 22:40:37 2003 UTC (20 years, 6 months ago) by stephd
Branch: MAIN
CVS Tags: checkpoint52e_pre, checkpoint52e_post, hrcube_1, checkpoint52d_pre, checkpoint52d_post, checkpoint52f_post, checkpoint52i_post, checkpoint52i_pre, checkpoint52h_pre, checkpoint52f_pre, hrcube_2, hrcube_3
Branch point for: netcdf-sm0
Changes since 1.5: +0 -16 lines
o fixes to make adjoint work

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

  ViewVC Help
Powered by ViewVC 1.1.22