/[MITgcm]/MITgcm/pkg/grdchk/grdchk_main.F
ViewVC logotype

Diff of /MITgcm/pkg/grdchk/grdchk_main.F

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

revision 1.3 by heimbach, Fri Sep 28 16:53:46 2001 UTC revision 1.3.6.5 by heimbach, Fri Jun 20 19:38:59 2003 UTC
# Line 54  c     ================================== Line 54  c     ==================================
54  c     o Compare the gradients calculated by the adjoint model with  c     o Compare the gradients calculated by the adjoint model with
55  c       finite difference approximations.  c       finite difference approximations.
56  c     started: Christian Eckert eckert@mit.edu 24-Feb-2000  c     started: Christian Eckert eckert@mit.edu 24-Feb-2000
57  c     continued: heimbach@mit.edu: 13-Jun-2001  c     continued&finished: heimbach@mit.edu: 13-Jun-2001
58    c     changed: mlosch@ocean.mit.edu: 09-May-2002
59    c              - added centered difference vs. 1-sided difference option
60    c              - improved output format for readability
61    c              - added control variable hFacC
62    c              heimbach@mit.edu 24-Feb-2003
63    c              - added tangent linear gradient checks
64    c              - fixes for multiproc. gradient checks
65    c              - added more control variables
66    c    
67  c     ==================================================================  c     ==================================================================
68  c     SUBROUTINE grdchk_main  c     SUBROUTINE grdchk_main
69  c     ==================================================================  c     ==================================================================
# Line 85  c     == local variables == Line 94  c     == local variables ==
94        integer j,  jmin, jmax        integer j,  jmin, jmax
95        integer k        integer k
96    
       integer jprocs  
       integer proc_grdchk  
97        integer icomp        integer icomp
98        integer ichknum        integer ichknum
99        integer icvrec        integer icvrec
100        integer jtile        integer jtile
101        integer itile        integer itile
102        integer layer        integer layer
103          integer obcspos
104        integer itilepos        integer itilepos
105        integer jtilepos        integer jtilepos
106        integer itest        integer itest
# Line 100  c     == local variables == Line 108  c     == local variables ==
108        integer ierr_grdchk        integer ierr_grdchk
109        _RL     gfd        _RL     gfd
110        _RL     fcref        _RL     fcref
111        _RL     fcpert        _RL     fcpertplus, fcpertminus
112        _RL     ratio        _RL     ratio_ad
113          _RL     ratio_ftl
114        _RL     xxmemo_ref        _RL     xxmemo_ref
115        _RL     xxmemo_pert        _RL     xxmemo_pert
116        _RL     adxxmemo        _RL     adxxmemo
117          _RL     ftlxxmemo
118          _RL     localEps
119          _RL     grdchk_epsfac
120    
 cph(  
121        _RL tmpplot1(1-olx:snx+olx,1-oly:sny+oly,nr,nsx,nsy)        _RL tmpplot1(1-olx:snx+olx,1-oly:sny+oly,nr,nsx,nsy)
122        _RL tmpplot2(1-olx:snx+olx,1-oly:sny+oly,nr,nsx,nsy)        _RL tmpplot2(1-olx:snx+olx,1-oly:sny+oly,nr,nsx,nsy)
123  cph)        _RL tmpplot3(1-olx:snx+olx,1-oly:sny+oly,nr,nsx,nsy)
124    
125    #ifdef ALLOW_TANGENTLINEAR_RUN
126          _RL     g_fc
127          common /g_cost_r/ g_fc
128    #endif
129    
130  c     == end of interface ==  c     == end of interface ==
131  CEOP  CEOP
# Line 136  cph   assuming all xx_ fields are initia Line 152  cph   assuming all xx_ fields are initia
152        fcref = fc        fcref = fc
153        ierr_grdchk = 0        ierr_grdchk = 0
154    
 cph(  
155        do bj = jtlo, jthi        do bj = jtlo, jthi
156           do bi = itlo, ithi           do bi = itlo, ithi
157              do k = 1, nr              do k = 1, nr
# Line 144  cph( Line 159  cph(
159                    do i = imin, imax                    do i = imin, imax
160                       tmpplot1(i,j,k,bi,bj) = 0. _d 0                       tmpplot1(i,j,k,bi,bj) = 0. _d 0
161                       tmpplot2(i,j,k,bi,bj) = 0. _d 0                       tmpplot2(i,j,k,bi,bj) = 0. _d 0
162                         tmpplot3(i,j,k,bi,bj) = 0. _d 0
163                    end do                    end do
164                 end do                 end do
165              end do              end do
166           end do           end do
167        end do        end do
168  cph)  
169          if ( useCentralDiff ) then
170             grdchk_epsfac = 2. _d 0
171          else
172             grdchk_epsfac = 1. _d 0
173          end if
174    
175          print *, 'ph-grd 3 -------------------------------'
176          print ('(2a)'),
177         &     ' ph-grd 3  proc    #    i    j    k            fc ref',
178         &     '        fc + eps        fc - eps'
179    #ifdef ALLOW_TANGENTLINEAR_RUN
180          print ('(2a)'),
181         &     ' ph-grd 3  proc    #    i    j    k          tlm grad',
182         &     '         fd grad      1 - fd/tlm'
183    #else
184          print ('(2a)'),
185         &     ' ph-grd 3  proc    #    i    j    k          adj grad',
186         &     '         fd grad      1 - fd/adj'
187    #endif
188    
189  c--   Compute the finite difference approximations.  c--   Compute the finite difference approximations.
190  c--   Cycle through all processes doing NINT(nend-nbeg+1)/nstep  c--   Cycle through all processes doing NINT(nend-nbeg+1)/nstep
191  c--   gradient checks.  c--   gradient checks.
       do jprocs = 1,numberOfProcs  
          proc_grdchk = jprocs - 1  
   
          if ( myProcId .eq. proc_grdchk ) then  
