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

Diff of /MITgcm_contrib/SOSE/BoxAdj/code_ad/ctrl_getobcsw.F

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

revision 1.4 by mmazloff, Wed Jan 19 12:47:11 2011 UTC revision 1.5 by mmazloff, Wed Jan 19 21:08:32 2011 UTC
# Line 1  Line 1 
1    C $Header$
2    C $Name$
3    
4  #include "CTRL_CPPOPTIONS.h"  #include "CTRL_CPPOPTIONS.h"
5  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
# Line 65  c     == local variables == Line 67  c     == local variables ==
67        logical obcswchanged        logical obcswchanged
68        integer obcswcount0        integer obcswcount0
69        integer obcswcount1        integer obcswcount1
70  cih            integer nk,nz
       Integer nk,nz  
71        _RL     tmpz (nr,nsx,nsy)        _RL     tmpz (nr,nsx,nsy)
72        _RL     stmp        _RL     stmp
73        character*(80) fnamein  
74  cih  cgg      _RL maskyz   (1-oly:sny+oly,nr,nsx,nsy)
75    
76        logical doglobalread        logical doglobalread
77        logical ladinit        logical ladinit
78    
79        character*(80) fnameobcsw        character*(80) fnameobcsw
80    
81    cgg(  Variables for splitting barotropic/baroclinic vels.
82          _RL ubaro
83          _RL utop
84    cgg)
85    
86  c     == external functions ==  c     == external functions ==
87    
# Line 95  c     == end of interface == Line 101  c     == end of interface ==
101        imax = snx+olx        imax = snx+olx
102        ip1  = 1        ip1  = 1
103    
104    cgg(  Initialize variables for balancing volume flux.
105          ubaro = 0.d0
106          utop = 0.d0
107    cgg)
108    
109  c--   Now, read the control vector.  c--   Now, read the control vector.
110        doglobalread = .false.        doglobalread = .false.
# Line 102  c--   Now, read the control vector. Line 112  c--   Now, read the control vector.
112    
113        if (optimcycle .ge. 0) then        if (optimcycle .ge. 0) then
114          ilobcsw=ilnblnk( xx_obcsw_file )          ilobcsw=ilnblnk( xx_obcsw_file )
115          write(fnameobcsw(1:80),'(2a,i10.10)')          write(fnameobcsw(1:80),'(2a,i10.10)')
116       &       xx_obcsw_file(1:ilobcsw), '.', optimcycle       &       xx_obcsw_file(1:ilobcsw), '.', optimcycle
117        endif        endif
118    
# Line 112  c--   Get the counters, flags, and the i Line 122  c--   Get the counters, flags, and the i
122       O                   obcswfac, obcswfirst, obcswchanged,       O                   obcswfac, obcswfirst, obcswchanged,
123       O                   obcswcount0,obcswcount1,       O                   obcswcount0,obcswcount1,
124       I                   mytime, myiter, mythid )       I                   mytime, myiter, mythid )
125  cih  
126        do iobcs = 1,nobcs        do iobcs = 1,nobcs
127          if ( obcswfirst ) then          if ( obcswfirst ) then
128            call active_read_yz( fnameobcsw, tmpfldyz,            call active_read_yz( fnameobcsw, tmpfldyz,
129       &                         (obcswcount0-1)*nobcs+iobcs,       &                         (obcswcount0-1)*nobcs+iobcs,
130       &                         doglobalread, ladinit, optimcycle,       &                         doglobalread, ladinit, optimcycle,
131       &                         mythid, xx_obcsw_dummy )       &                         mythid, xx_obcsw_dummy )
132  cnma Here we go into the modes' space  
133  #ifdef ALLOW_OBCS_CONTROL_MODES  
134  cih            if ( optimcycle .gt. 0) then
           if ( optimcycle .ge. 0) then  
 cih    If normal velocity                  
