/[MITgcm]/MITgcm/pkg/ebm/ebm_area_t.F
ViewVC logotype

Contents of /MITgcm/pkg/ebm/ebm_area_t.F

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


Revision 1.4 - (show annotations) (download)
Tue Apr 28 18:42:56 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63a, checkpoint63b, checkpoint62, checkpoint63, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61n, checkpoint61o, checkpoint61m, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.3: +9 -9 lines
change macros (EXCH & GLOBAL_SUM/MAX) sufix _R4/_R8 to _RS/_RL
 when applied to _RS/_RL variable
BUG to fix: global_sum of var in common block (EBM.h) is wrong (multi-threaded)

1 C $Header: /u/gcmpack/MITgcm/pkg/ebm/ebm_area_t.F,v 1.3 2004/05/21 21:45:35 heimbach Exp $
2 C $Name: $
3
4 #include "EBM_OPTIONS.h"
5
6 SUBROUTINE EBM_AREA_T( myTime, myIter, myThid )
7 C |==========================================================|
8 C | S/R CALCULATE ZONAL MEAN TEMPERATURE |
9 C |==========================================================|
10
11 IMPLICIT NONE
12
13 C === Global variables ===
14 #include "SIZE.h"
15 #include "EEPARAMS.h"
16 #include "PARAMS.h"
17 #include "FFIELDS.h"
18 #include "DYNVARS.h"
19 #include "GRID.h"
20 #ifdef ALLOW_EBM
21 # include "EBM.h"
22 #endif
23 #ifdef ALLOW_AUTODIFF_TAMC
24 # include "tamc.h"
25 # include "tamc_keys.h"
26 #endif
27
28 C === Routine arguments ===
29 C myThid - Instance number for this innvocation
30 INTEGER myThid
31 INTEGER myIter
32 _RL myTime
33
34 CEndOfInterface
35 C == Local variables ==
36 C I, J, K - Loop counters
37
38 #ifdef ALLOW_EBM
39
40 INTEGER iMin, iMax, jMin, jMax
41 INTEGER i, j, k, bi, bj
42 _RL TmlS_tile(nSx, nSy)
43 _RL TmlN_tile(nSx, nSy)
44 _RL TtS_tile(nSx, nSy)
45 _RL TtN_tile(nSx, nSy)
46 _RL CountmlS_tile(nSx, nSy)
47 _RL CountmlN_tile(nSx, nSy)
48 _RL CounttS_tile(nSx, nSy)
49 _RL CounttN_tile(nSx, nSy)
50 _RL CountmlS
51 _RL CountmlN
52 _RL CounttS
53 _RL CounttN
54
55 C-- Top layer only
56 k = 1
57
58 TmlS = 0.0
59 CountmlS = 0.0
60 TmlN = 0.0
61 CountmlN = 0.0
62 TtS = 0.0
63 CounttS = 0.0
64 TtN = 0.0
65 CounttN = 0.0
66
67 DO bj=myByLo(myThid),myByHi(myThid)
68 DO bi=myBxLo(myThid),myBxHi(myThid)
69
70 TmlS_tile(bi,bj) = 0.
71 TmlN_tile(bi,bj) = 0.
72 TtS_tile(bi,bj) = 0.
73 TtN_tile(bi,bj) = 0.
74 CountmlS_tile(bi,bj) = 0.
75 CountmlN_tile(bi,bj) = 0.
76 CounttS_tile(bi,bj) = 0.
77 CounttN_tile(bi,bj) = 0.
78
79 C-- Calculate sum of temperatures over each tile
80 DO j = 1,sNy
81 DO i = 1, sNx
82 IF ( yC(i,j,bi,bj) .GE. -lat(3) .AND.
83 & yC(i,j,bi,bj) .LE. -lat(2)) THEN
84 TmlS_tile(bi,bj) = TmlS_tile(bi,bj) +
85 & theta(i,j,k,bi,bj)
86 CountmlS_tile(bi,bj) = CountmlS_tile(bi,bj) +
87 & maskC(i,j,k,bi,bj)
88 ELSEIF ( yC(i,j,bi,bj) .GT. -lat(2) .AND.
89 & yC(i,j,bi,bj) .LT. -lat(1)) THEN
90 TtS_tile(bi,bj) = TtS_tile(bi,bj) +
91 & theta(i,j,k,bi,bj)
92 CounttS_tile(bi,bj) = CounttS_tile(bi,bj) +
93 & maskC(i,j,k,bi,bj)
94 ELSEIF ( yC(i,j,bi,bj) .GT. lat(1) .AND.
95 & yC(i,j,bi,bj) .LT. lat(2)) THEN
96 TtN_tile(bi,bj) = TtN_tile(bi,bj) +
97 & theta(i,j,k,bi,bj)
98 CounttN_tile(bi,bj) = CounttN_tile(bi,bj) +
99 & maskC(i,j,k,bi,bj)
100 ELSEIF ( yC(i,j,bi,bj) .GE. lat(2) .AND.
101 & yC(i,j,bi,bj) .LT. lat(3)) THEN
102 TmlN_tile(bi,bj) = TmlN_tile(bi,bj) +
103 & theta(i,j,k,bi,bj)
104 CountmlN_tile(bi,bj) = CountmlN_tile(bi,bj) +
105 & maskC(i,j,k,bi,bj)
106 ENDIF
107
108 ENDDO
109 ENDDO
110
111 C-- Sum over the tiles
112 TmlS = TmlS + TmlS_tile(bi,bj)
113 CountmlS = CountmlS + CountmlS_tile(bi,bj)
114 TmlN = TmlN + TmlN_tile(bi,bj)
115 CountmlN = CountmlN + CountmlN_tile(bi,bj)
116 TtS = TtS + TtS_tile(bi,bj)
117 CounttS = CounttS + CounttS_tile(bi,bj)
118 TtN = TtN + TtN_tile(bi,bj)
119 CounttN = CounttN + CounttN_tile(bi,bj)
120
121 ENDDO
122 ENDDO
123
124 _GLOBAL_SUM_RL( TmlS, myThid )
125 _GLOBAL_SUM_RL( TmlN, myThid )
126 _GLOBAL_SUM_RL( TtS, myThid )
127 _GLOBAL_SUM_RL( TtN, myThid )
128 c
129 _GLOBAL_SUM_RL( CountmlS, myThid )
130 _GLOBAL_SUM_RL( CountmlN, myThid )
131 _GLOBAL_SUM_RL( CounttS, myThid )
132 _GLOBAL_SUM_RL( CounttN, myThid )
133
134 #ifdef ALLOW_AUTODIFF_TAMC
135 CADJ STORE CountmlS = comlev1, key = ikey_dynamics
136 CADJ STORE CountmlN = comlev1, key = ikey_dynamics
137 CADJ STORE CounttS = comlev1, key = ikey_dynamics
138 CADJ STORE CounttN = comlev1, key = ikey_dynamics
139 #endif
140 if ( CountmlS .NE. 0.) TmlS = TmlS/CountmlS + t_mlt
141 if ( CountmlN .NE. 0.) TmlN = TmlN/CountmlN + t_mlt
142 if ( CounttS .NE. 0.) TtS = TtS/CounttS + t_mlt
143 if ( CounttN .NE. 0.) TtN = TtN/CounttN + t_mlt
144
145 #endif /* ALLOW_EBM */
146
147 RETURN
148 END
149
150
151

  ViewVC Help
Powered by ViewVC 1.1.22