/[MITgcm]/MITgcm/pkg/ecco/cost_trans_zonal.F
ViewVC logotype

Annotation of /MITgcm/pkg/ecco/cost_trans_zonal.F

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


Revision 1.4 - (hide annotations) (download)
Tue Apr 28 18:13:28 2009 UTC (15 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62i, checkpoint62h, checkpoint61n, checkpoint61o, checkpoint61m, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.3: +5 -5 lines
change macros (EXCH & GLOBAL_SUM/MAX) sufix _R4/_R8 to _RS/_RL
 when applied to _RS/_RL variable

1 jmc 1.4 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_trans_zonal.F,v 1.3 2007/10/09 00:02:51 jmc Exp $
2 jmc 1.3 C $Name: $
3 heimbach 1.1
4     #include "COST_CPPOPTIONS.h"
5    
6    
7     subroutine cost_trans_zonal( mythid )
8    
9     c ==================================================================
10     c SUBROUTINE cost_trans_zonal
11     c ==================================================================
12     c
13 jmc 1.3 c o Compute zonal transports.
14 heimbach 1.1 c
15     c ==================================================================
16     c SUBROUTINE cost_trans_zonal
17     c ==================================================================
18    
19     implicit none
20    
21     c == global variables ==
22    
23     #include "EEPARAMS.h"
24     #include "SIZE.h"
25     #include "PARAMS.h"
26     #include "GRID.h"
27     #include "DYNVARS.h"
28    
29     #include "optim.h"
30     #include "cost.h"
31     #include "ecco_cost.h"
32     #include "ctrl_dummy.h"
33    
34     c == routine arguments ==
35    
36     integer mythid
37    
38 heimbach 1.2 #ifdef ALLOW_COST_TRANSPORT
39 heimbach 1.1
40     c == local variables ==
41    
42     integer nsect
43     parameter ( nsect = 5 )
44    
45     integer isect
46     integer kmin(nsect),kmax(nsect)
47     c
48     integer bi,bj
49     integer i,j,k
50     integer itlo,ithi
51     integer jtlo,jthi
52     integer jmin,jmax
53     integer imin,imax
54     integer irec
55     integer il
56     integer funit
57    
58     character*(80) fnameout
59     character*(80) fnametheta
60     character*(80) fnamesalt
61     character*(80) fnameuvel
62     character*(80) fnamevvel
63     character*(MAX_LEN_MBUF) msgbuf
64    
65     _RL p5
66     parameter( p5 = 0.5 )
67    
68     _RL dummy
69     _RL del_x
70     c-- tv: heat transport --- [Watt] (order of 1.E15 = PW)
71     c-- sv: freshwater transport --- [kg/sec] (order 1.E9 equiv. 1 Sv in vol.)
72     c-- convert from [ppt*m^3/sec] via rhoConst/1000.
73     c-- ( 1ppt = 1000*[mass(salt)]/[mass(seawater)] )
74     c-- mv: volume flux --- [m^3/sec] (order of 10^6 = 1 Sv)
75     _RL tu(nsect), su(nsect), mu(nsect)
76     _RL musum(nsect), mumin(nsect), mumax(nsect), mulev(nsect,Nr)
77     _RL xlon(nsect),beglat(nsect),endlat(nsect)
78     c-- 1: A21 - Drake Passage 67W
79     c-- 2: J89 - Indonesian Throughflow 125E
80     c-- 3: I6 - South Africa 30E
81     c-- 4: I9S - Western Australia 115E
82     c-- 5: P12 - Tasmania 145E
83     DATA xlon / 293.0, 125.0, 30.0, 115.0, 145.0 /
84     DATA beglat / -67.0, -14.5, -70.0, -67.0, -67.0 /
85     DATA endlat / -55.0, -8.5, -31.0, -32.0, -42.0 /
86     c
87 jmc 1.3 c _RL ylat2,beglon2,endlon2
88     c _RL ylat3,beglon3,endlon3
89 heimbach 1.1 c parameter(ylat= 29., beglon=-42., endlon =-2.)
90     c parameter(ylat= 29., beglon=282., endlon =352.)
91     c parameter(ylat= 29., beglon=-82., endlon =-2.)
92     cc parameter(ylat= 66.75,beglon=-34.5,endlon =-22.5)
93     cc parameter(ylat2= 63.8,beglon2=-20,endlon2 =-5.)
94     cc parameter(ylat3= 63.8,beglon3=-98.5,endlon3 =-80.0)
95    
96     logical doglobalread
97     logical ladinit
98    
99     c == external functions ==
100    
101     integer ilnblnk
102     external ilnblnk
103    
104     c == end of interface ==
105    
106     doglobalread = .false.
107     ladinit = .false.
108    
109     jtlo = mybylo(mythid)
110     jthi = mybyhi(mythid)
111     itlo = mybxlo(mythid)
112     ithi = mybxhi(mythid)
113     jmin = 1
114     jmax = sny
115     imin = 1
116     imax = snx
117    
118     il=ilnblnk( tbarfile )
119     write(fnametheta(1:80),'(2a,i10.10)')
120     & tbarfile(1:il),'.',optimcycle
121     c
122     il=ilnblnk( sbarfile )
123     write(fnamesalt(1:80),'(2a,i10.10)')
124     & sbarfile(1:il),'.',optimcycle
125     c
126     il=ilnblnk( ubarfile )
127     write(fnameuvel(1:80),'(2a,i10.10)')
128     & ubarfile(1:il),'.',optimcycle
129     c
130     il=ilnblnk( vbarfile )
131     write(fnamevvel(1:80),'(2a,i10.10)')
132     & vbarfile(1:il),'.',optimcycle
133    
134     do isect = 1, nsect
135    
136     call mdsfindunit( funit, mythid )
137     write(fnameout(1:80),'(a,i2.2,a,i4.4)')
138     & 'cost_trans_zon',isect,'.',optimcycle
139     open(unit=funit,file=fnameout)
140    
141     write(msgbuf,'(a,1(X,D22.15))')
142     & 'ECCO_TRANS_ZON_XLON: section at lon: ', xlon(isect)
143     call print_message( msgbuf, standardmessageunit,
144     & SQUEEZE_RIGHT, mythid )
145    
146     musum(isect) = 0.0
147    
148     do irec = 1, nmonsrec
149    
150     call active_read_xyz( fnametheta, tbar, irec,
151     & doglobalread, ladinit,
152     & optimcycle, mythid,
153     & dummy )
154     c
155     call active_read_xyz( fnamesalt, sbar, irec,
156     & doglobalread, ladinit,
157     & optimcycle, mythid,
158     & dummy )
159     c
160     call active_read_xyz( fnameuvel, ubar, irec,
161     & doglobalread, ladinit,
162     & optimcycle, mythid,
163     & dummy )
164     c
165     call active_read_xyz( fnamevvel, vbar, irec,
166     & doglobalread, ladinit,
167     & optimcycle, mythid,
168     & dummy )
169    
170     tu(isect) = 0.0
171     su(isect) = 0.0
172     mu(isect) = 0.0
173     mumin(isect) = 0.0
174     mumax(isect) = 0.0
175     kmin(isect) = 0
176     kmax(isect) = 0
177    
178     c-- Next, do the monthly average for temperature.
179     c-- Assign the first value to the array holding the average.
180     do bj = jtlo,jthi
181     do bi = itlo,ithi
182     do k = 1,nr
183     do j = jmin,jmax
184     do i = imin,imax
185     del_x = xc(i,j,bi,bj)-xc(i-1,j,bi,bj)
186     if ( xc(i,j,bi,bj) .ge. xlon(isect) .and.
187     $ xc(i,j,bi,bj) .lt. xlon(isect)+del_x .and.
188     $ yc(i,j,bi,bj) .ge. beglat(isect) .and.
189     $ yc(i,j,bi,bj) .le. endlat(isect) ) then
190     tu(isect) = tu(isect) + p5*(tbar(i,j,k,bi,bj)
191     $ + tbar(i-1,j,k,bi,bj))*ubar(i,j,k,bi,bj)
192     $ * _dyG(i,j,bi,bj)
193     & * drF(k)*_hFacW(i,j,k,bi,bj)
194     $ *HeatCapacity_Cp*rhoNil
195     su(isect) = su(isect) + p5*(sbar(i,j,k,bi,bj)
196     $ + sbar(i-1,j,k,bi,bj))*ubar(i,j,k,bi,bj)
197     $ * _dyG(i,j,bi,bj)
198     & * drF(k)*_hFacW(i,j,k,bi,bj)
199     & * rhoNil/1000.
200     mu(isect) = mu(isect) + p5*(hFacC(i,j,k,bi,bj)
201     $ + hFacC(i-1,j,k,bi,bj))*ubar(i,j,k,bi,bj)
202     $ * _dyG(i,j,bi,bj)
203     & * drF(k)*_hFacW(i,j,k,bi,bj)
204     endif
205     enddo
206     enddo
207     mulev(isect,k) = mu(isect)
208     enddo
209     enddo
210     enddo
211    
212 jmc 1.4 _GLOBAL_SUM_RL( tu(isect), mythid )
213     _GLOBAL_SUM_RL( su(isect), mythid )
214     _GLOBAL_SUM_RL( mu(isect), mythid )
215 heimbach 1.1 c
216     do k =1,nr
217 jmc 1.4 _GLOBAL_SUM_RL( mulev(isect,k), mythid )
218 heimbach 1.1 enddo
219     mumin(isect) = mulev(isect,1)
220     mumax(isect) = mulev(isect,1)
221     do k = 2,nr
222     if ( mulev(isect,k) .GT. mulev(isect,k-1) ) then
223     mumax(isect) = mulev(isect,k)
224     kmax(isect) = k
225     endif
226     if ( mulev(isect,k) .LT. mulev(isect,k-1) ) then
227     mumin(isect) = mulev(isect,k)
228     kmin(isect) = k
229     endif
230     enddo
231    
232     musum(isect) = musum(isect) + mu(isect)
233    
234     write(msgbuf,'(a,i3,i5,2i3,5(X,D15.8))')
235 jmc 1.3 & 'ECCO_TRANS_ZON ', isect, irec, kmin(isect), kmax(isect),
236 heimbach 1.1 & tu(isect), su(isect), mu(isect), mumin(isect), mumax(isect)
237     call print_message( msgbuf, standardmessageunit,
238     & SQUEEZE_RIGHT, mythid )
239     c
240     write(msgbuf,'(a,i3,1(X,D22.15))')
241     & 'ECCO_TRANS_ZON_SUM musum ', isect, musum(isect)
242     call print_message( msgbuf, standardmessageunit,
243     & SQUEEZE_RIGHT, mythid )
244    
245 jmc 1.3 write(funit,'(i3,i5,2i3,5(X,D22.15))')
246     & isect, irec, kmin(isect), kmax(isect),
247 heimbach 1.1 & tu(isect), su(isect), mu(isect), mumin(isect), mumax(isect)
248    
249     c-- end loop over irec
250     enddo
251    
252     close(funit)
253    
254     c-- end loop over isect
255     enddo
256    
257 heimbach 1.2 #endif
258 heimbach 1.1
259     end

  ViewVC Help
Powered by ViewVC 1.1.22