135              if (iobcs .eq. 3) then              if (iobcs .eq. 3) then
136  cih    Begin loop over y-points.  cgg         Special attention is needed for the normal velocity.
137    cgg         For the north, this is the v velocity, iobcs = 4.
138    cgg         This is done on a columnwise basis here.
139                do bj = jtlo,jthi                do bj = jtlo,jthi
140                  do bi = itlo, ithi                  do bi = itlo, ithi
141                    do j = jmin,jmax                    do j = jmin,jmax
142  cih    If open boundary.  cih    If open boundary.
143                       if ( OB_Iw(j,bi,bj) .ne. 0. ) then                       if ( OB_Iw(j,bi,bj) .ne. 0. ) then
144                          i = OB_Iw(j,bi,bj)                      i = OB_Iw(J,bi,bj)
145    #ifdef ALLOW_OBCS_CONTROL_MODES
146  cih    Determine number of open vertical layers.  cih    Determine number of open vertical layers.
147                             nz = 0                             nz = 0
148                             do k = 1,Nr                             do k = 1,Nr
149                                nz = nz + maskW(i+ip1,j,k,bi,bj)                                nz = nz + maskW(i+ip1,j,k,bi,bj)
150                             end do                             end do
151  cih    Compute absolute velocities from the barotropic-baroclinic modes.  cih    Compute absolute velocities from the barotropic-baroclinic modes.
152    #ifdef ALLOW_CTRL_OBCS_BALANCE
153    CMM not sure if ALLOW_OBCS_CONTROL_MODES and ALLOW_CTRL_OBCS_BALANCE are
154    c     compatible - to ensure volume conservation can just set barotropic
155    c     mode amplitude to 0
156    c     however this means no inflow at every horizontal location....
157                       do k = 1,nr
158                         tmpfldyz(k,1,bi,bj)= 0.
159                       end do
160    #endif
161                             do k = 1,Nr                             do k = 1,Nr
162                               if (k.le.nz) then                               if (k.le.nz) then
163                                  stmp = 0.                                  stmp = 0.
164                                  do nk = 1,nz                                  do nk = 1,nz
165                                   stmp = stmp +                                   stmp = stmp +
166       &                            modesv(k,nk,nz)*tmpfldyz(j,nk,bi,bj)       &                            modesv(k,nk,nz)*tmpfldyz(j,nk,bi,bj)
167                                  end do                                  end do
168                                  tmpz(k,bi,bj) = stmp                                  tmpz(k,bi,bj) = stmp
169                               else                               else
170                                  tmpz(k,bi,bj) = 0.                                  tmpz(k,bi,bj) = 0.
171                               end if                               end if
172                             end do                               end do
173                             do k = 1,Nr                             do k = 1,Nr
174                          tmpfldyz(j,k,bi,bj) = tmpz(k,bi,bj)                          tmpfldyz(j,k,bi,bj) = tmpz(k,bi,bj)
175       &                           *recip_hFacW(i+ip1,j,k,bi,bj)       &                           *recip_hFacW(i+ip1,j,k,bi,bj)
176                             end do                                             end do  
177    #elif defined (ALLOW_CTRL_OBCS_BALANCE)
178    cgg         The barotropic velocity is stored in the level 1.
179                        ubaro = tmpfldyz(j,1,bi,bj)
180                        tmpfldyz(j,1,bi,bj) = 0.d0
181                        utop = 0.d0
182    
183                        do k = 1,Nr
184    cgg    If cells are not full, this should be modified with hFac.
185    cgg
186    cgg    The xx field (tmpfldxz) does not contain the velocity at the
187    cgg    surface level. This velocity is not independent; it must
188    cgg    exactly balance the volume flux, since we are dealing with
189    cgg    the baroclinic velocity structure..
190                          utop = tmpfldyz(j,k,bi,bj)*
191         &                maskW(i+ip1,j,k,bi,bj) * delR(k) + utop
192    cgg    Add the barotropic velocity component.
193                          if (maskW(i+ip1,j,k,bi,bj) .ne. 0.) then
194                            tmpfldyz(j,k,bi,bj) = tmpfldyz(j,k,bi,bj)+ ubaro
195                          endif
196                        enddo
197    cgg    Compute the baroclinic velocity at level 1. Should balance flux.
198                      tmpfldyz(j,1,bi,bj) = tmpfldyz(j,1,bi,bj)
199         &                                      - utop / delR(1)
200    #endif
201  cih    End open boundary.  cih    End open boundary.
202                          end if                                                  end if
203  cih    End loop over x-points                    enddo
204                       end do                  enddo
205                    end do                enddo
206                 end do              endif
 cih    End if iobcs = 3.  
             end if        
 cih  
 cih    If tangential velocity                  
