/[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.1 - (hide annotations) (download)
Thu Sep 1 05:32:56 2005 UTC (18 years, 9 months ago) by heimbach
Branch: MAIN
o Adding cost term for seaice obs (daily SMR vs. AREA)
  new seaice_cost init/weight/final routines
o Modularized cost_averages routines (new cost_averagesgeneric.F)

1 heimbach 1.1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_averagesfields.F,v 1.3 2005/07/28 13:51:36 heimbach Exp $
2    
3     #include "COST_CPPOPTIONS.h"
4    
5     subroutine cost_averagesgeneric(
6     & localbarfile,
7     & localbar, localfld, xx_localbar_mean_dummy,
8     & first, last, startofloc, endofloc, inloc,
9     & sum1loc, locrec, nnz, mythid )
10    
11     c ==================================================================
12     c SUBROUTINE cost_averagesgeneric
13     c ==================================================================
14     c
15     c o Compute time averages of cost variables
16     c
17     c ==================================================================
18     c SUBROUTINE cost_averagesgeneric
19     c ==================================================================
20    
21     implicit none
22    
23     c == global variables ==
24    
25     #include "EEPARAMS.h"
26     #include "SIZE.h"
27     #include "PARAMS.h"
28     #include "SEAICE.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     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