/[MITgcm]/MITgcm_contrib/jscott/pkg_atm2d/calc_1dto2d.F
ViewVC logotype

Contents of /MITgcm_contrib/jscott/pkg_atm2d/calc_1dto2d.F

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


Revision 1.2 - (show annotations) (download)
Tue Aug 22 20:21:38 2006 UTC (19 years, 4 months ago) by jscott
Branch: MAIN
Changes since 1.1: +36 -34 lines
new revision of atm2d package

1 #include "ctrparam.h"
2 #include "ATM2D_OPTIONS.h"
3
4 C !INTERFACE:
5 SUBROUTINE CALC_1DTO2D( inMonth, myThid )
6 C *==========================================================*
7 C | - Takes 1D atmos data, regrid to 2D ocean grid |
8 c | |
9 C *==========================================================*
10 IMPLICIT NONE
11
12 #include "ATMSIZE.h"
13 #include "SIZE.h"
14 #include "GRID.h"
15 #include "EEPARAMS.h"
16
17 C === Global SeaIce Variables ===
18 #include "THSICE_VARS.h"
19
20 C === Atmos/Ocean/Seaice Interface Variables ===
21 #include "ATM2D_VARS.h"
22
23 C !INPUT/OUTPUT PARAMETERS:
24 C === Routine arguments ===
25 C inMonth - current month (or forcing period)
26 C myThid - Thread no. that called this routine.
27 INTEGER inMonth
28 INTEGER myThid
29
30 C LOCAL VARIABLES:
31 INTEGER i,j
32 INTEGER ib,ibj1,ibj2
33 _RL run_b(sNy)
34
35 CALL INIT_2DFLD(myThid)
36
37 C Accumulate runoff into bands (runoff bands are on the ocean grid)
38 DO ib=1,numBands
39 ibj1=1
40 IF (ib.GT.1) ibj1= rband(ib-1)+1
41 ibj2=sNy
42 IF (ib.LT.numBands) ibj2= rband(ib)
43 run_b(ib)=0. _d 0
44 DO j=ibj1,ibj2
45 run_b(ib)=run_b(ib)+atm_runoff(atm_oc_ind(j))*atm_oc_wgt(j) +
46 & atm_runoff(atm_oc_ind(j)+1)*(1. _d 0-atm_oc_wgt(j))
47 ENDDO
48 ENDDO
49
50 DO j=1,sNy
51 DO i=1,sNx
52
53 IF (maskC(i,j,1,1,1).EQ.1.) THEN
54
55 runoff_2D(i,j) = run_b(runIndex(j)) *
56 & runoffVal(i,j)/rA(i,j,1,1)
57
58 CALL CALC_WGHT2D(i,j,atm_oc_ind(j),atm_oc_wgt(j))
59
60 IF (atm_oc_wgt(j).LT.1. _d 0)
61 & CALL CALC_WGHT2D(i, j, atm_oc_ind(j)+1,
62 & 1. _d 0-atm_oc_wgt(j))
63
64 C Tabulate following diagnostic fluxes from atmos model only
65
66 qnet_atm(i,j)= qnet_atm(i,j) +
67 & qneti_2D(i,j)*dtatmo*iceMask(i,j,1,1) +
68 & qneto_2D(i,j)*dtatmo*(1. _d 0-iceMask(i,j,1,1))
69 evap_atm(i,j)= evap_atm(i,j) +
70 & evapi_2D(i,j)*dtatmo*iceMask(i,j,1,1) +
71 & evapo_2D(i,j)*dtatmo*(1. _d 0-iceMask(i,j,1,1))
72 precip_atm(i,j)= precip_atm(i,j) +
73 & precipi_2D(i,j)*dtatmo*iceMask(i,j,1,1) +
74 & precipo_2D(i,j)*dtatmo*(1. _d 0-iceMask(i,j,1,1))
75 runoff_atm(i,j)= runoff_atm(i,j) +
76 & runoff_2D(i,j)*dtatmo
77 C time_cum = time_cum + dtatmo
78 ENDIF
79
80 ENDDO
81 ENDDO
82
83 C PRINT *,'*** bottom calc_1to2d; evapo_2D',evapo_2D(JBUGI,JBUGJ)
84 C PRINT *,'*** bottom calc_1to2d; precipo_2D',precipo_2D(JBUGI,JBUGJ)
85 C PRINT *,'*** bottom calc_1to2d; runoff_2D',runoff_2D(JBUGI,JBUGJ)
86 C PRINT *,'*** bottom calc_1to2d; qneto_2D',qneto_2D(JBUGI,JBUGJ)
87
88 RETURN
89 END
90
91
92 C--------------------------------------------------------------------------
93
94 #include "ctrparam.h"
95 #include "ATM2D_OPTIONS.h"
96
97 C !INTERFACE:
98 SUBROUTINE CALC_WGHT2D( i, j, ind, wgt)
99 C *==========================================================*
100 C | Use atmos grid cell 1D value and weight to convert to 2D |
101 C | Variations from zonal mean computed used derivative dF/dT|
102 C | and dL/dT for heat flux and evap terms. |
103 C | |
104 C | Fluxes/values over seaice computed only if seaice present|
105 C *==========================================================*
106 IMPLICIT NONE
107
108 #include "ATMSIZE.h"
109 #include "SIZE.h"
110 #include "EEPARAMS.h"
111
112 C === Global SeaIce Variables ===
113 #include "THSICE_VARS.h"
114
115 C === Atmos/Ocean/Seaice Interface Variables ===
116 #include "ATM2D_VARS.h"
117
118 C !INPUT/OUTPUT PARAMETERS:
119 C === Routine arguments ===
120 C index - index into the atmos grid array
121 C wght - weight of this atmos cell for total
122 INTEGER i, j
123 INTEGER ind
124 _RL wgt
125
126 precipo_2D(i,j)= precipo_2D(i,j) + atm_precip(ind)*wgt
127 solarnet_ocn_2D(i,j)=solarnet_ocn_2D(i,j) + atm_solar_ocn(ind)*wgt
128 slp_2D(i,j)= slp_2D(i,j) + atm_slp(ind)*wgt
129 pCO2_2D(i,j)= pCO2_2D(i,j) + atm_pco2(ind)*wgt
130 wspeed_2D(i,j)= wspeed_2D(i,j) + atm_windspeed(ind)*wgt
131 fu_2D(i,j)= fu_2D(i,j) + atm_tauu(ind)*wgt
132 fv_2D(i,j)= fv_2D(i,j) + atm_tauv(ind)*wgt
133
134 qneto_2D(i,j)= qneto_2D(i,j) + atm_qnet_ocn(ind)*wgt
135 evapo_2D(i,j)= evapo_2D(i,j) + atm_evap_ocn(ind)*wgt
136 IF (evapo_2D(i,j).GT.0. _d 0) THEN !convert negative evap. to precip
137 precipo_2D(i,j)= precipo_2D(i,j) - evapo_2D(i,j)
138 evapo_2D(i,j)=0. _d 0
139 ENDIF
140
141 IF (iceMask(i,j,1,1) .GT. 0. _d 0) THEN
142 qneti_2D(i,j)= qneti_2D(i,j) + atm_qnet_ice(ind)*wgt
143 precipi_2D(i,j)= precipi_2D(i,j) + atm_precip(ind)*wgt
144 evapi_2D(i,j)= evapi_2D(i,j) + atm_evap_ice(ind)*wgt
145 IF (evapi_2D(i,j).GT.0. _d 0) THEN !convert negative evap. to precip
146 precipi_2D(i,j)= precipi_2D(i,j) - evapi_2D(i,j)
147 evapi_2D(i,j)=0. _d 0
148 ENDIF
149 dFdT_ice_2D(i,j)= dFdT_ice_2D(i,j) + atm_dFdT_ice(ind)*wgt
150 Tair_2D(i,j)= Tair_2D(i,j) + atm_Tair(ind)*wgt
151 solarinc_2D(i,j)= solarinc_2D(i,j) + atm_solarinc(ind)*wgt
152 ENDIF
153
154 IF (useAltDeriv) THEN
155 qneto_2D(i,j)= qneto_2D(i,j) + atm_dFdt_ocnq(ind)*
156 & (sstFromOcn(i,j)-ctocn(ind)*wgt)
157 evapo_2D(i,j)= evapo_2D(i,j) + atm_dLdt_ocnq(ind)*
158 & (sstFromOcn(i,j)-ctocn(ind)*wgt)
159 IF (iceMask(i,j,1,1) .GT. 0. _d 0) THEN
160 qneti_2D(i,j)=qneti_2D(i,j)+atm_dFdt_iceq(ind)*
161 & (Tsrf(i,j,1,1)-ctice(ind)*wgt)
162 evapi_2D(i,j)=evapi_2D(i,j)+atm_dLdt_iceq(ind)*
163 & (Tsrf(i,j,1,1)-ctice(ind)*wgt)
164 ENDIF
165 ELSE
166 qneto_2D(i,j)= qneto_2D(i,j) + atm_dFdt_ocn(ind)*
167 & (sstFromOcn(i,j)-ctocn(ind)*wgt)
168 evapo_2D(i,j)= evapo_2D(i,j) + atm_dLdt_ocn(ind)*
169 & (sstFromOcn(i,j)-ctocn(ind)*wgt)
170 IF (iceMask(i,j,1,1) .GT. 0. _d 0) THEN
171 qneti_2D(i,j)= qneti_2D(i,j) + atm_dFdt_ice(ind)*
172 & (Tsrf(i,j,1,1)-ctice(ind)*wgt)
173 evapi_2D(i,j)= evapi_2D(i,j)+atm_dLdt_ice(ind)*
174 & (Tsrf(i,j,1,1)-ctice(ind)*wgt)
175 ENDIF
176 ENDIF
177
178
179 RETURN
180 END
181
182 C--------------------------------------------------------------------------
183
184 #include "ctrparam.h"
185 #include "ATM2D_OPTIONS.h"
186
187 C !INTERFACE:
188 SUBROUTINE INIT_2DFLD( myThid)
189 C *==========================================================*
190 C | |
191 c | |
192 C *==========================================================*
193 IMPLICIT NONE
194
195 #include "ATMSIZE.h"
196 #include "SIZE.h"
197 #include "EEPARAMS.h"
198 #include "ATM2D_VARS.h"
199
200 C !INPUT/OUTPUT PARAMETERS:
201 C === Routine arguments ===
202 C myThid - Thread no. that called this routine.
203 INTEGER myThid
204
205 C LOCAL VARIABLES:
206 INTEGER i,j
207
208 DO i=1,sNx
209 DO j=1,sNy
210
211 precipo_2D(i,j)= 0. _d 0
212 precipi_2D(i,j)= 0. _d 0
213 solarnet_ocn_2D(i,j)= 0. _d 0
214 slp_2D(i,j)= 0. _d 0
215 pCO2_2D(i,j)= 0. _d 0
216 wspeed_2D(i,j)= 0. _d 0
217 fu_2D(i,j)= 0. _d 0
218 fv_2D(i,j)= 0. _d 0
219 qneto_2D(i,j)= 0. _d 0
220 evapo_2D(i,j)= 0. _d 0
221 qneti_2D(i,j)= 0. _d 0
222 evapi_2D(i,j)= 0. _d 0
223 dFdT_ice_2D(i,j)= 0. _d 0
224 Tair_2D(i,j)= 0. _d 0
225 solarinc_2D(i,j)= 0. _d 0
226 runoff_2D(i,j)= 0. _d 0
227
228 ENDDO
229 ENDDO
230
231 RETURN
232 END

  ViewVC Help
Powered by ViewVC 1.1.22