207              if (iobcs .eq. 4) then              if (iobcs .eq. 4) then
208  cih    Begin loop over y-points.  cgg         Special attention is needed for the normal velocity.
209    cgg         For the north, this is the v velocity, iobcs = 4.
210    cgg         This is done on a columnwise basis here.
211                do bj = jtlo,jthi                do bj = jtlo,jthi
212                  do bi = itlo, ithi                  do bi = itlo, ithi
213                    do j = jmin,jmax                    do j = jmin,jmax
214  cih    If open boundary.  cih    If open boundary.
215                       if ( OB_Iw(j,bi,bj) .ne. 0. ) then                       if ( OB_Iw(j,bi,bj) .ne. 0. ) then
216                          i = OB_Iw(j,bi,bj)                      i = OB_Iw(J,bi,bj)
217    #ifdef ALLOW_OBCS_CONTROL_MODES
218  cih    Determine number of open vertical layers.  cih    Determine number of open vertical layers.
219                             nz = 0                             nz = 0
220                             do k = 1,Nr                             do k = 1,Nr
221                                nz = nz + maskS(i,j,k,bi,bj)                                nz = nz + maskS(i,j,k,bi,bj)
222                             end do                             end do
223  cih    Compute absolute velocities from the barotropic-baroclinic modes.  cih    Compute absolute velocities from the barotropic-baroclinic modes.
224    #ifdef ALLOW_CTRL_OBCS_BALANCE
225    CMM not sure if ALLOW_OBCS_CONTROL_MODES and ALLOW_CTRL_OBCS_BALANCE are
226    c     compatible - to ensure volume conservation can just set barotropic
227    c     mode amplitude to 0
228    c     however this means no inflow at every horizontal location....
229                       do k = 1,nr
230                         tmpfldyz(k,1,bi,bj)= 0.
231                       end do
232    #endif
233                             do k = 1,Nr                             do k = 1,Nr
234                               if (k.le.nz) then                               if (k.le.nz) then
235                                  stmp = 0.                                  stmp = 0.
236                                  do nk = 1,nz                                  do nk = 1,nz
237                                   stmp = stmp +                                   stmp = stmp +
238       &                            modesv(k,nk,nz)*tmpfldyz(j,nk,bi,bj)       &                            modesv(k,nk,nz)*tmpfldyz(j,nk,bi,bj)
239                                  end do                                  end do
240                                  tmpz(k,bi,bj) = stmp                                  tmpz(k,bi,bj) = stmp
241                               else                               else
242                                  tmpz(k,bi,bj) = 0.                                  tmpz(k,bi,bj) = 0.
243                               end if                               end if
244                             end do                               end do  
245                             do k = 1,Nr                             do k = 1,Nr
246                          tmpfldyz(j,k,bi,bj) = tmpz(k,bi,bj)                          tmpfldyz(j,k,bi,bj) = tmpz(k,bi,bj)
247       &                           *recip_hFacS(i,j,k,bi,bj)       &                           *recip_hFacS(i,j,k,bi,bj)
248                             end do                                             end do
249  cih    End open boundary.  #elif defined (ALLOW_CTRL_OBCS_BALANCE)
250                          end if                          cgg         The barotropic velocity is stored in the level 1.
251  cih    End loop over x-points                      ubaro = tmpfldyz(j,1,bi,bj)
252                       end do                      tmpfldyz(j,1,bi,bj) = 0.d0
253                    end do                      utop = 0.d0
254                 end do  
255                        do k = 1,Nr
256    cgg    If cells are not full, this should be modified with hFac.
257    cgg
258    cgg    The xx field (tmpfldxz) does not contain the velocity at the
259    cgg    surface level. This velocity is not independent; it must
260    cgg    exactly balance the volume flux, since we are dealing with
261    cgg    the baroclinic velocity structure..
262                          utop = tmpfldyz(j,k,bi,bj)*
263         &                maskS(i,j,k,bi,bj) * delR(k) + utop
264    cgg    Add the barotropic velocity component.
265                          if (maskS(i,j,k,bi,bj) .ne. 0.) then
266                            tmpfldyz(j,k,bi,bj) = tmpfldyz(j,k,bi,bj)+ ubaro
267                          endif
268                        enddo
269    cgg    Compute the baroclinic velocity at level 1. Should balance flux.
270                      tmpfldyz(j,1,bi,bj) = tmpfldyz(j,1,bi,bj)
271         &                                      - utop / delR(1)
272    #endif
273  cih    End if iobcs = 4.  cih    End if iobcs = 4.
274              end if              end if
275  cih    End if optimcycle > 0 .                      enddo
276           end if                  enddo
277  cnma                enddo
278  #endif                    endif
279  cih            endif
280    
281            do bj = jtlo,jthi            do bj = jtlo,jthi
282              do bi = itlo,ithi              do bi = itlo,ithi
283                do k = 1,nr                do k = 1,nr
284                  do j = jmin,jmax                  do j = jmin,jmax
285                    xx_obcsw1(j,k,bi,bj,iobcs)  = tmpfldyz (j,k,bi,bj)                    xx_obcsw1(j,k,bi,bj,iobcs)  = tmpfldyz (j,k,bi,bj)
286    cgg     &                                        *   maskyz (j,k,bi,bj)
287                   enddo                   enddo
288                enddo                enddo
289              enddo              enddo
290            enddo            enddo
 cih     End if obcswfirst  
