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

Diff of /MITgcm/pkg/ecco/cost_obcse.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_obcse(        subroutine cost_obcse(
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_obcse  c     SUBROUTINE cost_obcse
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 ip1        integer ip1
       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-oly:sny+oly,nr,nsx,nsy)  
       _RL barofield (1-oly:sny+oly,nsx,nsy)  
       _RL maskyz   (1-oly:sny+oly,nr,nsx,nsy)  
       _RL ubottom  
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_OBCSE_COST_CONTRIBUTION  #ifdef ALLOW_OBCSE_COST_CONTRIBUTION
98    
99        ip1 = 0        ip1 = 0
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_obcse: 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_obcse_file )          iobcs = 1
107          write(fnamefld(1:80),'(2a,i10.10)')  c--     Read time averages and the monthly mean data.
108       &       xx_obcse_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 mdsreadfieldyz( OBEtFile, ReadBinaryPrec, 'RS',
117        do irec = 1,nrec       &                       nr, OBEt, irec, mythid)
118    
119          do bj = jtlo,jthi          do bj = jtlo,jthi
120            do bi = itlo,ithi            do bi = itlo,ithi
121              do j = jmin,jmax  c--         Loop over the model layers
122                barofield(j,bi,bj) = 0. _d 0              fctile = 0. _d 0
123                do k = 1,nr
124    c--           Compute model data misfit and cost function term for
125    c             the temperature field.
126                   do j = jmin,jmax
127                      i = OB_Ie(J,bi,bj)
128                      if (maskS(i+ip1,j,k,bi,bj) .ne. 0.) then
129                         fctile = fctile +
130         &                    wobcse(k,iobcs)*cosphi(i,j,bi,bj)*
131         &                    (tbar(i,j,k,bi,bj) - OBEt(j,k,bi,bj))*
132         &                    (tbar(i,j,k,bi,bj) - OBEt(j,k,bi,bj))
133                      endif
134                   enddo
135              enddo              enddo
136    c--         End of loop over layers.
137                fcthread         = fcthread           + fctile
138                objf_obcse(bi,bj) = objf_obcse(bi,bj) + fctile
139            enddo            enddo
140          enddo          enddo
                 
         call active_read_yz( fnamefld, tmpfield, irec, doglobalread,  
      &                       ladinit, optimcycle, mythid  
      &        , xx_obcse_dummy )  
   
 cgg    Need to solve for iobcs would have been.  
           gg    = (irec-1)/nobcs  
           igg   = int(gg)  
           iobcs = irec - igg*nobcs  
141    
142  c--     Loop over this thread's tiles.  c--     salt
143            iobcs = 2
144    c--     Read time averages and the monthly mean data.
145            il = ilnblnk( sbarfile )
146            write(fnamesalt(1:80),'(2a,i10.10)')
147         &       sbarfile(1:il),'.',optimcycle
148            call active_read_xyz( fnamesalt, sbar, irec,
149         &                        doglobalread, ladinit,
150         &                        optimcycle, mythid,
151         &                        xx_sbar_mean_dummy )
152    
153            call mdsreadfieldyz( OBEsFile, readBinaryPrec, 'RS',
154         &                       nr, OBEs, irec, mythid)
155    
156          do bj = jtlo,jthi          do bj = jtlo,jthi
157            do bi = itlo,ithi            do bi = itlo,ithi
158    c--         Loop over the model layers
159            call active_read_yz( 'maskobcse', maskyz,              fctile = 0. _d 0
160       &                         iobcs,              do k = 1,nr
161       &                         doglobalread, ladinit, 0,  c--           Compute model data misfit and cost function term for
162       &                         mythid, dummy )  c             the temperature field.
163                   do j = jmin,jmax
164  cgg     Need to change xx field to baroclinic vel.                    i = OB_Ie(J,bi,bj)
165  cgg     Level Nr contains barotropic vel, remove it.                    if (maskS(i+ip1,j,k,bi,bj) .ne. 0.) then
166  cgg     The deepest wet level velocity should be                       fctile = fctile +
167  cgg     computed in order to ensure zero integrated flux.       &                    wobcse(k,iobcs)*cosphi(i,j,bi,bj)*
168          if (iobcs .eq. 3 .or. iobcs .eq. 4) then       &                    (sbar(i,j,k,bi,bj) - OBEs(j,k,bi,bj))*
169  c--     Loop over this thread's tiles.       &                    (sbar(i,j,k,bi,bj) - OBEs(j,k,bi,bj))
170            do bj = jtlo,jthi                    endif
171              do bi = itlo,ithi                 enddo
               do j = jmin,jmax  
   
 cgg         The barotropic velocity is stored in level 1.  
 cgg         Penalize for deviation in it.  
                 barofield(j,bi,bj) = tmpfield(j,1,bi,bj)  
      &                             * maskyz(j,1,bi,bj)  
   
                 tmpfield(j,1,bi,bj) = 0.d0  
                 utop = 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..  
                   utop = tmpfield(j,k,bi,bj)*  
      &               maskyz(j,k,bi,bj) * delZ(k) + utop  
                 enddo  
                 tmpfield(j,1,bi,bj) = -utop / delZ(1)  
               enddo  
