/[MITgcm]/MITgcm_contrib/SOSE/BoxAdj/code_ad/cost_obcss.F
ViewVC logotype

Annotation of /MITgcm_contrib/SOSE/BoxAdj/code_ad/cost_obcss.F

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


Revision 1.2 - (hide annotations) (download)
Mon Apr 18 23:50:34 2011 UTC (14 years, 8 months ago) by mmazloff
Branch: MAIN
CVS Tags: HEAD
Changes since 1.1: +0 -0 lines
FILE REMOVED
updating

1 mmazloff 1.1
2     #include "COST_CPPOPTIONS.h"
3     #ifdef ALLOW_OBCS
4     # include "OBCS_OPTIONS.h"
5     #endif
6    
7     subroutine cost_obcss(
8     I myiter,
9     I mytime,
10     I startrec,
11     I endrec,
12     I mythid
13     & )
14    
15     c ==================================================================
16     c SUBROUTINE cost_obcss
17     c ==================================================================
18     c
19     c o cost function contribution obc
20     c
21     c o G. Gebbie, gebbie@mit.edu, 18-Mar-2003
22     c ==================================================================
23     c SUBROUTINE cost_obcss
24     c ==================================================================
25    
26     implicit none
27    
28     c == global variables ==
29    
30     #include "EEPARAMS.h"
31     #include "SIZE.h"
32     #include "PARAMS.h"
33     #include "GRID.h"
34     #include "DYNVARS.h"
35     #ifdef ALLOW_OBCS
36     # include "OBCS.h"
37     #endif
38    
39     #include "cal.h"
40     #include "ecco_cost.h"
41     #include "ctrl.h"
42     #include "ctrl_dummy.h"
43     #include "optim.h"
44    
45     c == routine arguments ==
46    
47     integer myiter
48     _RL mytime
49     integer mythid
50     cgg(
51     integer startrec
52     integer endrec
53     cgg)
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     integer irec
64     integer il
65     integer iobcs
66     integer jp1
67     integer nrec
68     integer ilfld
69     integer igg
70    
71     _RL fctile
72     _RL fcthread
73     _RL dummy
74     _RL gg
75     _RL tmpx
76     _RL tmpfield (1-olx:snx+olx,nr,nsx,nsy)
77     _RL maskxz (1-olx:snx+olx,nr,nsx,nsy)
78    
79     character*(80) fnamefld
80    
81     logical doglobalread
82     logical ladinit
83    
84     #ifdef ECCO_VERBOSE
85     character*(MAX_LEN_MBUF) msgbuf
86     #endif
87    
88     c == external functions ==
89    
90     integer ilnblnk
91     external ilnblnk
92    
93     c == end of interface ==
94    
95     jtlo = mybylo(mythid)
96     jthi = mybyhi(mythid)
97     itlo = mybxlo(mythid)
98     ithi = mybxhi(mythid)
99     jmin = 1
100     jmax = sny
101     imin = 1
102     imax = snx
103    
104     c-- Read tiled data.
105     doglobalread = .false.
106     ladinit = .false.
107    
108     c Number of records to be used.
109     nrec = endrec-startrec+1
110    
111     #ifdef ALLOW_OBCSS_COST_CONTRIBUTION
112    
113     jp1 = 1
114     fcthread = 0. _d 0
115    
116     #ifdef ECCO_VERBOSE
117     _BEGIN_MASTER( mythid )
118     write(msgbuf,'(a)') ' '
119     call print_message( msgbuf, standardmessageunit,
120     & SQUEEZE_RIGHT , mythid)
121     write(msgbuf,'(a)') ' '
122     call print_message( msgbuf, standardmessageunit,
123     & SQUEEZE_RIGHT , mythid)
124     write(msgbuf,'(a,i9.8)')
125     & ' cost_obcss: number of records to process: ',nrec
126     call print_message( msgbuf, standardmessageunit,
127     & SQUEEZE_RIGHT , mythid)
128     write(msgbuf,'(a)') ' '
129     call print_message( msgbuf, standardmessageunit,
130     & SQUEEZE_RIGHT , mythid)
131     _END_MASTER( mythid )
132     #endif
133    
134     if (optimcycle .ge. 0) then
135     ilfld=ilnblnk( xx_obcss_file )
136     write(fnamefld(1:80),'(2a,i10.10)')
137     & xx_obcss_file(1:ilfld), '.', optimcycle
138     endif
139    
140     c-- Loop over records.
141     do irec = 1,nrec
142    
143     call active_read_xz( fnamefld, tmpfield, irec, doglobalread,
144     & ladinit, optimcycle, mythid
145     & , xx_obcss_dummy )
146    
147     cgg Need to solve for iobcs would have been.
148     gg = (irec-1)/nobcs
149     igg = int(gg)
150     iobcs = irec - igg*nobcs
151     cgg print*,'S IREC, IOBCS',irec, iobcs
152    
153     call active_read_xz( 'maskobcss', maskxz,
154     & iobcs,
155     & doglobalread, ladinit, 0,
156     & mythid, dummy )
157    
158    
159     c-- Loop over this thread's tiles.
160     do bj = jtlo,jthi
161     do bi = itlo,ithi
162    
163     c-- Determine the weights to be used.
164     fctile = 0. _d 0
165    
166     do k = 1, Nr
167     do i = imin,imax
168     j = OB_Js(I,bi,bj)
169     cgg if (maskS(i,j+jp1,k,bi,bj) .ne. 0.) then
170     tmpx = tmpfield(i,k,bi,bj)
171     CMM fctile = fctile + wobcss2(i,k,bi,bj,iobcs)
172     fctile = fctile + wobcss(k,iobcs)
173     & *tmpx*tmpx*maskxz(i,k,bi,bj)
174     cgg endif
175     CMM if (wobcss2(i,k,bi,bj,iobcs)*maskxz(i,k,bi,bj).ne.0.)
176     if (wobcss(k,iobcs)*maskxz(i,k,bi,bj).ne.0.)
177     & num_obcss(bi,bj) = num_obcss(bi,bj) + 1. _d 0
178     cgg print*,'S fctile',fctile
179     enddo
180     enddo
181    
182     objf_obcss(bi,bj) = objf_obcss(bi,bj) + fctile
183     fcthread = fcthread + fctile
184     enddo
185     enddo
186    
187     #ifdef ECCO_VERBOSE
188     c-- Print cost function for all tiles.
189     _GLOBAL_SUM_RL( fcthread , myThid )
190     write(msgbuf,'(a)') ' '
191     call print_message( msgbuf, standardmessageunit,
192     & SQUEEZE_RIGHT , mythid)
193     write(msgbuf,'(a,i8.8)')
194     & ' cost_obcss: irec = ',irec
195     call print_message( msgbuf, standardmessageunit,
196     & SQUEEZE_RIGHT , mythid)
197     write(msgbuf,'(a,a,d22.15)')
198     & ' global cost function value',
199     & ' (obcss) = ',fcthread
200     call print_message( msgbuf, standardmessageunit,
201     & SQUEEZE_RIGHT , mythid)
202     write(msgbuf,'(a)') ' '
203     call print_message( msgbuf, standardmessageunit,
204     & SQUEEZE_RIGHT , mythid)
205     #endif
206    
207     enddo
208     c-- End of loop over records.
209    
210     #endif
211    
212     return
213     end
214    
215    
216    
217    
218    
219    
220    

  ViewVC Help
Powered by ViewVC 1.1.22