/[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.4 - (show annotations) (download)
Wed Dec 24 00:29:17 2003 UTC (20 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube4, hrcube5, checkpoint52j_pre, checkpoint52k_post, checkpoint52f_post, checkpoint52i_pre, hrcube_1, hrcube_2, hrcube_3, checkpoint52e_pre, checkpoint52e_post, checkpoint52f_pre, checkpoint52i_post, checkpoint52h_pre, checkpoint52j_post, checkpoint52l_post
Changes since 1.3: +2 -3 lines
litle cleaning

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

  ViewVC Help
Powered by ViewVC 1.1.22