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

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

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


Revision 1.1 - (hide annotations) (download)
Fri Nov 22 02:33:24 2002 UTC (21 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint47e_post, checkpoint47c_post, checkpoint48c_pre, checkpoint47d_pre, checkpoint47a_post, checkpoint47i_post, checkpoint47d_post, checkpoint47g_post, checkpoint48a_post, checkpoint47j_post, branch-exfmods-tag, checkpoint48c_post, checkpoint47b_post, checkpoint47f_post, checkpoint48, checkpoint47h_post
Branch point for: branch-exfmods-curt
print out the global average of the surface correction terms

1 jmc 1.1 C $Header: $
2     C $Name: $
3    
4     #include "CPP_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 correction term
11     C |==========================================================
12     C | Diagnose mean surface correction term = w_surf * Tracer
13     C | units = W_units * Tracer units ; + = out
14     C | Atmosphere :
15     C | convert surf.cor(Theta) to surface heating,
16     C | units= W/m2, + = out
17     C | compute mean conversion term Temp -> PE , units= W/m2,
18     C | + = decreasing heat content, increasing PE
19     C |==========================================================
20     IMPLICIT NONE
21    
22     C === Global data ===
23     #include "SIZE.h"
24     #include "EEPARAMS.h"
25     #include "PARAMS.h"
26     #include "DYNVARS.h"
27     #include "SURFACE.h"
28     #include "GRID.h"
29     #include "MONITOR.h"
30    
31     C === Routine arguments ===
32     INTEGER myThid
33    
34     C === Local variables ====
35     INTEGER i,j,k,ks,bi,bj
36     _RL theArea, wT_Mean, wS_Mean, tmp_wS_M
37     _RL tmpVal, ddPI, wT_Heat, theta2PE
38    
39     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
40     c-- Compute surface correction term & do the integral
41     theArea = 0.
42     wT_Mean = 0.
43     wS_Mean = 0.
44     wT_Heat = 0.
45     theta2PE = 0.
46     DO bj=myByLo(myThid),myByHi(myThid)
47     DO bi=myBxLo(myThid),myBxHi(myThid)
48     tmp_wS_M = wS_Mean
49     DO j=1,sNy
50     DO i=1,sNx
51     ks = ksurfC(i,j,bi,bj)
52     IF (ks.LE.Nr) THEN
53     theArea = theArea + rA(i,j,bi,bj)
54     tmpVal =
55     & rA(i,j,bi,bj)*wVel(i,j,ks,bi,bj)*theta(i,j,ks,bi,bj)
56     wT_Mean = wT_Mean + tmpVal
57     wS_Mean = wS_Mean
58     & + rA(i,j,bi,bj)*wVel(i,j,ks,bi,bj)* salt(i,j,ks,bi,bj)
59     C-- Atmos in Pot.Temp => convert Omega*Theta to heat flux :
60     IF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
61     wT_Heat = wT_Heat
62     & + tmpVal*atm_cp*((rC(ks)/atm_po)**atm_kappa)
63     ENDIF
64     ENDIF
65     ENDDO
66     ENDDO
67     C-- Atmos in Pot.Temp => conmpute energy conversion Temp -> PE
68     C = Omega*Theta*DeltaPI
69     IF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
70     DO k=2,Nr
71     ddPI=atm_cp*( (rC(K-1)/atm_po)**atm_kappa
72     & -(rC( K )/atm_po)**atm_kappa )
73     DO j=1,sNy
74     DO i=1,sNx
75     theta2PE = theta2PE
76     & - ddPI*rA(i,j,bi,bj)*wVel(i,j,k,bi,bj)
77     & *(theta(i,j,k,bi,bj)+theta(i,j,k-1,bi,bj))*0.5 _d 0
78     & *maskC(i,j,k-1,bi,bj)*maskC(i,j,k,bi,bj)
79     ENDDO
80     ENDDO
81     ENDDO
82     ENDIF
83     #ifdef ALLOW_AIM
84     IF ( useAIM ) THEN
85     DO j=1,sNy
86     DO i=1,sNx
87     ks = ksurfC(i,j,bi,bj)
88     IF (ks.LE.Nr) THEN
89     tmpVal = salt(i,j,ks,bi,bj)
90     & + salt(i,j,Nr,bi,bj)*drF(Nr)*recip_drF(ks)
91     & *hFacC(i,j,Nr,bi,bj)*recip_hFacC(i,j,ks,bi,bj)
92     tmp_wS_M = tmp_wS_M
93     & + rA(i,j,bi,bj)*wVel(i,j,ks,bi,bj)*tmpVal
94     ENDIF
95     ENDDO
96     ENDDO
97     wS_Mean = tmp_wS_M
98     ENDIF
99     #endif /* ALLOW_AIM */
100     ENDDO
101     ENDDO
102    
103     _GLOBAL_SUM_R8(theArea,myThid)
104     _GLOBAL_SUM_R8(wT_Mean,myThid)
105     _GLOBAL_SUM_R8(wS_Mean,myThid)
106     IF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
107     _GLOBAL_SUM_R8(wT_Heat,myThid)
108     _GLOBAL_SUM_R8(theta2PE,myThid)
109     ENDIF
110     IF (theArea.GT.0.) THEN
111     wT_Mean = wT_Mean / theArea
112     wS_Mean = wS_Mean / theArea
113     wT_Heat = wT_Heat / theArea
114     theta2PE = theta2PE / theArea
115     wT_Heat = wT_Heat * rhoConst*recip_horiVertRatio
116     theta2PE = theta2PE * rhoConst*recip_horiVertRatio
117     ENDIF
118    
119     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
120     C Print the Average value (monitor type output)
121    
122     CALL MON_SET_PREF('surf_Corr',myThid)
123     CALL MON_OUT_RL( '_theta', wT_Mean, mon_foot_mean ,myThid)
124     CALL MON_OUT_RL( '_salt' , wS_Mean, mon_foot_mean ,myThid)
125     IF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
126     CALL MON_OUT_RL( '_Heat' , wT_Heat, mon_foot_mean ,myThid)
127     CALL MON_SET_PREF('En_Budget',myThid)
128     CALL MON_OUT_RL('_T2PE',theta2PE, mon_foot_mean ,myThid)
129     ENDIF
130    
131     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
132    
133     RETURN
134     END

  ViewVC Help
Powered by ViewVC 1.1.22