/[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.10 - (hide annotations) (download)
Tue Nov 24 21:23:48 2015 UTC (8 years, 7 months ago) by gforget
Branch: MAIN
CVS Tags: HEAD
Changes since 1.9: +1 -1 lines
FILE REMOVED
- retire old codes to the Attic.

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

  ViewVC Help
Powered by ViewVC 1.1.22