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

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

  ViewVC Help
Powered by ViewVC 1.1.22