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

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

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


Revision 1.4 - (show annotations) (download)
Sat Mar 14 11:53:41 2009 UTC (15 years, 1 month ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, 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, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.3: +2 -2 lines
o A final fix in cost_ssh_new(!)
o Move ecco_check to earlier instance
o Increase maxNumDays to 17yr
o A few debug calls

1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_averagesgeneric.F,v 1.3 2007/10/09 00:02:50 jmc Exp $
2 C $Name: $
3
4 #include "COST_CPPOPTIONS.h"
5
6 subroutine cost_averagesgeneric(
7 & localbarfile,
8 & 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*(MAX_LEN_FNAM) 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 localbar(i,j,k,bi,bj) =
106 & (localbar(i,j,k,bi,bj)
107 & +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 write(fname,'(2a,i10.10)')
118 & 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 localbar(i,j,k,bi,bj) =
136 & 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