192    
193              do icomp = nbeg, nend, nstep        do icomp = nbeg, nend, nstep
194    
195                 ichknum = (icomp - nbeg)/nstep + 1           ichknum = (icomp - nbeg)/nstep + 1
196    
197                 if (ichknum .le. maxgrdchecks ) then           if (ichknum .le. maxgrdchecks ) then
198    
199  c--         Determine the location of icomp on the grid.  c--         Determine the location of icomp on the grid.
200                    call grdchk_loc( icomp, ichknum,              if ( myProcId .EQ. grdchkwhichproc ) then
201       &                 icvrec, itile, jtile, layer,                 call grdchk_loc( icomp, ichknum,
202       &                 itilepos, jtilepos, itest, ierr,       &              icvrec, itile, jtile, layer, obcspos,
203       &                 mythid )       &              itilepos, jtilepos, itest, ierr,
204         &              mythid )
205                endif
206                _BARRIER
207                                
208                    if ( ierr .eq. 0 ) then  c******************************************************
209    c--   (A): get gradient component calculated via adjoint
210    c******************************************************
211    
212    c--   get gradient component calculated via adjoint
213                if ( myProcId .EQ. grdchkwhichproc .AND.
214         &           ierr .EQ. 0 ) then
215                   call grdchk_getadxx( icvrec,
216         &              itile, jtile, layer,
217         &              itilepos, jtilepos,
218         &              adxxmemo, mythid )
219                endif
220                _BARRIER
221    
222    #ifdef ALLOW_TANGENTLINEAR_RUN
223    c******************************************************
224    c--   (B): Get gradient component g_fc from tangent linear run:
225    c******************************************************
226    c--
227    c--   1. perturb control vector component: xx(i)=1.
228    
229                if ( myProcId .EQ. grdchkwhichproc .AND.
230         &           ierr .EQ. 0 ) then
231                   localEps = 1. _d 0
232                   call grdchk_getxx( icvrec, TANGENT_SIMULATION,
233         &              itile, jtile, layer,
234         &              itilepos, jtilepos,
235         &              xxmemo_ref, xxmemo_pert, localEps,
236         &              mythid )
237                endif
238                _BARRIER
239    
240    c--
241    c--   2. perform tangent linear run
242                mytime = starttime
243                myiter = niter0
244                g_fc = 0.
245                call g_the_main_loop( mytime, myiter, mythid )
246                ftlxxmemo = g_fc
247                _BARRIER
248    c--
249    c--   3. reset control vector
250                if ( myProcId .EQ. grdchkwhichproc .AND.
251         &           ierr .EQ. 0 ) then
252                   call grdchk_setxx( icvrec, TANGENT_SIMULATION,
253         &              itile, jtile, layer,
254         &              itilepos, jtilepos,
255         &              xxmemo_ref, mythid )
256                endif
257                _BARRIER
258    
259    #endif /* ALLOW_TANGENTLINEAR_RUN */
260    
261    
262    c******************************************************
263    c--   (C): Get gradient via finite difference perturbation
264    c******************************************************
265    
266  c--   get control vector component from file  c--   get control vector component from file
267  c--   perturb it and write back to file  c--   perturb it and write back to file
268                       call grdchk_getxx( icvrec,  c--   positive perturbation
269       &                    itile, jtile, layer,              localEps = abs(grdchk_eps)
270       &                    itilepos, jtilepos,              if ( myProcId .EQ. grdchkwhichproc .AND.
271       &                    xxmemo_ref, xxmemo_pert, mythid )       &           ierr .EQ. 0 ) then
272                       _BARRIER                 call grdchk_getxx( icvrec, FORWARD_SIMULATION,
273         &              itile, jtile, layer,
274         &              itilepos, jtilepos,
275         &              xxmemo_ref, xxmemo_pert, localEps,
276         &              mythid )
277                endif
278                _BARRIER
279                                            
 c--   get gradient component calculated via adjoint  
                      call grdchk_getadxx( icvrec,  
      &                    itile, jtile, layer,  
      &                    itilepos, jtilepos,  
      &                    adxxmemo, mythid )  
                      _BARRIER  
   
