/[MITgcm]/MITgcm/pkg/atm2d/calc_1dto2d.F
ViewVC logotype

Contents of /MITgcm/pkg/atm2d/calc_1dto2d.F

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


Revision 1.3 - (show annotations) (download)
Mon Oct 8 23:48:28 2007 UTC (16 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59i, checkpoint59j
Changes since 1.2: +10 -7 lines
add missing cvs $Header:$ or $Name:$

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

  ViewVC Help
Powered by ViewVC 1.1.22