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

Diff of /MITgcm/pkg/ecco/cost_obcss.F

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

revision 1.1 by heimbach, Thu Nov 6 22:10:07 2003 UTC revision 1.2 by heimbach, Mon Oct 11 16:38:53 2004 UTC
# Line 7  Line 7 
7        subroutine cost_obcss(        subroutine cost_obcss(
8       I                       myiter,       I                       myiter,
9       I                       mytime,       I                       mytime,
      I                       startrec,  
      I                       endrec,  
10       I                       mythid       I                       mythid
11       &                     )       &                     )
12    
# Line 18  c     ================================== Line 16  c     ==================================
16  c  c
17  c     o cost function contribution obc  c     o cost function contribution obc
18  c  c
 c     o G. Gebbie, gebbie@mit.edu, 18-Mar-2003  
19  c     ==================================================================  c     ==================================================================
20  c     SUBROUTINE cost_obcss  c     SUBROUTINE cost_obcss
21  c     ==================================================================  c     ==================================================================
# Line 47  c     == routine arguments == Line 44  c     == routine arguments ==
44        integer myiter        integer myiter
45        _RL     mytime        _RL     mytime
46        integer mythid        integer mythid
 cgg(    
       integer startrec  
       integer endrec  
 cgg)  
47    
48  c     == local variables ==  c     == local variables ==
49    
# Line 64  c     == local variables == Line 57  c     == local variables ==
57        integer il        integer il
58        integer iobcs        integer iobcs
59        integer jp1        integer jp1
       integer nrec  
       integer ilfld  
       integer igg  
60    
61        _RL fctile        _RL fctile
62        _RL fcthread        _RL fcthread
63        _RL dummy        _RL dummy
       _RL gg  
       _RL tmpx  
       _RL tmpfield (1-olx:snx+olx,nr,nsx,nsy)  
       _RL barofield (1-olx:snx+olx,nsx,nsy)  
       _RL maskxz   (1-olx:snx+olx,nr,nsx,nsy)  
       _RL vtop  
64    
65        character*(80) fnamefld        character*(80) fnametheta
66          character*(80) fnamesalt
67          character*(80) fnameuvel
68          character*(80) fnamevvel
69    
70        logical doglobalread        logical doglobalread
71        logical ladinit        logical ladinit
# Line 107  c--   Read tiled data. Line 94  c--   Read tiled data.
94        doglobalread = .false.        doglobalread = .false.
95        ladinit      = .false.        ladinit      = .false.
96    
 c     Number of records to be used.  
       nrec = endrec-startrec+1  
   
97  #ifdef ALLOW_OBCSS_COST_CONTRIBUTION  #ifdef ALLOW_OBCSS_COST_CONTRIBUTION
98    
99        jp1 = 1        jp1 = 1
100        fcthread = 0. _d 0        fcthread = 0. _d 0
101    
102  #ifdef ECCO_VERBOSE  c--   Loop over records.
103        _BEGIN_MASTER( mythid )        do irec = 1,nmonsrec
       write(msgbuf,'(a)') ' '  
       call print_message( msgbuf, standardmessageunit,  
      &                    SQUEEZE_RIGHT , mythid)  
       write(msgbuf,'(a)') ' '  
       call print_message( msgbuf, standardmessageunit,  
      &                    SQUEEZE_RIGHT , mythid)  
       write(msgbuf,'(a,i9.8)')  
      &  ' cost_obcss: number of records to process: ',nrec  
       call print_message( msgbuf, standardmessageunit,  
      &                    SQUEEZE_RIGHT , mythid)  
       write(msgbuf,'(a)') ' '  
       call print_message( msgbuf, standardmessageunit,  
      &                    SQUEEZE_RIGHT , mythid)  
       _END_MASTER( mythid )  
 #endif  