291          endif          endif
292  cih  
293          if ( (obcswfirst) .or. (obcswchanged) ) then            if ( (obcswfirst) .or. (obcswchanged)) then
294  cih          
           do bj = jtlo,jthi  
             do bi = itlo,ithi  
               do k = 1,nr  
                 do j = jmin,jmax  
                   tmpfldyz(j,k,bi,bj) = xx_obcsw1(j,k,bi,bj,iobcs)  
                 enddo  
               enddo  
             enddo  
           enddo  
 cih          
           call exf_swapffields_yz( tmpfldyz2, tmpfldyz, mythid)  
 cih          
295            do bj = jtlo,jthi            do bj = jtlo,jthi
296              do bi = itlo,ithi             do bi = itlo,ithi
297                do k = 1,nr              do k = 1,nr
298                  do j = jmin,jmax               do j = jmin,jmax
299                    xx_obcsw0(j,k,bi,bj,iobcs) = tmpfldyz2(j,k,bi,bj)                xx_obcsw0(j,k,bi,bj,iobcs) = xx_obcsw1(j,k,bi,bj,iobcs)
300                  enddo                tmpfldyz (j,k,bi,bj)       = 0. _d 0
301                enddo               enddo
302              enddo              enddo
303               enddo
304            enddo            enddo
305  cih          
306            call active_read_yz( fnameobcsw, tmpfldyz,            call active_read_yz( fnameobcsw, tmpfldyz,
307       &                         (obcswcount1-1)*nobcs+iobcs,       &                         (obcswcount1-1)*nobcs+iobcs,
308       &                         doglobalread, ladinit, optimcycle,       &                         doglobalread, ladinit, optimcycle,
309       &                         mythid, xx_obcsw_dummy )       &                         mythid, xx_obcsw_dummy )
310  cnma  
311  #ifdef ALLOW_OBCS_CONTROL_MODES            if ( optimcycle .gt. 0) then
 cih          
           if ( optimcycle .ge. 0) then  
 cih    If normal velocity                  
