/[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.3 - (hide annotations) (download)
Tue Oct 9 00:02:50 2007 UTC (16 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59k, checkpoint59j, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61h, checkpoint61i
Changes since 1.2: +7 -6 lines
add missing cvs $Header:$ or $Name:$

1 jmc 1.3 C $Header: $
2     C $Name: $
3 heimbach 1.1
4     #include "COST_CPPOPTIONS.h"
5    
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     #ifdef ALLOW_COST
31     # include "optim.h"
32     # include "ecco_cost.h"
33     # include "ctrl_dummy.h"
34     #endif
35    
36     c == routine arguments ==
37    
38     integer mythid
39     integer nnz
40     integer locrec
41     integer sum1loc
42    
43     _RL localbar(1-olx:snx+olx,1-oly:sny+oly,nnz,nsx,nsy)
44     _RL localfld(1-olx:snx+olx,1-oly:sny+oly,nnz,nsx,nsy)
45     _RL xx_localbar_mean_dummy
46    
47     logical first
48     logical last
49     logical startofloc
50     logical endofloc
51     logical inloc
52    
53     character*(128) localbarfile
54    
55     c == local variables ==
56    
57     integer bi,bj
58     integer i,j,k
59     integer itlo,ithi
60     integer jtlo,jthi
61     integer jmin,jmax
62     integer imin,imax
63    
64     integer il
65    
66     character*(128) fname
67    
68     c == external functions ==
69    
70     integer ilnblnk
71     external ilnblnk
72    
73     c == end of interface ==
74    
75     jtlo = mybylo(mythid)
76     jthi = mybyhi(mythid)
77     itlo = mybxlo(mythid)
78     ithi = mybxhi(mythid)
79     jmin = 1
80     jmax = sny
81     imin = 1
82     imax = snx
83    
84     c-- First, do the daily averages.
85     if (first .or. startofloc) then
86     c-- Assign the first value to the array holding the average.
87     do bj = jtlo,jthi
88     do bi = itlo,ithi
89     do k = 1,nnz
90     do j = jmin,jmax
91     do i = imin,imax
92     localbar(i,j,k,bi,bj) = localfld(i,j,k,bi,bj)
93     enddo
94     enddo
95     enddo
96     enddo
97     enddo
98     else if (last .or. endofloc) then
99     c-- Add the last value and devide by the number of accumulated records.
100     do bj = jtlo,jthi
101     do bi = itlo,ithi
102     do k = 1,nnz
103     do j = jmin,jmax
104     do i = imin,imax
105 jmc 1.3 localbar(i,j,k,bi,bj) =
106     & (localbar(i,j,k,bi,bj)
107 heimbach 1.1 & +localfld(i,j,k,bi,bj))/
108     & float(sum1loc)
109     enddo
110     enddo
111     enddo
112     enddo
113     enddo
114     c-- Save ...bar on file.
115     write(fname(1:128),'(80a)') ' '
116     il=ilnblnk( localbarfile )
117 jmc 1.3 write(fname,'(2a,i10.10)')
118 heimbach 1.1 & localbarfile(1:il), '.', optimcycle
119     if ( nnz .EQ. 1 ) then
120     call active_write_xy( fname, localbar, locrec, optimcycle,
121     & mythid, xx_localbar_mean_dummy )
122     else
123     call active_write_xyz( fname, localbar, locrec, optimcycle,
124     & mythid, xx_localbar_mean_dummy )
125     endif
126     else if ( ( inloc ) .and.
127     & .not. (first .or. startofloc) .and.
128     & .not. (last .or. endofloc ) ) then
129     c-- Accumulate the array holding the average.
130     do bj = jtlo,jthi
131     do bi = itlo,ithi
132     do j = jmin,jmax
133     do k = 1,nnz
134     do i = imin,imax
135 jmc 1.3 localbar(i,j,k,bi,bj) =
136 heimbach 1.1 & localbar(i,j,k,bi,bj) + localfld(i,j,k,bi,bj)
137     enddo
138     enddo
139     enddo
140     enddo
141     enddo
142     else
143     stop 'in cost_averagesgeneric'
144     endif
145    
146     return
147     end
148    

  ViewVC Help
Powered by ViewVC 1.1.22