104    
105        if (optimcycle .ge. 0) then  c--     temperature
106          ilfld=ilnblnk( xx_obcss_file )          iobcs = 1
107          write(fnamefld(1:80),'(2a,i10.10)')  c--     Read time averages and the monthly mean data.
108       &       xx_obcss_file(1:ilfld), '.', optimcycle          il = ilnblnk( tbarfile )
109        endif          write(fnametheta(1:80),'(2a,i10.10)')
110         &       tbarfile(1:il),'.',optimcycle
111            call active_read_xyz( fnametheta, tbar, irec,
112         &                        doglobalread, ladinit,
113         &                        optimcycle, mythid,
114         &                        xx_tbar_mean_dummy )
115    
116  c--   Loop over records.          call mdsreadfieldxz( OBStFile, readBinaryPrec, 'RS',
117        do irec = 1,nrec       &                       nr, OBSt, irec, mythid)
118    
119           do bj = jtlo,jthi          do bj = jtlo,jthi
120             do bi = itlo,ithi            do bi = itlo,ithi
121               do i = imin,imax  c--         Loop over the model layers
122                 barofield(i,bi,bj) = 0. _d 0              fctile = 0. _d 0
123               enddo              do k = 1,nr
124             enddo  c--           Compute model data misfit and cost function term for
125    c             the temperature field.
126                   do i = imin,imax
127                      j = OB_Js(I,bi,bj)
128                      if (maskS(i,j+jp1,k,bi,bj) .ne. 0.) then
129                         fctile = fctile +
130         &                    wobcss(k,iobcs)*cosphi(i,j,bi,bj)*
131         &                    (tbar(i,j,k,bi,bj) - OBSt(i,k,bi,bj))*
132         &                    (tbar(i,j,k,bi,bj) - OBSt(i,k,bi,bj))
133                      endif
134                   enddo
135                enddo
136    c--         End of loop over layers.
137                fcthread         = fcthread           + fctile
138                objf_obcss(bi,bj) = objf_obcss(bi,bj) + fctile
139              enddo
140          enddo          enddo
141    
142          call active_read_xz( fnamefld, tmpfield, irec, doglobalread,  c--     salt
143       &                       ladinit, optimcycle, mythid          iobcs = 2
144       &        , xx_obcss_dummy )  c--     Read time averages and the monthly mean data.
145            il = ilnblnk( sbarfile )
146  cgg    Need to solve for iobcs would have been.          write(fnamesalt(1:80),'(2a,i10.10)')
147            gg    = (irec-1)/nobcs       &       sbarfile(1:il),'.',optimcycle
148            igg   = int(gg)          call active_read_xyz( fnamesalt, sbar, irec,
149            iobcs = irec - igg*nobcs       &                        doglobalread, ladinit,
150  cgg          print*,'S IREC, IOBCS',irec, iobcs       &                        optimcycle, mythid,
151         &                        xx_sbar_mean_dummy )
152            call active_read_xz( 'maskobcss', maskxz,  
153       &                         iobcs,          call mdsreadfieldxz( OBSsFile, readBinaryPrec, 'RS',
154       &                         doglobalread, ladinit, 0,       &                       nr, OBSs, irec, mythid)
155       &                         mythid, dummy )  
156            do bj = jtlo,jthi
157  cgg     Need to change xx field to baroclinic vel.            do bi = itlo,ithi
158  cgg     Level Nr contains barotropic vel, remove it.  c--         Loop over the model layers
159  cgg     The deepest wet level velocity should be              fctile = 0. _d 0
160  cgg     computed in order to ensure zero integrated flux.              do k = 1,nr
161          if (iobcs .eq. 3 .or. iobcs .eq. 4) then  c--           Compute model data misfit and cost function term for
162  c--     Loop over this thread's tiles.  c             the temperature field.
163            do bj = jtlo,jthi                 do i = imin,imax
164              do bi = itlo,ithi                    j = OB_Js(I,bi,bj)
165                do i = imin,imax                    if (maskS(i,j+jp1,k,bi,bj) .ne. 0.) then
166                         fctile = fctile +
167  cgg         The barotropic velocity is stored in level 1.       &                    wobcss(k,iobcs)*cosphi(i,j,bi,bj)*
168  cgg         Penalize for deviation in it.       &                    (sbar(i,j,k,bi,bj) - OBSs(i,k,bi,bj))*
169                  barofield(i,bi,bj) = tmpfield(i,1,bi,bj)       &                    (sbar(i,j,k,bi,bj) - OBSs(i,k,bi,bj))
170       &                             * maskxz(i,1,bi,bj)                    endif
171                   enddo
                 vtop = 0.d0  
                 tmpfield(i,1,bi,bj) = 0.d0  
   
                 do k = 1,Nr  
 cgg    If cells are not full, this should be modified with hFac.  
 cgg      
 cgg    The xx field (tmpfldxz) does not contain the velocity at the  
 cgg    lowest wet level. This velocity is not independent; it must  
 cgg    exactly balance the volume flux, since we are dealing with  
 cgg    the baroclinic velocity structure..  
                   vtop = tmpfield(i,k,bi,bj)*  
      &               maskxz(i,k,bi,bj) * delZ(k) + vtop  
                 enddo  
                 tmpfield(i,1,bi,bj) = -vtop / delZ(1)  
               enddo  
