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

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

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


Revision 1.10 - (hide annotations) (download)
Mon Mar 23 21:10:04 2015 UTC (9 years, 3 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65k, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, HEAD
Changes since 1.9: +18 -1 lines
- use eccoiter in place of optimcycle.
- if autodiff is not compiled then use READ_REC_XY_RL/READ_REC_XYZ_RL instead of active read/write

1 gforget 1.10 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_averagesgeneric.F,v 1.9 2014/10/22 13:28:27 gforget Exp $
2 jmc 1.3 C $Name: $
3 heimbach 1.1
4 jmc 1.7 #include "ECCO_OPTIONS.h"
5 heimbach 1.1
6     subroutine cost_averagesgeneric(
7 jmc 1.3 & localbarfile,
8 heimbach 1.1 & localbar, localfld, xx_localbar_mean_dummy,
9     & first, last, startofloc, endofloc, inloc,
10     & sum1loc, locrec, nnz, mythid )
11    
12     c ==================================================================
13     c SUBROUTINE cost_averagesgeneric
14     c ==================================================================
15     c
16     c o Compute time averages of cost variables
17     c
18     c ==================================================================
19     c SUBROUTINE cost_averagesgeneric
20     c ==================================================================
21    
22     implicit none
23    
24     c == global variables ==
25    
26     #include "EEPARAMS.h"
27     #include "SIZE.h"
28     #include "PARAMS.h"
29    
30 gforget 1.8 #ifdef ALLOW_ECCO
31     # include "ecco.h"
32 heimbach 1.1 #endif
33    
34     c == routine arguments ==
35    
36     integer mythid
37     integer nnz
38     integer locrec
39     integer sum1loc
40    
41     _RL localbar(1-olx:snx+olx,1-oly:sny+oly,nnz,nsx,nsy)
42     _RL localfld(1-olx:snx+olx,1-oly:sny+oly,nnz,nsx,nsy)
43     _RL xx_localbar_mean_dummy
44    
45     logical first
46     logical last
47     logical startofloc
48     logical endofloc
49     logical inloc
50    
51 heimbach 1.4 character*(MAX_LEN_FNAM) localbarfile
52 heimbach 1.1
53     c == local variables ==
54    
55     integer bi,bj
56     integer i,j,k
57     integer itlo,ithi
58     integer jtlo,jthi
59     integer jmin,jmax
60     integer imin,imax
61    
62     integer il
63    
64     character*(128) fname
65 gforget 1.8 #ifdef ALLOW_ECCO_DEBUG
66     character*(max_len_mbuf) msgbuf
67     #endif
68 heimbach 1.1
69     c == external functions ==
70    
71     integer ilnblnk
72     external ilnblnk
73    
74     c == end of interface ==
75    
76 gforget 1.8 #ifdef ALLOW_ECCO_DEBUG
77     write(msgbuf,'(a)') '>> entering'
78     call print_message( msgbuf, standardmessageunit,
79     & SQUEEZE_RIGHT , mythid)
80    
81     il=ilnblnk( localbarfile )
82     write(msgbuf,'(a,a)')
83     & 'cost_averagesgeneric, file : ',localbarfile(1:il)
84     call print_message( msgbuf, standardmessageunit,
85     & SQUEEZE_RIGHT , mythid)
86    
87     write(msgbuf,'(a,5L5)')
88     & 'cost_averagesgeneric, logicals : ',
89     & first, last, startofloc, endofloc, inloc
90     call print_message( msgbuf, standardmessageunit,
91     & SQUEEZE_RIGHT , mythid)
92    
93     write(msgbuf,'(a,3i5)')
94     & 'cost_averagesgeneric, integers : ',
95     & sum1loc, locrec, nnz
96     call print_message( msgbuf, standardmessageunit,
97     & SQUEEZE_RIGHT , mythid)
98    
99     write(msgbuf,'(a)') '<< leaving'
100     call print_message( msgbuf, standardmessageunit,
101     & SQUEEZE_RIGHT , mythid)
102     #endif
103    
104 heimbach 1.1 jtlo = mybylo(mythid)
105     jthi = mybyhi(mythid)
106     itlo = mybxlo(mythid)
107     ithi = mybxhi(mythid)
108     jmin = 1
109     jmax = sny
110     imin = 1
111     imax = snx
112    
113 gforget 1.9 if (startofloc .and. endofloc) then
114     c-- Save snapshot at every time step
115     do bj = jtlo,jthi
116     do bi = itlo,ithi
117     do k = 1,nnz
118     do j = jmin,jmax
119     do i = imin,imax
120     localbar(i,j,k,bi,bj) = localfld(i,j,k,bi,bj)
121     enddo
122     enddo
123     enddo
124     enddo
125     enddo
126     c-- Save ...bar on file.
127     write(fname(1:128),'(80a)') ' '
128     il=ilnblnk( localbarfile )
129     write(fname,'(2a,i10.10)')
130     & localbarfile(1:il), '.', eccoiter
131 gforget 1.10 #ifdef ALLOW_AUTODIFF
132 gforget 1.9 if ( nnz .EQ. 1 ) then
133     call active_write_xy( fname, localbar, locrec, eccoiter,
134     & mythid, xx_localbar_mean_dummy )
135     else
136     call active_write_xyz( fname, localbar, locrec, eccoiter,
137     & mythid, xx_localbar_mean_dummy )
138     endif
139 gforget 1.10 #else
140     if ( nnz .EQ. 1 ) then
141     CALL WRITE_REC_XY_RL( fname, localbar, locrec, 1, myThid )
142     else
143     CALL WRITE_REC_XYZ_RL( fname, localbar, locrec, 1, myThid )
144     endif
145     #endif
146    
147 gforget 1.9 elseif (first .or. startofloc) then
148 heimbach 1.1 c-- Assign the first value to the array holding the average.
149     do bj = jtlo,jthi
150     do bi = itlo,ithi
151     do k = 1,nnz
152     do j = jmin,jmax
153     do i = imin,imax
154     localbar(i,j,k,bi,bj) = localfld(i,j,k,bi,bj)
155     enddo
156     enddo
157     enddo
158     enddo
159     enddo
160     else if (last .or. endofloc) then
161     c-- Add the last value and devide by the number of accumulated records.
162     do bj = jtlo,jthi
163     do bi = itlo,ithi
164     do k = 1,nnz
165     do j = jmin,jmax
166     do i = imin,imax
167 jmc 1.3 localbar(i,j,k,bi,bj) =
168     & (localbar(i,j,k,bi,bj)
169 heimbach 1.1 & +localfld(i,j,k,bi,bj))/
170     & float(sum1loc)
171     enddo
172     enddo
173     enddo
174     enddo
175     enddo
176     c-- Save ...bar on file.
177     write(fname(1:128),'(80a)') ' '
178     il=ilnblnk( localbarfile )
179 jmc 1.3 write(fname,'(2a,i10.10)')
180 gforget 1.8 & localbarfile(1:il), '.', eccoiter
181 gforget 1.10 #ifdef ALLOW_AUTODIFF
182 heimbach 1.1 if ( nnz .EQ. 1 ) then
183 gforget 1.8 call active_write_xy( fname, localbar, locrec, eccoiter,
184 heimbach 1.1 & mythid, xx_localbar_mean_dummy )
185     else
186 gforget 1.8 call active_write_xyz( fname, localbar, locrec, eccoiter,
187 heimbach 1.1 & mythid, xx_localbar_mean_dummy )
188     endif
189 gforget 1.10 #else
190     if ( nnz .EQ. 1 ) then
191     CALL WRITE_REC_XY_RL( fname, localbar, locrec, 1, myThid )
192     else
193     CALL WRITE_REC_XYZ_RL( fname, localbar, locrec, 1, myThid )
194     endif
195     #endif
196 heimbach 1.1 else if ( ( inloc ) .and.
197     & .not. (first .or. startofloc) .and.
198     & .not. (last .or. endofloc ) ) then
199     c-- Accumulate the array holding the average.
200     do bj = jtlo,jthi
201     do bi = itlo,ithi
202     do j = jmin,jmax
203     do k = 1,nnz
204     do i = imin,imax
205 jmc 1.3 localbar(i,j,k,bi,bj) =
206 heimbach 1.1 & localbar(i,j,k,bi,bj) + localfld(i,j,k,bi,bj)
207     enddo
208     enddo
209     enddo
210     enddo
211     enddo
212     else
213     stop 'in cost_averagesgeneric'
214     endif
215    
216     return
217     end
218    

  ViewVC Help
Powered by ViewVC 1.1.22