312              if (iobcs .eq. 3) then              if (iobcs .eq. 3) then
313  cih    Begin loop over y-points.  cgg         Special attention is needed for the normal velocity.
314    cgg         For the north, this is the v velocity, iobcs = 4.
315    cgg         This is done on a columnwise basis here.
316                do bj = jtlo,jthi                do bj = jtlo,jthi
317                  do bi = itlo, ithi                  do bi = itlo, ithi
318                    do j = jmin,jmax                    do j = jmin,jmax
319  cih    If open boundary.  cih    If open boundary.
320                       if ( OB_Iw(j,bi,bj) .ne. 0. ) then                       if ( OB_Iw(j,bi,bj) .ne. 0. ) then
321                          i = OB_Iw(j,bi,bj)                      i = OB_Iw(J,bi,bj)
322    #ifdef ALLOW_OBCS_CONTROL_MODES
323  cih    Determine number of open vertical layers.  cih    Determine number of open vertical layers.
324                             nz = 0                             nz = 0
325                             do k = 1,Nr                             do k = 1,Nr
326                                nz = nz + maskW(i+ip1,j,k,bi,bj)                                nz = nz + maskW(i+ip1,j,k,bi,bj)
327                             end do                             end do
328  cih    Compute absolute velocities from the barotropic-baroclinic modes.  cih    Compute absolute velocities from the barotropic-baroclinic modes.
329    #ifdef ALLOW_CTRL_OBCS_BALANCE
330    CMM not sure if ALLOW_OBCS_CONTROL_MODES and ALLOW_CTRL_OBCS_BALANCE are
331    c     compatible - to ensure volume conservation can just set barotropic
332    c     mode amplitude to 0
333    c     however this means no inflow at every horizontal location....
334                       do k = 1,nr
335                         tmpfldyz(k,1,bi,bj)= 0.
336                       end do
337    #endif
338                             do k = 1,Nr                             do k = 1,Nr
339                               if (k.le.nz) then                               if (k.le.nz) then
340                                  stmp = 0.                                  stmp = 0.
341                                  do nk = 1,nz                                  do nk = 1,nz
342                                   stmp = stmp +                                   stmp = stmp +
343       &                            modesv(k,nk,nz)*tmpfldyz(j,nk,bi,bj)       &                            modesv(k,nk,nz)*tmpfldyz(j,nk,bi,bj)
344                                  end do                                  end do
345                                  tmpz(k,bi,bj) = stmp                                  tmpz(k,bi,bj) = stmp
346                               else                               else
347                                  tmpz(k,bi,bj) = 0.                                  tmpz(k,bi,bj) = 0.
348                               end if                               end if
349                             end do                               end do
350                             do k = 1,Nr                             do k = 1,Nr
351                          tmpfldyz(j,k,bi,bj) = tmpz(k,bi,bj)                          tmpfldyz(j,k,bi,bj) = tmpz(k,bi,bj)
352       &                           *recip_hFacW(i+ip1,j,k,bi,bj)       &                           *recip_hFacW(i+ip1,j,k,bi,bj)
353                             end do                                             end do  
354    #elif defined (ALLOW_CTRL_OBCS_BALANCE)
355    cgg         The barotropic velocity is stored in the level 1.
356                        ubaro = tmpfldyz(j,1,bi,bj)
357                        tmpfldyz(j,1,bi,bj) = 0.d0
358                        utop = 0.d0
359    
360                        do k = 1,Nr
361    cgg    If cells are not full, this should be modified with hFac.
362    cgg
363    cgg    The xx field (tmpfldxz) does not contain the velocity at the
364    cgg    surface level. This velocity is not independent; it must
365    cgg    exactly balance the volume flux, since we are dealing with
366    cgg    the baroclinic velocity structure..
367                          utop = tmpfldyz(j,k,bi,bj)*
368         &                maskW(i+ip1,j,k,bi,bj) * delR(k) + utop
369    cgg    Add the barotropic velocity component.
370                          if (maskW(i+ip1,j,k,bi,bj) .ne. 0.) then
371                            tmpfldyz(j,k,bi,bj) = tmpfldyz(j,k,bi,bj)+ ubaro
372                          endif
373                        enddo
374    cgg    Compute the baroclinic velocity at level 1. Should balance flux.
375                      tmpfldyz(j,1,bi,bj) = tmpfldyz(j,1,bi,bj)
376         &                                      - utop / delR(1)
377    #endif
378  cih    End open boundary.  cih    End open boundary.
379                          end if                                                  end if
380  cih    End loop over x-points                    enddo
381                       end do                  enddo
382                    end do                enddo
383                 end do              endif
 cih    End if iobcs = 3.  
             end if        
 cih  
 cih    If tangential velocity                  