172              enddo              enddo
173    c--         End of loop over layers.
174                fcthread         = fcthread           + fctile
175                objf_obcss(bi,bj) = objf_obcss(bi,bj) + fctile
176            enddo            enddo
177            enddo
178    
179          endif  c--     uvel
180            iobcs = 3
181    c--     Read time averages and the monthly mean data.
182            il = ilnblnk( ubarfile )
183            write(fnameuvel(1:80),'(2a,i10.10)')
184         &       ubarfile(1:il),'.',optimcycle
185            call active_read_xyz( fnameuvel, ubar, irec,
186         &                        doglobalread, ladinit,
187         &                        optimcycle, mythid,
188         &                        dummy )
189    
190  c--     Loop over this thread's tiles.          call mdsreadfieldxz( OBSuFile, readBinaryPrec, 'RS',
191         &                       nr, OBSu, irec, mythid)
192          do bj = jtlo,jthi          do bj = jtlo,jthi
193            do bi = itlo,ithi            do bi = itlo,ithi
194    c--         Loop over the model layers
 c--         Determine the weights to be used.  
195              fctile = 0. _d 0              fctile = 0. _d 0
196                do k = 1,nr
197              if (iobcs .eq. 3 .or. iobcs .eq. 4) then  c--           Compute model data misfit and cost function term for
198                do i = imin,imax  c             the temperature field.
199                  j = OB_Js(I,bi,bj)                 do i = imin,imax
200                  tmpx = barofield(i,bi,bj)                    j = OB_Js(I,bi,bj)
201                    fctile = fctile                    if (maskW(i,j,k,bi,bj) .ne. 0.) then
202       &               + wbaro*cosphi(i,j,bi,bj)                       fctile = fctile +
203       &                 *tmpx*tmpx       &                    wobcss(k,iobcs)*cosphi(i,j,bi,bj)*
204       &                 *maskxz(i,1,bi,bj)       &                    (ubar(i,j,k,bi,bj) - OBSu(i,k,bi,bj))*
205  cgg                print*,'S bt fctile',fctile       &                    (ubar(i,j,k,bi,bj) - OBSu(i,k,bi,bj))
206                enddo                    endif
207              endif                 enddo
   
             do k = 1, Nr  
               do i = imin,imax  
                  j = OB_Js(I,bi,bj)  
 cgg                 if (maskS(i,j+jp1,k,bi,bj) .ne. 0.) then  
                   tmpx = tmpfield(i,k,bi,bj)  
                   fctile = fctile  
      &                 + wobcssLev(i,k,bi,bj,iobcs)*cosphi(i,j,bi,bj)  
      &                 *tmpx*tmpx  
      &                 *maskxz(i,k,bi,bj)  
 cgg                endif  
 cgg                print*,'S fctile',fctile  
               enddo  
208              enddo              enddo
209    c--         End of loop over layers.
210                fcthread         = fcthread           + fctile
211                objf_obcss(bi,bj) = objf_obcss(bi,bj) + fctile
212              enddo
213            enddo
214    
215    c--     vvel
216            iobcs = 4
217    c--     Read time averages and the monthly mean data.
218            il = ilnblnk( vbarfile )
219            write(fnamevvel(1:80),'(2a,i10.10)')
220         &       vbarfile(1:il),'.',optimcycle
221            call active_read_xyz( fnamevvel, vbar, irec,
222         &                        doglobalread, ladinit,
223         &                        optimcycle, mythid,
224         &                        dummy )
225    
226            call mdsreadfieldxz( OBSvFile, readBinaryPrec, 'RS',
227         &                       nr, OBSv, irec, mythid)
228    
229            do bj = jtlo,jthi
230              do bi = itlo,ithi
231    c--         Loop over the model layers
232                fctile = 0. _d 0
233                do k = 1,nr
234    c--           Compute model data misfit and cost function term for
235    c             the temperature field.
236                   do i = imin,imax
237                      j = OB_Js(I,bi,bj)
238                      if (maskS(i,j+jp1,k,bi,bj) .ne. 0.) then
239                         fctile = fctile +
240         &                    wobcss(k,iobcs)*cosphi(i,j,bi,bj)*
241         &                    (vbar(i,j,k,bi,bj) - OBSv(i,k,bi,bj))*
242         &                    (vbar(i,j,k,bi,bj) - OBSv(i,k,bi,bj))
243                      endif
244                   enddo
245                enddo
246    c--         End of loop over layers.
247                fcthread         = fcthread           + fctile
248              objf_obcss(bi,bj) = objf_obcss(bi,bj) + fctile              objf_obcss(bi,bj) = objf_obcss(bi,bj) + fctile
             fcthread         = fcthread + fctile  
249            enddo            enddo
250          enddo          enddo
251    

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.2

  ViewVC Help
Powered by ViewVC 1.1.22