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

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

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


Revision 1.4 - (show annotations) (download)
Tue Aug 21 16:06:21 2007 UTC (17 years, 11 months ago) by jscott
Branch: MAIN
CVS Tags: HEAD
Changes since 1.3: +0 -0 lines
FILE REMOVED
remove old atm2d pkg repository

1 #include "ctrparam.h"
2 #include "ATM2D_OPTIONS.h"
3
4 C !INTERFACE:
5 SUBROUTINE CALC_ZONAL_MEANS(doAll,myThid )
6 C *==========================================================*
7 C | Calculate zonal mean ocean quantities (at a specific |
8 C | point in time). If first argument is false, only seaice |
9 C | means are calculated, i.e. called after an atm timestep. |
10 C *==========================================================*
11 IMPLICIT NONE
12
13 C === Global Atmosphere Variables ===
14 #include "ATMSIZE.h"
15 #include "AGRID.h"
16
17 C === Global Ocean Variables ===
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 doAll - boolean, false -> only vars changed after atm step
31 C myThid - Thread no. that called this routine.
32 LOGICAL doAll
33 INTEGER myThid
34
35 C LOCAL VARIABLES:
36 _RL mWgt ! weight of ocean point j+1
37 INTEGER i,j ! loop counters for the ocean grid
38 INTEGER j_atm ! loop counter for the atm grid
39
40 DO j_atm=1,jm0
41 IF (doAll) THEN
42 ctocn(j_atm)=0. _d 0
43 cfice(j_atm)=0. _d 0
44 cco2flux(j_atm)=0. _d 0
45 ENDIF
46 ctice(j_atm)=0. _d 0
47 csAlb(j_atm)=0. _d 0
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 IF (doAll) THEN
56 ctocn(atm_oc_ind(j))= ctocn(atm_oc_ind(j)) +
57 & sstFromOcn(i,j) * rA(i,j,1,1) *
58 & (1. _d 0-iceMask(i,j,1,1))*atm_oc_wgt(j)
59 cfice(atm_oc_ind(j))=cfice(atm_oc_ind(j)) +
60 & rA(i,j,1,1)*iceMask(i,j,1,1)*atm_oc_wgt(j)
61 cco2flux(atm_oc_ind(j))=cco2flux(atm_oc_ind(j)) +
62 & fluxCO2(i,j)*rA(i,j,1,1)*atm_oc_wgt(j)
63 ENDIF
64 ctice(atm_oc_ind(j))=ctice(atm_oc_ind(j)) + Tsrf(i,j,1,1)
65 & *rA(i,j,1,1)*iceMask(i,j,1,1)*atm_oc_wgt(j)
66 csAlb(atm_oc_ind(j))=csAlb(atm_oc_ind(j)) + siceAlb(i,j,1,1)
67 & *rA(i,j,1,1)*iceMask(i,j,1,1)*atm_oc_wgt(j)
68
69 IF (atm_oc_wgt(j).LT.1. _d 0) THEN
70 mWgt= 1. _d 0-atm_oc_wgt(j)
71 IF (doAll) THEN
72 ctocn(atm_oc_ind(j)+1)= ctocn(atm_oc_ind(j)+1) +
73 & sstFromOcn(i,j) * rA(i,j,1,1) *
74 & (1. _d 0-iceMask(i,j,1,1))*mWgt
75 cfice(atm_oc_ind(j)+1)= cfice(atm_oc_ind(j)+1) +
76 & rA(i,j,1,1)*iceMask(i,j,1,1)*mWgt
77 cco2flux(atm_oc_ind(j)+1)= cco2flux(atm_oc_ind(j)+1) +
78 & fluxCO2(i,j)*rA(i,j,1,1)*mWgt
79 ENDIF
80 ctice(atm_oc_ind(j)+1)= ctice(atm_oc_ind(j)+1) +
81 & Tsrf(i,j,1,1)*rA(i,j,1,1)*iceMask(i,j,1,1)*mWgt
82 csAlb(atm_oc_ind(j)+1)= csAlb(atm_oc_ind(j)+1) +
83 & siceAlb(i,j,1,1)*rA(i,j,1,1)*iceMask(i,j,1,1)*mWgt
84 ENDIF
85
86 ENDIF
87
88 ENDDO
89 ENDDO
90
91 DO j_atm=2,jm0-1
92
93 IF (ocnArea(j_atm).GT.1. _d -32) THEN
94
95 IF (doAll)THEN
96 cfice(j_atm)= cfice(j_atm)/ocnArea(j_atm)
97 cco2flux(j_atm)= cco2flux(j_atm)/ocnArea(j_atm)
98 ENDIF
99 IF (cfice(j_atm).GT.1. _d -32) THEN
100 ctice(j_atm)= ctice(j_atm)/ocnArea(j_atm)/cfice(j_atm)
101 csAlb(j_atm)= csAlb(j_atm)/ocnArea(j_atm)/cfice(j_atm)
102 ENDIF
103
104 IF ((1. _d 0-cfice(j_atm).GT.1. _d -32).AND.doAll)
105 & ctocn(j_atm)= ctocn(j_atm)/ocnArea(j_atm)
106 & /(1. _d 0-cfice(j_atm))
107
108 ENDIF
109
110 C At present, keeping separate variables in AGRID.h and ATM2D_VARS.h
111
112 IF (doALL) THEN
113 mmsst(j_atm)= ctocn(j_atm)
114 mmfice(j_atm)= cfice(j_atm)
115 mmco2flux(j_atm)= cco2flux(j_atm)
116 ENDIF
117 mmtice(j_atm)= ctice(j_atm)
118 mmsAlb(j_atm)= csAlb(j_atm)
119
120 ENDDO
121
122 C Copy data to atmosphere polar points
123 IF (doALL) THEN
124 mmsst(1)= ctocn(2)
125 mmsst(jm0)= ctocn(jm0-1)
126 mmfice(1)= cfice(2)
127 mmfice(jm0)= cfice(jm0-1)
128 mmco2flux(1)= cco2flux(2)
129 mmco2flux(jm0)= cco2flux(jm0-1)
130 ENDIF
131 mmtice(1)= ctice(2)
132 mmtice(jm0)= ctice(jm0-1)
133 mmsAlb(1)= csAlb(2)
134 mmsAlb(jm0)= csAlb(jm0-1)
135
136 RETURN
137 END

  ViewVC Help
Powered by ViewVC 1.1.22