384              if (iobcs .eq. 4) then              if (iobcs .eq. 4) then
385  cih    Begin loop over y-points.  cgg         Special attention is needed for the normal velocity.
386    cgg         For the north, this is the v velocity, iobcs = 4.
387    cgg         This is done on a columnwise basis here.
388                do bj = jtlo,jthi                do bj = jtlo,jthi
389                  do bi = itlo, ithi                  do bi = itlo, ithi
390                    do j = jmin,jmax                    do j = jmin,jmax
391  cih    If open boundary.  cih    If open boundary.
392                       if ( OB_Iw(j,bi,bj) .ne. 0. ) then                       if ( OB_Iw(j,bi,bj) .ne. 0. ) then
393                          i = OB_Iw(j,bi,bj)                      i = OB_Iw(J,bi,bj)
394    #ifdef ALLOW_OBCS_CONTROL_MODES
395  cih    Determine number of open vertical layers.  cih    Determine number of open vertical layers.
396                             nz = 0                             nz = 0
397                             do k = 1,Nr                             do k = 1,Nr
398                                nz = nz + maskS(i,j,k,bi,bj)                                nz = nz + maskS(i,j,k,bi,bj)
399                             end do                             end do
400  cih    Compute absolute velocities from the barotropic-baroclinic modes.  cih    Compute absolute velocities from the barotropic-baroclinic modes.
401    #ifdef ALLOW_CTRL_OBCS_BALANCE
402    CMM not sure if ALLOW_OBCS_CONTROL_MODES and ALLOW_CTRL_OBCS_BALANCE are
403    c     compatible - to ensure volume conservation can just set barotropic
404    c     mode amplitude to 0
405    c     however this means no inflow at every horizontal location....
406                       do k = 1,nr
407                         tmpfldyz(k,1,bi,bj)= 0.
408                       end do
409    #endif
410                             do k = 1,Nr                             do k = 1,Nr
411                               if (k.le.nz) then                               if (k.le.nz) then
412                                  stmp = 0.                                  stmp = 0.
413                                  do nk = 1,nz                                  do nk = 1,nz
414                                   stmp = stmp +                                   stmp = stmp +
415       &                             modesv(k,nk,nz)*tmpfldyz(j,nk,bi,bj)       &                            modesv(k,nk,nz)*tmpfldyz(j,nk,bi,bj)
416                                  end do                                  end do
417                                  tmpz(k,bi,bj) = stmp                                  tmpz(k,bi,bj) = stmp
418                               else                               else
419                                  tmpz(k,bi,bj) = 0.                                  tmpz(k,bi,bj) = 0.
420                               end if                               end if
421                             end do                             end do  
422                             do k = 1,Nr                             do k = 1,Nr
423                          tmpfldyz(j,k,bi,bj) = tmpz(k,bi,bj)                          tmpfldyz(j,k,bi,bj) = tmpz(k,bi,bj)
424       &                           *recip_hFacS(i,j,k,bi,bj)       &                           *recip_hFacS(i,j,k,bi,bj)
425                             end do                                               end do
426  cih    End open boundary.  #elif defined (ALLOW_CTRL_OBCS_BALANCE)
427                          end if                          cgg         The barotropic velocity is stored in the level 1.
428  cih    End loop over x-points                      ubaro = tmpfldyz(j,1,bi,bj)
429                       end do                      tmpfldyz(j,1,bi,bj) = 0.d0
430                    end do                      utop = 0.d0
431                 end do  
432  cih    End if iobcs = 4.                      do k = 1,Nr
433              end if  cgg    If cells are not full, this should be modified with hFac.
434  cih    End if optimcycle > 0 .    cgg
435           end if        cgg    The xx field (tmpfldxz) does not contain the velocity at the
436  cnma  cgg    surface level. This velocity is not independent; it must
437    cgg    exactly balance the volume flux, since we are dealing with
438    cgg    the baroclinic velocity structure..
439                          utop = tmpfldyz(j,k,bi,bj)*
440         &                maskS(i,j,k,bi,bj) * delR(k) + utop
441    cgg    Add the barotropic velocity component.
442                          if (maskS(i,j,k,bi,bj) .ne. 0.) then
443                            tmpfldyz(j,k,bi,bj) = tmpfldyz(j,k,bi,bj)+ ubaro
444                          endif
445                        enddo
446    cgg    Compute the baroclinic velocity at level 1. Should balance flux.
447                      tmpfldyz(j,1,bi,bj) = tmpfldyz(j,1,bi,bj)
448         &                                      - utop / delR(1)
449  #endif  #endif
450  cih  cih    End if iobcs = 4.
451                end if
452                      enddo
453                    enddo
454                  enddo
455                endif
456              endif
457    
458            do bj = jtlo,jthi            do bj = jtlo,jthi
459              do bi = itlo,ithi              do bi = itlo,ithi
460                do k = 1,nr                do k = 1,nr
461                  do j = jmin,jmax                  do j = jmin,jmax
462                    xx_obcsw1 (j,k,bi,bj,iobcs) = tmpfldyz (j,k,bi,bj)                    xx_obcsw1 (j,k,bi,bj,iobcs) = tmpfldyz (j,k,bi,bj)
463    cgg     &                                        *   maskyz (j,k,bi,bj)
464                   enddo                   enddo
465                enddo                enddo
466              enddo              enddo
467            enddo            enddo
 cih     End if obcswfirst .or. obcswchanged  
468          endif          endif
469    
470  c--     Add control to model variable.  c--     Add control to model variable.

Legend:
Removed from v.1.4  
changed lines
  Added in v.1.5

  ViewVC Help
Powered by ViewVC 1.1.22