172              enddo              enddo
173    c--         End of loop over layers.
174                fcthread         = fcthread           + fctile
175                objf_obcse(bi,bj) = objf_obcse(bi,bj) + fctile
176            enddo            enddo
177          endif          enddo
178    
179  c--         Determine the weights to be used.  c--     uvel
180              fctile = 0. _d 0          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              if (iobcs .eq. 3 .or. iobcs .eq. 4) then          call mdsreadfieldyz( OBEuFile, readBinaryPrec, 'RS',
191                do j = jmin,jmax       &                       nr, OBEu, irec, mythid)
192                  i = OB_Ie(j,bi,bj)          do bj = jtlo,jthi
193                  tmpx = barofield(j,bi,bj)            do bi = itlo,ithi
194                    fctile = fctile  c--         Loop over the model layers
195       &               + wbaro*cosphi(i,j,bi,bj)              fctile = 0. _d 0
196       &                 *tmpx*tmpx              do k = 1,nr
197       &                 *maskyz(j,1,bi,bj)  c--           Compute model data misfit and cost function term for
198                  print*,'fctile barotropic E',fctile  c             the temperature field.
199                enddo                 do j = jmin,jmax
200              endif                    i = OB_Ie(J,bi,bj)
201                      if (maskW(i+ip1,j,k,bi,bj) .ne. 0.) then
202              do k = 1, Nr                       fctile = fctile +
203                do j = jmin,jmax       &                    wobcse(k,iobcs)*cosphi(i,j,bi,bj)*
204                  i = OB_Ie(j,bi,bj)       &                    (ubar(i,j,k,bi,bj) - OBEu(j,k,bi,bj))*
205  cgg                if (maskW(i+ip1,j,k,bi,bj) .ne. 0.) then       &                    (ubar(i,j,k,bi,bj) - OBEu(j,k,bi,bj))
206                    tmpx = tmpfield(j,k,bi,bj)                    endif
207                    fctile = fctile                 enddo
      &                 + wobcseLev(j,k,bi,bj,iobcs)*cosphi(i,j,bi,bj)  
      &                 *tmpx*tmpx  
      &                 *maskyz(j,k,bi,bj)  
 cgg                endif  
               enddo  
208              enddo              enddo
209    c--         End of loop over layers.
210                fcthread         = fcthread           + fctile
211                objf_obcse(bi,bj) = objf_obcse(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 mdsreadfieldyz( OBEvFile, readBinaryPrec, 'RS',
227         &                       nr, OBEv, 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 j = jmin,jmax
237                      i = OB_Ie(J,bi,bj)
238                      if (maskS(i,j,k,bi,bj) .ne. 0.) then
239                         fctile = fctile +
240         &                    wobcse(k,iobcs)*cosphi(i,j,bi,bj)*
241         &                    (vbar(i,j,k,bi,bj) - OBEv(j,k,bi,bj))*
242         &                    (vbar(i,j,k,bi,bj) - OBEv(j,k,bi,bj))
243                      endif
244                   enddo
245                enddo
246    c--         End of loop over layers.
247                fcthread         = fcthread           + fctile
248              objf_obcse(bi,bj) = objf_obcse(bi,bj) + fctile              objf_obcse(bi,bj) = objf_obcse(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