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

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

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

revision 1.4 by heimbach, Sat Jul 13 02:55:58 2002 UTC revision 1.10 by jmc, Tue Oct 9 00:05:45 2007 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    C $Name$
3    
4  #include "CTRL_CPPOPTIONS.h"  #include "CTRL_CPPOPTIONS.h"
5    
6    
7        subroutine grdchk_init(        subroutine grdchk_init( mythid )
      I                       mythid  
      &                      )  
8    
9  c     ==================================================================  c     ==================================================================
10  c     SUBROUTINE grdchk_init  c     SUBROUTINE grdchk_init
# Line 35  c     == routine arguments == Line 34  c     == routine arguments ==
34    
35        integer       mythid        integer       mythid
36    
37  #ifdef ALLOW_GRADIENT_CHECK  #ifdef ALLOW_GRDCHK
38  c     == local variables ==  c     == local variables ==
39    
40        integer bi,bj        integer bi,bj
# Line 46  c     == local variables == Line 45  c     == local variables ==
45        integer jmin,jmax        integer jmin,jmax
46        integer imin,imax        integer imin,imax
47    
48        integer itest        integer itest,iobcs
49        integer icomptest        integer icomptest
50    
51  c     == end of interface ==  c     == end of interface ==
# Line 62  c     == end of interface == Line 61  c     == end of interface ==
61    
62        _BEGIN_MASTER( mythid )        _BEGIN_MASTER( mythid )
63    
64    c--   initialise
65          do bj = jtlo,jthi
66             do bi = itlo,ithi
67                do k = 1,ncvarnrmax(grdchkvarindex)
68                   do iobcs = 1, nobcs
69                      nwettile(bi,bj,k,iobcs) = 0
70                   enddo
71                enddo
72             enddo
73          enddo
74    
75  c--   Determine the number of components of the given  c--   Determine the number of components of the given
76  c--   control variable on the current tile.  c--   control variable on the current tile.
77        if ( ncvargrd(grdchkvarindex) .eq. 'c' ) then        if ( ncvargrd(grdchkvarindex) .eq. 'c' ) then
78           do bj = jtlo,jthi           do bj = jtlo,jthi
79              do bi = itlo,ithi              do bi = itlo,ithi
80                 do k = 1,ncvarnrmax(grdchkvarindex)                 do k = 1,ncvarnrmax(grdchkvarindex)
81                    nwettile(bi,bj,k) = nwetctile(bi,bj,k)                    nwettile(bi,bj,k,1) = nwetctile(bi,bj,k)
82                 enddo                 enddo
83              enddo              enddo
84           enddo           enddo
# Line 76  c--   control variable on the current ti Line 86  c--   control variable on the current ti
86           do bj = jtlo,jthi           do bj = jtlo,jthi
87              do bi = itlo,ithi              do bi = itlo,ithi
88                 do k = 1,ncvarnrmax(grdchkvarindex)                 do k = 1,ncvarnrmax(grdchkvarindex)
89                    nwettile(bi,bj,k) = nwetstile(bi,bj,k)                    nwettile(bi,bj,k,1) = nwetstile(bi,bj,k)
90                 enddo                 enddo
91              enddo              enddo
92           enddo           enddo
# Line 84  c--   control variable on the current ti Line 94  c--   control variable on the current ti
94           do bj = jtlo,jthi           do bj = jtlo,jthi
95              do bi = itlo,ithi              do bi = itlo,ithi
96                 do k = 1,ncvarnrmax(grdchkvarindex)                 do k = 1,ncvarnrmax(grdchkvarindex)
97                    nwettile(bi,bj,k) = nwetwtile(bi,bj,k)                    nwettile(bi,bj,k,1) = nwetwtile(bi,bj,k)
98                 enddo                 enddo
99              enddo              enddo
100           enddo           enddo
# Line 92  c--   control variable on the current ti Line 102  c--   control variable on the current ti
102           do bj = jtlo,jthi           do bj = jtlo,jthi
103              do bi = itlo,ithi              do bi = itlo,ithi
104                 do k = 1,ncvarnrmax(grdchkvarindex)                 do k = 1,ncvarnrmax(grdchkvarindex)
105                    nwettile(bi,bj,k) = nwetvtile(bi,bj,k)                    nwettile(bi,bj,k,1) = nwetvtile(bi,bj,k)
106                   enddo
107                enddo
108             enddo
109          else if ( ncvargrd(grdchkvarindex) .eq. 'm' ) then
110             do bj = jtlo,jthi
111                do bi = itlo,ithi
112                   do k = 1,ncvarnrmax(grdchkvarindex)
113                      do iobcs = 1, nobcs
114                         if ( grdchkvarindex .eq. 11 ) then
115    #ifdef ALLOW_OBCSN_CONTROL
116                            nwettile(bi,bj,k,iobcs) =
117         &                       nwetobcsn(bi,bj,k,iobcs)
118    #endif
119                         else if ( grdchkvarindex .eq. 12 ) then
120    #ifdef ALLOW_OBCSS_CONTROL
121                            nwettile(bi,bj,k,iobcs) =
122         &                       nwetobcss(bi,bj,k,iobcs)
123    #endif
124                         else if ( grdchkvarindex .eq. 13 ) then
125    #ifdef ALLOW_OBCSW_CONTROL
126                            nwettile(bi,bj,k,iobcs) =
127         &                       nwetobcsw(bi,bj,k,iobcs)
128    #endif
129                         else if ( grdchkvarindex .eq. 14 ) then
130    #ifdef ALLOW_OBCSE_CONTROL
131                            nwettile(bi,bj,k,iobcs) =
132         &                       nwetobcse(bi,bj,k,iobcs)
133    #endif
134                         endif
135                      enddo
136                 enddo                 enddo
137              enddo              enddo
138           enddo           enddo
# Line 100  c--   control variable on the current ti Line 140  c--   control variable on the current ti
140  ce        --> wrong grid specification for the control variable.  ce        --> wrong grid specification for the control variable.
141        endif        endif
142    
143    c--   get mask file for obcs
144    #ifdef ALLOW_OBCS_CONTROL
145          call grdchk_get_obcs_mask ( mythid )
146    #endif
147    
148  c     ----------------------------------------------------------------  c     ----------------------------------------------------------------
149    
150  c--   Determine the actual and the maximum possible number of  c--   Determine the actual and the maximum possible number of
# Line 109  c--   components of the given control va Line 154  c--   components of the given control va
154        do bj = jtlo,jthi        do bj = jtlo,jthi
155           do bi = itlo,ithi           do bi = itlo,ithi
156              do k = 1,ncvarnrmax(grdchkvarindex)              do k = 1,ncvarnrmax(grdchkvarindex)
157                 ncvarcomp     = ncvarcomp     + nwettile(bi,bj,k)                 do iobcs = 1, nobcs
158                 maxncvarcomps = maxncvarcomps + snx*sny                    ncvarcomp     = ncvarcomp + nwettile(bi,bj,k,iobcs)
159                      maxncvarcomps = maxncvarcomps +
160         &                 ncvarxmax(grdchkvarindex)*
161         &                 ncvarymax(grdchkvarindex)
162                   enddo
163              enddo              enddo
164           enddo           enddo
165        enddo        enddo
166        ncvarcomp     = ncvarcomp*ncvarrecs(grdchkvarindex)        ncvarcomp     = ncvarcomp*ncvarrecs(grdchkvarindex)
167        maxncvarcomps = maxncvarcomps*ncvarrecs(grdchkvarindex)        maxncvarcomps = maxncvarcomps*ncvarrecs(grdchkvarindex)
168    
169          do bj = jtlo,jthi
170             do bi = itlo,ithi
171                iwetsum(bi,bj,0)    = 0
172                do k = 1,ncvarnrmax(grdchkvarindex)
173                   iwetsum(bi,bj,k) = iwetsum(bi,bj,k-1) +
174         &              nwettile(bi,bj,k,1)
175                enddo
176             enddo
177          enddo
178    
179        _END_MASTER( mythid )        _END_MASTER( mythid )
180    
181        _BARRIER        _BARRIER
182    
183  #endif /* ALLOW_GRADIENT_CHECK */  #endif /* ALLOW_GRDCHK */
184    
185        end        end
186    

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

  ViewVC Help
Powered by ViewVC 1.1.22