/[MITgcm]/MITgcm/pkg/monitor/mon_surfcor.F
ViewVC logotype

Contents of /MITgcm/pkg/monitor/mon_surfcor.F

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


Revision 1.8 - (show annotations) (download)
Sat Nov 5 01:01:51 2005 UTC (18 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58b_post, checkpoint57y_post, checkpoint58, checkpoint58f_post, checkpoint58d_post, checkpoint58a_post, checkpoint57z_post, checkpoint57y_pre, checkpoint58e_post, checkpoint58g_post, checkpoint57x_post, checkpoint58c_post
Changes since 1.7: +5 -2 lines
remove unused variables (reduces number of compiler warnings)

1 C $Header: /u/gcmpack/MITgcm/pkg/monitor/mon_surfcor.F,v 1.7 2005/06/19 21:35:07 jmc Exp $
2 C $Name: $
3
4 #include "MONITOR_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP
8 C !ROUTINE: MON_SURFCOR
9
10 C !INTERFACE:
11 SUBROUTINE MON_SURFCOR(
12 I myThid )
13
14 C !DESCRIPTION:
15 C Compute and write area-mean surface expansion term (also called
16 C ``surface correction'' with Linear FS).
17 C
18 C Diagnose mean surface expansion term
19 C \begin{equation}
20 C \mbox{with r coordinate} = (\mbox{w surf})(\mbox{Tracer})
21 C \end{equation}
22 C \begin{equation}
23 C \mbox{units} = (\mbox{W units})(\mbox{Tracer units})
24 C \ ; \ \mbox{+ = out}
25 C \end{equation}
26 C \begin{equation}
27 C \mbox{with r* coord}) = \frac{d\eta}{dt} \frac{dz}{H}
28 C (\mbox{Tracer})
29 C \end{equation}
30 C
31 C Atmosphere: convert surf.cor(Theta) to surface heating,
32 C \begin{equation}
33 C \mbox{units} = \frac{W}{m^2}, \mbox{+ = out}
34 C \end{equation}
35 C compute mean conversion term Temp -> PE , units= W/m2,
36 C + = decreasing heat content, increasing PE
37
38 C !USES:
39 IMPLICIT NONE
40 #include "SIZE.h"
41 #include "EEPARAMS.h"
42 #include "PARAMS.h"
43 #include "DYNVARS.h"
44 #include "SURFACE.h"
45 #include "GRID.h"
46 #include "MONITOR.h"
47
48 C !INPUT PARAMETERS:
49 INTEGER myThid
50 CEOP
51
52 C !LOCAL VARIABLES:
53 INTEGER i,j,k,ks,bi,bj
54 _RL theArea, wT_Mean, wS_Mean, wT_Heat
55 _RL vT_Mean, vS_Mean, vT_Heat, theta2PE
56 _RL tmpVal, ddPI
57 _RL areaTile, wT_Tile, wS_Tile, wH_Tile, th2peTile
58 #ifdef NONLIN_FRSURF
59 _RL tmpVol, conv_th2Heat
60 #endif
61
62 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
63 theArea = 0.
64 theta2PE = 0.
65 wT_Mean = 0.
66 wS_Mean = 0.
67 wT_Heat = 0.
68 vT_Mean = 0.
69 vS_Mean = 0.
70 vT_Heat = 0.
71 DO bj=myByLo(myThid),myByHi(myThid)
72 DO bi=myBxLo(myThid),myBxHi(myThid)
73 areaTile = 0.
74 th2peTile = 0.
75 wT_Tile = 0.
76 wS_Tile = 0.
77 wH_Tile = 0.
78 C-- Compute surface "expansion" term & do the integral
79 DO j=1,sNy
80 DO i=1,sNx
81 ks = ksurfC(i,j,bi,bj)
82 IF (ks.LE.Nr) THEN
83 areaTile = areaTile + rA(i,j,bi,bj)
84 tmpVal =
85 & rA(i,j,bi,bj)*wVel(i,j,ks,bi,bj)*theta(i,j,ks,bi,bj)
86 wT_Tile = wT_Tile + tmpVal
87 wS_Tile = wS_Tile
88 & + rA(i,j,bi,bj)*wVel(i,j,ks,bi,bj)* salt(i,j,ks,bi,bj)
89 C- Atmos in Pot.Temp => convert Omega*Theta to heat flux :
90 IF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
91 wH_Tile = wH_Tile
92 & + tmpVal*atm_cp*((rC(ks)/atm_po)**atm_kappa)
93 ENDIF
94 ENDIF
95 ENDDO
96 ENDDO
97 #ifdef ALLOW_AIM
98 IF ( useAIM ) THEN
99 wS_Tile = 0.
100 DO j=1,sNy
101 DO i=1,sNx
102 ks = ksurfC(i,j,bi,bj)
103 IF (ks.LE.Nr) THEN
104 tmpVal = salt(i,j,ks,bi,bj)
105 & + salt(i,j,Nr,bi,bj)*drF(Nr)*recip_drF(ks)
106 & *hFacC(i,j,Nr,bi,bj)*recip_hFacC(i,j,ks,bi,bj)
107 wS_Tile = wS_Tile
108 & + rA(i,j,bi,bj)*wVel(i,j,ks,bi,bj)*tmpVal
109 ENDIF
110 ENDDO
111 ENDDO
112 ENDIF
113 #endif /* ALLOW_AIM */
114
115
116 C-- Atmos in Pot.Temp => conmpute energy conversion Temp -> PE
117 C = Omega*Theta*DeltaPI
118 IF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
119 DO k=2,Nr
120 ddPI=atm_cp*( (rC(K-1)/atm_po)**atm_kappa
121 & -(rC( K )/atm_po)**atm_kappa )
122 DO j=1,sNy
123 DO i=1,sNx
124 th2peTile = th2peTile
125 & - ddPI*rA(i,j,bi,bj)*wVel(i,j,k,bi,bj)
126 & *(theta(i,j,k,bi,bj)+theta(i,j,k-1,bi,bj))*0.5 _d 0
127 & *maskC(i,j,k-1,bi,bj)*maskC(i,j,k,bi,bj)
128 ENDDO
129 ENDDO
130 ENDDO
131 ENDIF
132
133 #ifdef NONLIN_FRSURF
134 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
135 IF (select_rStar.NE.0) THEN
136 C-- Compute Volume expansion term & do the integral
137 vT_Mean = 0.
138 vS_Mean = 0.
139 vT_Heat = 0.
140 conv_th2Heat = 0.
141 DO k=1,Nr
142 IF (fluidIsAir) conv_th2Heat =
143 & atm_cp*((rC(k)/atm_po)**atm_kappa)
144 DO j=1,sNy
145 DO i=1,sNx
146 tmpVol = rA(i,j,bi,bj)*h0FacC(i,j,k,bi,bj)*drF(k)
147 tmpVal = rStarDhCDt(i,j,bi,bj)*theta(i,j,k,bi,bj)
148 vT_Mean = vT_Mean + tmpVol*tmpVal
149 vS_Mean = vS_Mean
150 & +tmpVol*rStarDhCDt(i,j,bi,bj)*salt(i,j,k,bi,bj)
151 C- Atmos in Pot.Temp => convert Omega*Theta to heat flux :
152 IF (fluidIsAir) vT_Heat = vT_Heat
153 & + tmpVol*tmpVal*conv_th2Heat
154 ENDDO
155 ENDDO
156 ENDDO
157 wT_Tile = wT_Tile + vT_Mean
158 wS_Tile = wS_Tile + vS_Mean
159 wH_Tile = wH_Tile + vT_Heat
160 ENDIF
161 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
162 #endif /* NONLIN_FRSURF */
163
164 theArea = theArea + areaTile
165 theta2PE = theta2PE + th2peTile
166 wT_Mean = wT_Mean + wT_Tile
167 wS_Mean = wS_Mean + wS_Tile
168 wT_Heat = wT_Heat + wH_Tile
169 C-- end bi,bj loop
170 ENDDO
171 ENDDO
172
173 _GLOBAL_SUM_R8(theArea,myThid)
174 _GLOBAL_SUM_R8(wT_Mean,myThid)
175 _GLOBAL_SUM_R8(wS_Mean,myThid)
176 IF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
177 _GLOBAL_SUM_R8(wT_Heat,myThid)
178 _GLOBAL_SUM_R8(theta2PE,myThid)
179 ENDIF
180 IF (theArea.GT.0.) THEN
181 wT_Mean = wT_Mean / theArea
182 wS_Mean = wS_Mean / theArea
183 wT_Heat = wT_Heat / theArea
184 theta2PE = theta2PE / theArea
185 wT_Heat = wT_Heat * rhoConst*recip_horiVertRatio
186 theta2PE = theta2PE * rhoConst*recip_horiVertRatio
187 ENDIF
188
189 C- Print the Average value (monitor type output)
190
191 CALL MON_SET_PREF('surfExpan',myThid)
192 CALL MON_OUT_RL( '_theta', wT_Mean, mon_foot_mean ,myThid)
193 CALL MON_OUT_RL( '_salt' , wS_Mean, mon_foot_mean ,myThid)
194 IF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
195 CALL MON_OUT_RL( '_Heat' , wT_Heat, mon_foot_mean ,myThid)
196 CALL MON_SET_PREF('En_Budget',myThid)
197 CALL MON_OUT_RL('_T2PE',theta2PE, mon_foot_mean ,myThid)
198 ENDIF
199
200 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
201
202 RETURN
203 END

  ViewVC Help
Powered by ViewVC 1.1.22