280  c--   forward run with perturbed control vector  c--   forward run with perturbed control vector
281                       mytime = starttime              mytime = starttime
282                       myiter = niter0              myiter = niter0
283                       call the_main_loop( mytime, myiter, mythid )              call the_main_loop( mytime, myiter, mythid )
284                       fcpert = fc              fcpertplus = fc
285                _BARRIER
286                                        
287                       if ( grdchk_eps .eq. 0. ) then  c--   Reset control vector.
288                          gfd = (fcpert-fcref)              if ( myProcId .EQ. grdchkwhichproc .AND.
289                       else       &           ierr .EQ. 0 ) then
290                          gfd = (fcpert-fcref)/grdchk_eps                 call grdchk_setxx( icvrec, FORWARD_SIMULATION,
291                       endif       &              itile, jtile, layer,
292         &              itilepos, jtilepos,
293         &              xxmemo_ref, mythid )
294                endif
295                _BARRIER
296    
297                fcpertminus = fcref
298    
299                if ( useCentralDiff ) then
300    
301    c--   get control vector component from file
302    c--   perturb it and write back to file
303    c--   repeat the proceedure for a negative perturbation
304                   if ( myProcId .EQ. grdchkwhichproc .AND.
305         &           ierr .EQ. 0 ) then
306                      localEps = - abs(grdchk_eps)
307                      call grdchk_getxx( icvrec, FORWARD_SIMULATION,
308         &                 itile, jtile, layer,
309         &                 itilepos, jtilepos,
310         &                 xxmemo_ref, xxmemo_pert, localEps,
311         &                 mythid )
312                   endif
313                   _BARRIER
314                                            
315                       if ( gfd .eq. 0. ) then  c--   forward run with perturbed control vector
316                          ratio = abs( adxxmemo - gfd )                 mytime = starttime
317                       else                 myiter = niter0
318                          ratio = 1. - adxxmemo/gfd                 call the_main_loop( mytime, myiter, mythid )
319                       endif                 _BARRIER
320                   fcpertminus = fc
321                                        
322  c--   Reset control vector.  c--   Reset control vector.
323                       call grdchk_setxx( icvrec,                 if ( myProcId .EQ. grdchkwhichproc .AND.
324       &                    itile, jtile, layer,       &           ierr .EQ. 0 ) then
325       &                    itilepos, jtilepos,                    call grdchk_setxx( icvrec, FORWARD_SIMULATION,
326       &                    xxmemo_ref, mythid )       &                 itile, jtile, layer,
327                       _BARRIER       &                 itilepos, jtilepos,
328         &                 xxmemo_ref, mythid )
329  cph(                 endif
330                       tmpplot1(itilepos,jtilepos,layer,itile,jtile) =                 _BARRIER
331       &                    gfd  
332                       tmpplot2(itilepos,jtilepos,layer,itile,jtile) =  c-- end of if useCentralDiff ...
333       &                    ratio              end if
334  cph)  
335    c******************************************************
336    c--   (D): calculate relative differences between gradients
337    c******************************************************
338    
339                if ( myProcId .EQ. grdchkwhichproc .AND.
340         &           ierr .EQ. 0 ) then
341    
342                   if ( grdchk_eps .eq. 0. ) then
343                      gfd = (fcpertplus-fcpertminus)
344                   else
345                      gfd = (fcpertplus-fcpertminus)
346         &                 /(grdchk_epsfac*grdchk_eps)
347                   endif
348                                            
349                       fcpmem    ( ichknum ) = fcpert                 if ( adxxmemo .eq. 0. ) then
350                       xxmemref  ( ichknum ) = xxmemo_ref                    ratio_ad = abs( adxxmemo - gfd )
                      xxmempert ( ichknum ) = xxmemo_pert  
                      gfdmem    ( ichknum ) = gfd  
                      adxxmem   ( ichknum ) = adxxmemo  
                      ratiomem  ( ichknum ) = ratio  
   
                      irecmem   ( ichknum ) = icvrec  
                      bimem     ( ichknum ) = itile  
                      bjmem     ( ichknum ) = jtile  
                      ilocmem   ( ichknum ) = itilepos  
                      jlocmem   ( ichknum ) = jtilepos  
                      klocmem   ( ichknum ) = layer  
                      icompmem  ( ichknum ) = icomp  
                      ichkmem   ( ichknum ) = ichknum  
                      itestmem  ( ichknum ) = itest  
                      ierrmem   ( ichknum ) = ierr  
                     
 cph(  
                      print *, 'ph-grd 3 -------------------------------'  
                      print *, 'ph-grd 3 ',  
      &                    ichknum,itilepos,jtilepos,layer,  
      &                    fcref, fcpert  
                      print *, 'ph-grd 3 ',  
      &                    ichknum,ichkmem(ichknum),  
      &                    icompmem(ichknum),itestmem(ichknum),  
      &                    adxxmemo, gfd, ratio  
 cph)  
                   else  
 c  
                   endif  
351                 else                 else
352                    ierr_grdchk = -1                    ratio_ad = 1. - gfd/adxxmemo
353                 endif                 endif
               
             enddo  
          endif  
354    
355  c--   Everyone has to wait for the component to be reset.                 if ( ftlxxmemo .eq. 0. ) then
356           _BARRIER                    ratio_ftl = abs( ftlxxmemo - gfd )
357                   else
358                      ratio_ftl = 1. - gfd/ftlxxmemo
359                   endif
360                      
361                   tmpplot1(itilepos,jtilepos,layer,itile,jtile)
362         &              = gfd
363                   tmpplot2(itilepos,jtilepos,layer,itile,jtile)
364         &              = ratio_ad
365                   tmpplot3(itilepos,jtilepos,layer,itile,jtile)
366         &              = ratio_ftl
367    
368                   fcrmem      ( ichknum ) = fcref
369                   fcppmem     ( ichknum ) = fcpertplus
370                   fcpmmem     ( ichknum ) = fcpertminus
371                   xxmemref    ( ichknum ) = xxmemo_ref
372                   xxmempert   ( ichknum ) = xxmemo_pert
373                   gfdmem      ( ichknum ) = gfd
374                   adxxmem     ( ichknum ) = adxxmemo
375                   ftlxxmem    ( ichknum ) = ftlxxmemo
376                   ratioadmem  ( ichknum ) = ratio_ad
377                   ratioftlmem ( ichknum ) = ratio_ftl
378    
379                   irecmem   ( ichknum ) = icvrec
380                   bimem     ( ichknum ) = itile
381                   bjmem     ( ichknum ) = jtile
382                   ilocmem   ( ichknum ) = itilepos
383                   jlocmem   ( ichknum ) = jtilepos
384                   klocmem   ( ichknum ) = layer
385                   iobcsmem  ( ichknum ) = obcspos
386                   icompmem  ( ichknum ) = icomp
387                   ichkmem   ( ichknum ) = ichknum
388                   itestmem  ( ichknum ) = itest
389                   ierrmem   ( ichknum ) = ierr
390                      
391                   print *, 'ph-grd 3 -------------------------------'
392                   print '(a,5I5,2x,3(1x,E15.9))', ' ph-grd 3 ',
393         &              myprocid,ichknum,itilepos,jtilepos,layer,
394         &              fcref, fcpertplus, fcpertminus
395    #ifdef ALLOW_TANGENTLINEAR_RUN
396                   print '(a,5I5,2x,3(1x,E15.9))', ' ph-grd 3 ',
397         &              myprocid,ichknum,ichkmem(ichknum),
398         &              icompmem(ichknum),itestmem(ichknum),
399         &              ftlxxmemo, gfd, ratio_ftl
400    #else
401                   print '(a,5I5,2x,3(1x,E15.9))', ' ph-grd 3 ',
402         &              myprocid,ichknum,ichkmem(ichknum),
403         &              icompmem(ichknum),itestmem(ichknum),
404         &              adxxmemo, gfd, ratio_ad
405    #endif
406    
407                endif
408    
409                print *, 'ph-grd  ierr ---------------------------'
410                print *, 'ph-grd  ierr = ', ierr, ', icomp = ', icomp,
411         &           ', ichknum = ', ichknum
412    
413                _BARRIER
414    
415    c-- else of if ( ichknum ...
416             else
417                ierr_grdchk = -1
418    
419    c-- end of if ( ichknum ...
420             endif
421    
422    c-- end of do icomp = ...
423        enddo        enddo
424    
425  cph(        if ( myProcId .EQ. grdchkwhichproc ) then
426        CALL WRITE_REC_XYZ_RL( 'grd_findiff' , tmpplot1, 1, 0, myThid)           CALL WRITE_REC_XYZ_RL(
427        CALL WRITE_REC_XYZ_RL( 'grd_ratio' , tmpplot2, 1, 0, myThid)       &        'grd_findiff'   , tmpplot1, 1, 0, myThid)
428  cph)           CALL WRITE_REC_XYZ_RL(
429         &        'grd_ratio_ad'  , tmpplot2, 1, 0, myThid)
430             CALL WRITE_REC_XYZ_RL(
431         &        'grd_ratio_ftl' , tmpplot3, 1, 0, myThid)
432          endif
433    
434    c--   Everyone has to wait for the component to be reset.
435          _BARRIER
436    
437  c--   Print the results of the gradient check.  c--   Print the results of the gradient check.
438        call grdchk_print( ichknum, ierr_grdchk, mythid )        call grdchk_print( ichknum, ierr_grdchk, mythid )

Legend:
Removed from v.1.3  
changed lines
  Added in v.1.3.6.5

  ViewVC Help
Powered by ViewVC 1.1.22