/[MITgcm]/MITgcm/pkg/mnc/mnc_cwrapper.F
ViewVC logotype

Diff of /MITgcm/pkg/mnc/mnc_cwrapper.F

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

revision 1.9 by edhill, Fri Mar 19 03:28:36 2004 UTC revision 1.30 by edhill, Wed Apr 5 21:07:36 2006 UTC
# Line 4  C $Name$ Line 4  C $Name$
4  #include "MNC_OPTIONS.h"  #include "MNC_OPTIONS.h"
5                
6  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7    CBOP 0
8    C     !ROUTINE: MNC_CW_ADD_GNAME
9    
10    C     !INTERFACE:
11        SUBROUTINE MNC_CW_ADD_GNAME(        SUBROUTINE MNC_CW_ADD_GNAME(
12       I     name,       I     name,
13       I     ndim,       I     ndim,
# Line 13  C---+----1----+----2----+----3----+----4 Line 16  C---+----1----+----2----+----3----+----4
16       I     inds_beg, inds_end,       I     inds_beg, inds_end,
17       I     myThid )       I     myThid )
18    
19    C     !DESCRIPTION:
20    C     Add a grid name to the MNC convenience wrapper layer.
21          
22    C     !USES:
23        implicit none        implicit none
24  #include "mnc_common.h"  #include "mnc_common.h"
25  #include "EEPARAMS.h"  #include "EEPARAMS.h"
26    
27  C     Arguments  C     !INPUT PARAMETERS:
28        integer myThid, ndim        integer myThid, ndim
29        character*(*) name        character*(*) name
30        integer dlens(*), inds_beg(*), inds_end(*)        integer dlens(*), inds_beg(*), inds_end(*)
31        character*(*) dnames(*)        character*(*) dnames(*)
32    CEOP
33    
34  C     Functions  C     !LOCAL VARIABLES:
       integer IFNBLNK, ILNBLNK  
   
 C     Local Variables  
35        integer i, nnf,nnl, indg        integer i, nnf,nnl, indg
36        character*(MAX_LEN_MBUF) msgbuf        character*(MAX_LEN_MBUF) msgbuf
37    
38    C     Functions
39          integer IFNBLNK, ILNBLNK
40    
41        nnf = IFNBLNK(name)        nnf = IFNBLNK(name)
42        nnl = ILNBLNK(name)        nnl = ILNBLNK(name)
43    
# Line 42  C     Check that this name is not alread Line 50  C     Check that this name is not alread
50          stop 'ABNORMAL END: S/R MNC_CW_ADD_GNAME'          stop 'ABNORMAL END: S/R MNC_CW_ADD_GNAME'
51        ENDIF        ENDIF
52        CALL MNC_GET_NEXT_EMPTY_IND(MNC_MAX_ID, mnc_cw_gname,        CALL MNC_GET_NEXT_EMPTY_IND(MNC_MAX_ID, mnc_cw_gname,
53       &     indg, myThid)       &     'mnc_cw_gname', indg, myThid)
54    
55        mnc_cw_gname(indg)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)        mnc_cw_gname(indg)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)
56        mnc_cw_gname(indg)(1:(nnl-nnf+1)) = name(nnf:nnl)        mnc_cw_gname(indg)(1:(nnl-nnf+1)) = name(nnf:nnl)
# Line 62  C     Check that this name is not alread Line 70  C     Check that this name is not alread
70        END        END
71    
72  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
73    CBOP 0
74    C     !ROUTINE: MNC_CW_DEL_GNAME
75    
76        SUBROUTINE MNC_CW_DUMP()  C     !INTERFACE:
77          SUBROUTINE MNC_CW_DEL_GNAME(
78         I     name,
79         I     myThid )
80    
81    C     !DESCRIPTION:
82    C     Delete a grid name from the MNC convenience wrapper layer.
83          
84    C     !USES:
85        implicit none        implicit none
86  #include "mnc_common.h"  #include "mnc_common.h"
87    #include "EEPARAMS.h"
88    
89    C     !INPUT PARAMETERS:
90          integer myThid
91          character*(*) name
92    CEOP
93    
94    C     !LOCAL VARIABLES:
95          integer nnf,nnl, indg
96    
97  C     Local Variables  C     Functions
98          integer IFNBLNK, ILNBLNK
99    
100          nnf = IFNBLNK(name)
101          nnl = ILNBLNK(name)
102    
103    C     Check that this name is not already defined
104          CALL MNC_GET_IND(MNC_MAX_ID, name, mnc_cw_gname, indg, myThid)
105          IF (indg .LT. 1) THEN
106            RETURN
107          ENDIF
108    
109          mnc_cw_gname(indg)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)
110          mnc_cw_ndim(indg) = 0
111    
112          RETURN
113          END
114    
115    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
116    CBOP 1
117    C     !ROUTINE: MNC_CW_DUMP
118    
119    C     !INTERFACE:
120          SUBROUTINE MNC_CW_DUMP( myThid )
121    
122    C     !DESCRIPTION:
123    C     Write a condensed view of the current state of the MNC look-up
124    C     tables for the convenience wrapper section.
125          
126    C     !USES:
127          implicit none
128    #include "mnc_common.h"
129    #include "SIZE.h"
130    #include "EEPARAMS.h"
131    #include "PARAMS.h"
132    
133    C     !INPUT PARAMETERS:
134          integer myThid
135    CEOP
136    
137    C     !LOCAL VARIABLES:
138        integer i,j, ntot        integer i,j, ntot
139          integer NBLNK
140          parameter ( NBLNK = 150 )
141          character s1*(NBLNK), blnk*(NBLNK)
142    
143        write(*,'(a)') 'The currently defined Grid Types are:'        _BEGIN_MASTER(myThid)
144          
145          DO i = 1,NBLNK
146            blnk(i:i) = ' '
147          ENDDO
148          
149          s1(1:NBLNK) = blnk(1:NBLNK)
150          write(s1,'(a5,a)') 'MNC: ',
151         &     'The currently defined Grid Types are:'
152          CALL PRINT_MESSAGE(
153         &     s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
154        ntot = 0        ntot = 0
155        DO j = 1,MNC_MAX_ID        DO j = 1,MNC_MAX_ID
156          IF (mnc_cw_gname(j)(1:MNC_MAX_CHAR)          IF (mnc_cw_gname(j)(1:MNC_MAX_CHAR)
157       &       .NE. mnc_blank_name(1:MNC_MAX_CHAR)) THEN       &       .NE. mnc_blank_name(1:MNC_MAX_CHAR)) THEN
158                        
159            ntot = ntot + 1            ntot = ntot + 1
160            write(*,'(2i5,a3,a20,i3,a3,5i4,a4,5i4,a4,5i4,6a4)')            s1(1:NBLNK) = blnk(1:NBLNK)
161              write(s1,'(a5,2i5,a3,a20,i3,a3,5i4,a4,5i4,a4,5i4,6a8)')
162         &         'MNC: ',
163       &         j, ntot, ' : ', mnc_cw_gname(j)(1:20), mnc_cw_ndim(j),       &         j, ntot, ' : ', mnc_cw_gname(j)(1:20), mnc_cw_ndim(j),
164       &         ' : ', (mnc_cw_dims(i,j), i=1,5),       &         ' : ', (mnc_cw_dims(i,j), i=1,5),
165       &         '  | ', (mnc_cw_is(i,j), i=1,5),       &         '  | ', (mnc_cw_is(i,j), i=1,5),
166       &         '  | ', (mnc_cw_ie(i,j), i=1,5),       &         '  | ', (mnc_cw_ie(i,j), i=1,5),
167       &         '  | ', (mnc_cw_dn(i,j)(1:4), i=1,5)       &         '  | ', (mnc_cw_dn(i,j)(1:7), i=1,5)
168              CALL PRINT_MESSAGE(
169         &         s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
170              
171          ENDIF          ENDIF
172        ENDDO        ENDDO
173          
174        write(*,'(a)') 'The currently defined Variable Types are:'        s1(1:NBLNK) = blnk(1:NBLNK)
175          write(s1,'(a5,a)') 'MNC: ',
176         &     'The currently defined Variable Types are:'
177          CALL PRINT_MESSAGE(
178         &     s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
179        ntot = 0        ntot = 0
180        DO j = 1,MNC_MAX_ID        DO j = 1,MNC_MAX_ID
181          IF (mnc_cw_vname(j)(1:MNC_MAX_CHAR)          IF (mnc_cw_vname(j)(1:MNC_MAX_CHAR)
182       &       .NE. mnc_blank_name(1:MNC_MAX_CHAR)) THEN       &       .NE. mnc_blank_name(1:MNC_MAX_CHAR)) THEN
183              
184            ntot = ntot + 1            ntot = ntot + 1
185            write(*,'(2i5,a3,a25,a3,i4)') j, ntot, ' : ',            s1(1:NBLNK) = blnk(1:NBLNK)
186       &         mnc_cw_vname(j)(1:20), ' : ', mnc_cw_vgind(j)            write(s1,'(a5,2i5,a3,a25,a3,i4)') 'MNC: ',
187         &         j, ntot, ' | ',
188         &         mnc_cw_vname(j)(1:20), ' | ', mnc_cw_vgind(j)
189              CALL PRINT_MESSAGE(
190         &         s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
191              
192            DO i = 1,mnc_cw_vnat(1,j)            DO i = 1,mnc_cw_vnat(1,j)
193              write(*,'(a14,i4,a3,a25,a3,a55)') '      text_at:',i,              s1(1:NBLNK) = blnk(1:NBLNK)
194                write(s1,'(a5,a14,i4,a3,a25,a3,a55)')
195         &           'MNC: ','      text_at:',i,
196       &           ' : ', mnc_cw_vtnm(i,j)(1:25), ' : ',       &           ' : ', mnc_cw_vtnm(i,j)(1:25), ' : ',
197       &           mnc_cw_vtat(i,j)(1:55)       &           mnc_cw_vtat(i,j)(1:MNC_MAX_CHAR)
198                CALL PRINT_MESSAGE(
199         &           s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
200            ENDDO            ENDDO
201            DO i = 1,mnc_cw_vnat(2,j)            DO i = 1,mnc_cw_vnat(2,j)
202              write(*,'(a14,i4,a3,a25,a3,i20)') '      int__at:',i,              s1(1:NBLNK) = blnk(1:NBLNK)
203                write(s1,'(a5,a14,i4,a3,a25,a3,i20)')
204         &           'MNC: ','      int__at:',i,
205       &           ' : ', mnc_cw_vinm(i,j)(1:25), ' : ',       &           ' : ', mnc_cw_vinm(i,j)(1:25), ' : ',
206       &           mnc_cw_viat(i,j)       &           mnc_cw_viat(i,j)
207                CALL PRINT_MESSAGE(
208         &           s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
209            ENDDO            ENDDO
210            DO i = 1,mnc_cw_vnat(3,j)            DO i = 1,mnc_cw_vnat(3,j)
211              write(*,'(a14,i4,a3,a25,a3,f25.10)') '      dbl__at:',i,              s1(1:NBLNK) = blnk(1:NBLNK)
212                write(s1,'(a5,a14,i4,a3,a25,a3,f25.10)')
213         &           'MNC: ','      dbl__at:',i,
214       &           ' : ', mnc_cw_vdnm(i,j)(1:25), ' : ',       &           ' : ', mnc_cw_vdnm(i,j)(1:25), ' : ',
215       &           mnc_cw_vdat(i,j)       &           mnc_cw_vdat(i,j)
216            ENDDO              CALL PRINT_MESSAGE(
217         &           s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
218            ENDDO
219            
220          ENDIF          ENDIF
221        ENDDO        ENDDO
222        IF (ntot .EQ. 0) THEN        IF (ntot .EQ. 0) THEN
223          write(*,'(a)') '   None defined!'          s1(1:NBLNK) = blnk(1:NBLNK)
224            write(s1,'(a)') 'MNC:    None defined!'
225            CALL PRINT_MESSAGE(
226         &       s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
227        ENDIF        ENDIF
228          
229          _END_MASTER(myThid)
230    
231        RETURN        RETURN
232        END        END
233    
234  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
235    CBOP 0
236    C     !ROUTINE: MNC_CW_APPEND_VNAME
237    
238        SUBROUTINE MNC_CW_INIT(  C     !INTERFACE:
239       I     sNx,sNy, OLx,OLy, nSx,nSy, nPx,nPy, Nr,        SUBROUTINE MNC_CW_APPEND_VNAME(
240         I     vname,
241         I     gname,
242         I     bi_dim, bj_dim,
243       I     myThid )       I     myThid )
244    
245    C     !DESCRIPTION:
246    C     If it is not yet defined within the MNC CW layer, append a
247    C     variable type.  Calls MNC\_CW\_ADD\_VNAME().
248      
249    C     !USES:
250        implicit none        implicit none
251  #include "mnc_common.h"  #include "mnc_common.h"
 #include "EEPARAMS.h"  
   
 C     Arguments  
       integer myThid  
       integer sNx,sNy, OLx,OLy, nSx,nSy, nPx,nPy, Nr  
252    
253  C     Functions  C     !INPUT PARAMETERS:
254        integer IFNBLNK, ILNBLNK        integer myThid, bi_dim, bj_dim
255          character*(*) vname, gname
256    CEOP
257    
258  C     Local Variables  C     !LOCAL VARIABLES:
259        integer CW_MAX_LOC        integer indv
       parameter ( CW_MAX_LOC = 5 )  
       integer i, ihorz,ihsub,ivert,itime,ihalo, is,ih, n,ntot  
       integer ndim, ncomb  
       character*(MAX_LEN_MBUF) msgbuf  
       character*(MNC_MAX_CHAR) name  
       character*(MNC_MAX_CHAR) dn(CW_MAX_LOC)  
       character*(5) horz_dat(CW_MAX_LOC), hsub_dat(CW_MAX_LOC),  
      &     vert_dat(CW_MAX_LOC), time_dat(CW_MAX_LOC),  
      &     halo_dat(CW_MAX_LOC)  
       integer dim(CW_MAX_LOC), ib(CW_MAX_LOC), ie(CW_MAX_LOC)  
   
 C     ......12345....12345....12345....12345....12345...  
       data horz_dat /  
      &     '-    ', 'U    ', 'V    ', 'Cen  ', 'Cor  '  /  
       data hsub_dat /  
      &     'xy   ', 'x    ', 'y    ', '-    ', '     '  /  
       data halo_dat /  
      &     'Hn   ', 'Hy   ', '--   ', '     ', '     '  /  
       data vert_dat /  
      &     '-    ', 'C    ', 'I    ', '     ', '     '  /  
       data time_dat /  
      &     '-    ', 't    ', '     ', '     ', '     '  /  
   
       ncomb = 0  
       DO ihorz = 1,5  
         DO is = 1,3  
           DO ih = 1,2  
               
 C           Loop just ONCE if the Horiz component is "-"  
             ihsub = is  
             ihalo = ih  
             IF (ihorz .EQ. 1) THEN  
               IF ((is .EQ. 1) .AND. (ih .EQ. 1)) THEN  
                 ihsub = 4  
                 ihalo = 3  
               ELSE  
                 GOTO 10  
               ENDIF  
             ENDIF  
               
             DO ivert = 1,3  
               DO itime = 1,2  
                   
 C               horiz and hsub  
                 name(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)  
                 n = ILNBLNK(horz_dat(ihorz))  
                 name(1:n) = horz_dat(ihorz)(1:n)  
                 ntot = n + 1                
                 name(ntot:ntot) = '_'  
                 n = ILNBLNK(hsub_dat(ihsub))  
                 name((ntot+1):(ntot+n)) = hsub_dat(ihsub)(1:n)  
                 ntot = ntot + n  
   
 C               vert, time, and halo  
                 write(name((ntot+1):(ntot+9)), '(a1,2a2,a1,a2,a1)')  
      &               '_', halo_dat(ihalo)(1:2), '__',  
      &               vert_dat(ivert)(1:1), '__',  
      &               time_dat(itime)(1:1)  
   
                 ndim = 0  
                 DO i = 1,CW_MAX_LOC  
                   dn(i)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)  
                   dim(i) = 0  
                   ib(i) = 0  
                   ie(i) = 0  
                 ENDDO  
   
 C               Horizontal dimensions  
                 IF (halo_dat(ihalo)(1:5) .EQ. 'Hn   ') THEN  
   
                   IF (hsub_dat(ihsub)(1:1) .EQ. 'x') THEN  
                     ndim = ndim + 1  
                     IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cen')  
      &                   .OR. (horz_dat(ihorz)(1:1) .EQ. 'V') ) THEN  
                       dn(ndim)(1:1) = 'X'  
                       dim(ndim) = sNx + 2*OLx  
                       ib(ndim)  = OLx + 1  
                       ie(ndim)  = OLx + sNx  
                     ENDIF  
                     IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cor')  
      &                   .OR. (horz_dat(ihorz)(1:1) .EQ. 'U') ) THEN  
                       dn(ndim)(1:3) = 'Xp1'  
                       dim(ndim) = sNx + 2*OLx  
                       ib(ndim)  = OLx + 1  
                       ie(ndim)  = OLx + sNx + 1  
                     ENDIF  
                   ENDIF  
                   IF ((hsub_dat(ihsub)(1:1) .EQ. 'y')  
      &                 .OR. (hsub_dat(ihsub)(2:2) .EQ. 'y')) THEN  
                     ndim = ndim + 1  
                     IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cen')  
      &                   .OR. (horz_dat(ihorz)(1:1) .EQ. 'U') ) THEN  
                       dn(ndim)(1:1) = 'Y'  
                       dim(ndim) = sNy + 2*OLy  
                       ib(ndim)  = OLy + 1  
                       ie(ndim)  = OLy + sNy  
                     ENDIF  
                     IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cor')  
      &                   .OR. (horz_dat(ihorz)(1:1) .EQ. 'V') ) THEN  
                       dn(ndim)(1:3) = 'Yp1'  
                       dim(ndim) = sNy + 2*OLy  
                       ib(ndim)  = OLy + 1  
                       ie(ndim)  = OLy + sNy + 1  
                     ENDIF  
                   ENDIF  
   
                 ELSEIF (halo_dat(ihalo)(1:5) .EQ. 'Hy   ') THEN  
   
                   IF (hsub_dat(ihsub)(1:1) .EQ. 'x') THEN  
                     ndim = ndim + 1  
                     dn(ndim)(1:3) = 'Xwh'  
                     dim(ndim) = sNx + 2*OLx  
                     ib(ndim)  = 1  
                     ie(ndim)  = sNx + 2*OLx  
                   ENDIF  
                   IF ((hsub_dat(ihsub)(1:1) .EQ. 'y')  
      &                 .OR. (hsub_dat(ihsub)(2:2) .EQ. 'y')) THEN  
                     ndim = ndim + 1  
                     dn(ndim)(1:3) = 'Ywh'  
                     dim(ndim) = sNy + 2*OLy  
                     ib(ndim)  = 1  
                     ie(ndim)  = sNy + 2*OLy  
                   ENDIF  
   
                 ENDIF  
   
 C               Vertical dimension  
                 IF (vert_dat(ivert)(1:1) .EQ. 'C') THEN  
                   ndim = ndim + 1  
                   dn(ndim)(1:1) = 'Z'  
                   dim(ndim) = Nr  
                   ib(ndim)  = 1  
                   ie(ndim)  = Nr  
                 ENDIF  
                 IF (vert_dat(ivert)(1:1) .EQ. 'I') THEN  
                   ndim = ndim + 1  
                   dn(ndim)(1:3) = 'Zp1'  
                   dim(ndim) = Nr + 1  
                   ib(ndim)  = 1  
                   ie(ndim)  = Nr + 1  
                 ENDIF  
   
 C               Time dimension  
                 IF (time_dat(itime)(1:1) .EQ. 't') THEN  
                   ndim = ndim + 1  
                   dn(ndim)(1:1) = 'T'  
                   dim(ndim) = -1  
                   ib(ndim)  = 1  
                   ie(ndim)  = 1  
                 ENDIF  
   
                 IF (ndim .GT. 0) THEN  
 #ifdef MNC_DEBUG  
                   ncomb = ncomb + 1  
                   write(*,'(i4,a3,a15,i3,a3,5i4,a4,5i4,a4,5i4,6a4)')  
      &                 ncomb, ' : ', name(1:15), ndim,  
      &                 ' : ', (dim(i), i=1,5),  
      &                 '  | ', (ib(i), i=1,5),  
      &                 '  | ', (ie(i), i=1,5),  
      &                 '  | ', (dn(i)(1:4), i=1,5)  
 #endif  
260    
261                    CALL MNC_CW_ADD_GNAME(name, ndim,  C     Check whether vname is defined
262       &                 dim, dn, ib, ie, myThid)        CALL MNC_GET_IND(MNC_MAX_ID, vname, mnc_cw_vname, indv, myThid)
263                  ENDIF        IF (indv .LT. 1) THEN
264            CALL MNC_CW_ADD_VNAME(vname, gname, bi_dim, bj_dim, myThid)
265          ENDIF
266    
               ENDDO  
             ENDDO  
267    
  10         CONTINUE  
           ENDDO  
         ENDDO  
       ENDDO  
         
268        RETURN        RETURN
269        END        END
270    
271  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
272    CBOP 0
273    C     !ROUTINE: MNC_CW_ADD_VNAME
274    
275    C     !INTERFACE:
276        SUBROUTINE MNC_CW_ADD_VNAME(        SUBROUTINE MNC_CW_ADD_VNAME(
277       I     vname,       I     vname,
278       I     gname,       I     gname,
279       I     bi_dim, bj_dim,       I     bi_dim, bj_dim,
280       I     myThid )       I     myThid )
281    
282    C     !DESCRIPTION:
283    C     Add a variable type to the MNC CW layer.  The variable type is an
284    C     association between a variable type name and the following items:
285    C     \begin{center}
286    C       \begin{tabular}[h]{|ll|}\hline
287    C         \textbf{Item}  & \textbf{Purpose}  \\\hline
288    C         grid type  &  defines the in-memory arrangement  \\
289    C         \texttt{bi,bj} dimensions  &  tiling indices, if present  \\\hline
290    C       \end{tabular}
291    C     \end{center}
292      
293    C     !USES:
294        implicit none        implicit none
295  #include "mnc_common.h"  #include "mnc_common.h"
296  #include "EEPARAMS.h"  #include "EEPARAMS.h"
297    
298  C     Arguments  C     !INPUT PARAMETERS:
299        integer myThid, bi_dim, bj_dim        integer myThid, bi_dim, bj_dim
300        character*(*) vname, gname        character*(*) vname, gname
301    CEOP
302    
303  C     Functions  C     !LOCAL VARIABLES:
       integer IFNBLNK, ILNBLNK  
   
 C     Local Variables  
304        integer i, nvf,nvl, ngf,ngl, indv,indg        integer i, nvf,nvl, ngf,ngl, indv,indg
305        character*(MAX_LEN_MBUF) msgbuf        character*(MAX_LEN_MBUF) msgbuf
306    
307    C     Functions
308          integer IFNBLNK, ILNBLNK
309    
310        nvf = IFNBLNK(vname)        nvf = IFNBLNK(vname)
311        nvl = ILNBLNK(vname)        nvl = ILNBLNK(vname)
312        ngf = IFNBLNK(gname)        ngf = IFNBLNK(gname)
# Line 357  C     Check that this vname is not alrea Line 321  C     Check that this vname is not alrea
321          stop 'ABNORMAL END: S/R MNC_CW_ADD_VNAME'          stop 'ABNORMAL END: S/R MNC_CW_ADD_VNAME'
322        ENDIF        ENDIF
323        CALL MNC_GET_NEXT_EMPTY_IND(MNC_MAX_ID, mnc_cw_vname,        CALL MNC_GET_NEXT_EMPTY_IND(MNC_MAX_ID, mnc_cw_vname,
324       &     indv, myThid)       &     'mnc_cw_vname', indv, myThid)
325    
326  C     Check that gname exists  C     Check that gname exists
327        CALL MNC_GET_IND(MNC_MAX_ID, gname, mnc_cw_gname, indg, myThid)        CALL MNC_GET_IND(MNC_MAX_ID, gname, mnc_cw_gname, indg, myThid)
# Line 377  C     Check that gname exists Line 341  C     Check that gname exists
341        mnc_cw_vbij(1,indv) = bi_dim        mnc_cw_vbij(1,indv) = bi_dim
342        mnc_cw_vbij(2,indv) = bj_dim        mnc_cw_vbij(2,indv) = bj_dim
343    
344    #ifdef MNC_DEBUG_GTYPE
345        CALL MNC_CW_ADD_VATTR_TEXT(vname,1,'mitgcm_grid',gname, myThid)        CALL MNC_CW_ADD_VATTR_TEXT(vname,1,'mitgcm_grid',gname, myThid)
346    #endif
347    
348        RETURN        RETURN
349        END        END
350    
351  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
352    CBOP 0
353    C     !ROUTINE: MNC_CW_DEL_VNAME
354    
355        SUBROUTINE MNC_CW_ADD_VATTR_TEXT(  C     !INTERFACE:
356          SUBROUTINE MNC_CW_DEL_VNAME(
357       I     vname,       I     vname,
      I     ntat,  
      I     tnames,  
      I     tvals,  
358       I     myThid )       I     myThid )
359    
360    C     !DESCRIPTION:
361    C     Delete a variable type from the MNC CW layer.
362      
363    C     !USES:
364        implicit none        implicit none
365    #include "mnc_common.h"
366    #include "EEPARAMS.h"
367    
368  C     Arguments  C     !INPUT PARAMETERS:
369        integer myThid, ntat        integer myThid
370        character*(*) vname, tnames(*), tvals(*)        character*(*) vname
371    CEOP
372    
373        CALL MNC_CW_ADD_VATTR_ANY(vname,  C     !LOCAL VARIABLES:
374       &     ntat, 0, 0,        integer i, indv
375       &     tnames, ' ', ' ',  
376       &     tvals, 0, 0.0D0, myThid )  C     Check that this vname is not already defined
377          CALL MNC_GET_IND(MNC_MAX_ID, vname, mnc_cw_vname, indv, myThid)
378          IF (indv .LT. 1) THEN
379            RETURN
380          ENDIF
381    
382          mnc_cw_vname(indv)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)
383          mnc_cw_vgind(indv) = 0
384          DO i = 1,3
385            mnc_cw_vnat(i,indv) = 0
386          ENDDO
387    
388        RETURN        RETURN
389        END        END
390    
391  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
392    CBOP
393        SUBROUTINE MNC_CW_ADD_VATTR_INT(  C     !ROUTINE: MNC_CW_ADD_VATTR_TEXT
394       I     vname,  C     !INTERFACE:
395       I     niat,        SUBROUTINE MNC_CW_ADD_VATTR_TEXT(
396       I     inames,       I     vname, tname, tval,
      I     ivals,  
397       I     myThid )       I     myThid )
398    
399    C     !DESCRIPTION:
400    C     Add a text attribute
401          
402    C     !USES:
403        implicit none        implicit none
404    
405  C     Arguments  C     !INPUT PARAMETERS:
406        integer myThid, niat        integer myThid
407        character*(*) vname, inames(*)        character*(*) vname, tname, tval
408        integer ivals(*)        integer ival
409          REAL*8 dval
410    CEOP
411          ival = 0
412          dval = 0.0D0
413          CALL MNC_CW_ADD_VATTR_ANY(vname, 1,
414         &     tname, ' ', ' ', tval, ival, dval, myThid )
415          RETURN
416          END
417    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
418    CBOP
419    C     !ROUTINE: MNC_CW_ADD_VATTR_INT
420    C     !INTERFACE:
421          SUBROUTINE MNC_CW_ADD_VATTR_INT(
422         I     vname, iname, ival,
423         I     myThid )
424    
425        CALL MNC_CW_ADD_VATTR_ANY(vname,  C     !DESCRIPTION:
426       &     0, niat, 0,  C     Add integer attribute
      &     ' ', inames, ' ',  
      &     ' ', ivals, 0.0D0, myThid )  
427    
428    C     !USES:
429          implicit none
430    
431    C     !INPUT PARAMETERS:
432          integer myThid
433          character*(*) vname, iname
434          integer ival
435          REAL*8 dval
436    CEOP
437          dval = 0.0D0
438          CALL MNC_CW_ADD_VATTR_ANY(vname, 2,
439         &     ' ', iname, ' ', ' ', ival, dval, myThid )
440        RETURN        RETURN
441        END        END
   
442  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
443    CBOP
444    C !ROUTINE: MNC_CW_ADD_VATTR_DBL
445    C !INTERFACE:
446        SUBROUTINE MNC_CW_ADD_VATTR_DBL(        SUBROUTINE MNC_CW_ADD_VATTR_DBL(
447       I     vname,       I     vname, dname, dval,
      I     ndat,  
      I     dnames,  
      I     dvals,  
448       I     myThid )       I     myThid )
449    
450        implicit none  C     !DESCRIPTION:
451    C     Add double-precision real attribute
 C     Arguments  
       integer myThid, ndat  
       character*(*) vname, dnames(*)  
       REAL*8 dvals(*)  
452    
453        CALL MNC_CW_ADD_VATTR_ANY(vname,  C     !USES:
454       &     0, 0, ndat,        implicit none
      &     ' ', ' ', dnames,  
      &     ' ', 0, dvals, myThid )  
455    
456    C     !INPUT PARAMETERS:
457          integer myThid
458          character*(*) vname, dname
459          integer ival
460          REAL*8 dval
461    CEOP
462          ival = 0
463          CALL MNC_CW_ADD_VATTR_ANY(vname, 3,
464         &     ' ', ' ', dname, ' ', ival, dval, myThid )
465        RETURN        RETURN
466        END        END
   
467  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
468    CBOP 1
469    C     !ROUTINE: MNC_CW_ADD_VATTR_ANY
470    
471    C     !INTERFACE:
472        SUBROUTINE MNC_CW_ADD_VATTR_ANY(        SUBROUTINE MNC_CW_ADD_VATTR_ANY(
473       I     vname,       I     vname,
474       I     ntat,   niat,   ndat,       I     atype,
475       I     tnames, inames, dnames,       I     tname, iname, dname,
476       I     tvals,  ivals,  dvals,       I     tval,  ival,  dval,
477       I     myThid )       I     myThid )
478    
479    C     !DESCRIPTION:
480    
481    C     !USES:
482        implicit none        implicit none
483  #include "mnc_common.h"  #include "mnc_common.h"
484  #include "EEPARAMS.h"  #include "EEPARAMS.h"
485    
486  C     Arguments  C     !INPUT PARAMETERS:
487        integer myThid, ntat, niat, ndat        integer myThid
488          integer atype
489        character*(*) vname        character*(*) vname
490        character*(*) tnames(*), inames(*), dnames(*)        character*(*) tname, iname, dname
491        character*(*) tvals(*)        character*(*) tval
492        integer ivals(*)        integer ival
493        REAL*8 dvals(*)        REAL*8 dval
494    CEOP
495    
496    C     !LOCAL VARIABLES:
497          integer n, nvf,nvl, n1,n2, indv, ic
498          character*(MAX_LEN_MBUF) msgbuf
499    
500  C     Functions  C     Functions
501        integer IFNBLNK, ILNBLNK        integer IFNBLNK, ILNBLNK
502    
 C     Local Variables  
       integer i, n, nvf,nvl, n1,n2, indv  
       character*(MAX_LEN_MBUF) msgbuf  
   
503        nvf = IFNBLNK(vname)        nvf = IFNBLNK(vname)
504        nvl = ILNBLNK(vname)        nvl = ILNBLNK(vname)
505    
# Line 493  C     Check that vname is defined Line 512  C     Check that vname is defined
512          stop 'ABNORMAL END: S/R MNC_CW_ADD_VATTR_ANY'          stop 'ABNORMAL END: S/R MNC_CW_ADD_VATTR_ANY'
513        ENDIF        ENDIF
514    
515  C     Text Attributes        IF (atype .EQ. 1) THEN
516        n = mnc_cw_vnat(1,indv)  C       Text Attribute
517        DO i = 1,ntat          n = mnc_cw_vnat(1,indv) + 1
518          n1 = IFNBLNK(tnames(i))          n1 = IFNBLNK(tname)
519          n2 = ILNBLNK(tnames(i))          n2 = ILNBLNK(tname)
520          mnc_cw_vtnm(n+i,indv)(1:(n2-n1+1)) = tnames(i)(n1:n2)          IF ((n2-n1+1) .GT. MNC_MAX_CHAR) THEN
521          n1 = IFNBLNK(tvals(i))            write(msgbuf,'(3a,i6,2a)')
522          n2 = ILNBLNK(tvals(i))       &         'MNC_CW_ADD_VATTR_ANY WARNING: attribute name ''',
523          mnc_cw_vtat(n+i,indv)(1:(n2-n1+1)) = tvals(i)(n1:n2)       &         tname(n1:n2), ''' has more than ', MNC_MAX_CHAR,
524        ENDDO       &         ' characters and has been truncated to fit--please',
525        mnc_cw_vnat(1,indv) = n + ntat       &         'use a smaller name or increase MNC_MAX_CHAR'
526              CALL PRINT_MESSAGE( msgbuf, errorMessageUnit,
527  C     Integer Attributes       &                        SQUEEZE_RIGHT , myThid)
528        n = mnc_cw_vnat(2,indv)  C         MNC_MAX_CHAR = n2 - n1 + 1
529        DO i = 1,niat            n2 = MNC_MAX_CHAR + n1 - 1
530          n1 = IFNBLNK(inames(i))          ENDIF
531          n2 = ILNBLNK(inames(i))  C       write(*,*) atype,tname(n1:n2)
532          mnc_cw_vinm(n+i,indv)(1:(n2-n1+1)) = inames(i)(n1:n2)          mnc_cw_vtnm(n,indv)(1:MNC_MAX_CHAR) =
533          mnc_cw_viat(n+i,indv) = ivals(i)       &       mnc_blank_name(1:MNC_MAX_CHAR)
534        ENDDO          mnc_cw_vtnm(n,indv)(1:(n2-n1+1)) = tname(n1:n2)
535        mnc_cw_vnat(2,indv) = n + niat  
536            n1 = IFNBLNK(tval)
537  C     Double Attributes          n2 = ILNBLNK(tval)
538        n = mnc_cw_vnat(3,indv)          IF ((n2-n1+1) .GT. MNC_MAX_CATT) THEN
539        DO i = 1,ndat            write(msgbuf,'(3a,i6,2a)')
540          n1 = IFNBLNK(dnames(i))       &         'MNC_CW_ADD_VATTR_ANY WARNING: attribute value ''',
541          n2 = ILNBLNK(dnames(i))       &         tval(n1:n2), ''' has more than ', MNC_MAX_CATT,
542          mnc_cw_vdnm(n+i,indv)(1:(n2-n1+1)) = dnames(i)(n1:n2)       &         ' characters and has been truncated to fit--please',
543          mnc_cw_vdat(n+i,indv) = dvals(i)       &         'use a smaller name or increase MNC_MAX_CATT'
544        ENDDO            CALL PRINT_MESSAGE( msgbuf, errorMessageUnit,
545        mnc_cw_vnat(3,indv) = n + ndat       &                        SQUEEZE_RIGHT , myThid)
546              n2 = MNC_MAX_CATT + n1 - 1
547            ENDIF
548            
549            mnc_cw_vnat(1,indv) = n
550            DO ic = 1,MNC_MAX_CATT
551              mnc_cw_vtat(n,indv)(ic:ic) = ' '
552            ENDDO
553            IF ((n1 .NE. 0) .AND. (n2 .NE. 0)) THEN
554              mnc_cw_vtat(n,indv)(1:(n2-n1+1)) = tval(n1:n2)
555            ENDIF
556          ENDIF
557            
558          IF (atype .EQ. 2) THEN
559    C       Integer Attribute
560            n = mnc_cw_vnat(2,indv) + 1
561            n1 = IFNBLNK(iname)
562            n2 = ILNBLNK(iname)
563    C       write(*,*) atype,iname(n1:n2)
564            mnc_cw_vinm(n,indv)(1:(n2-n1+1)) = iname(n1:n2)
565            mnc_cw_viat(n,indv) = ival
566            mnc_cw_vnat(2,indv) = n
567          ENDIF
568    
569          IF (atype .EQ. 3) THEN
570    C       Double Attribute
571            n = mnc_cw_vnat(3,indv) + 1
572            n1 = IFNBLNK(dname)
573            n2 = ILNBLNK(dname)
574    C       write(*,*) atype,dname(n1:n2)
575            mnc_cw_vdnm(n,indv)(1:(n2-n1+1)) = dname(n1:n2)
576            mnc_cw_vdat(n,indv) = dval
577            mnc_cw_vnat(3,indv) = n
578          ENDIF
579          
580        RETURN        RETURN
581        END        END
582    
583  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
584    CBOP 1
585    C     !ROUTINE: MNC_CW_GET_TILE_NUM
586    
587    C     !INTERFACE:
588        SUBROUTINE MNC_CW_GET_TILE_NUM(        SUBROUTINE MNC_CW_GET_TILE_NUM(
589       I     bi, bj,       I     bi, bj,
590       O     uniq_tnum,       O     uniq_tnum,
591       I     myThid )       I     myThid )
592    
593    C     !DESCRIPTION:
594    
595    C     !USES:
596        implicit none        implicit none
597  #include "EEPARAMS.h"  #include "EEPARAMS.h"
598  #include "SIZE.h"  #include "SIZE.h"
# Line 543  C---+----1----+----2----+----3----+----4 Line 601  C---+----1----+----2----+----3----+----4
601  #include "W2_EXCH2_PARAMS.h"  #include "W2_EXCH2_PARAMS.h"
602  #endif  #endif
603    
604  C     Arguments  C     !INPUT PARAMETERS:
605        integer myThid, bi,bj, uniq_tnum        integer myThid, bi,bj, uniq_tnum
606    CEOP
607    
608  C     Local Variables  C     !LOCAL VARIABLES:
609        integer iG,jG        integer iG,jG
610    
611        iG = 0        iG = 0
# Line 572  CEH3      write(*,*) 'iG,jG,uniq_tnum :' Line 631  CEH3      write(*,*) 'iG,jG,uniq_tnum :'
631        END        END
632    
633  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
634    CBOP 1
635    C     !ROUTINE: MNC_CW_GET_FACE_NUM
636    
637    C     !INTERFACE:
638          SUBROUTINE MNC_CW_GET_FACE_NUM(
639         I     bi, bj,
640         O     uniq_fnum,
641         I     myThid )
642    
643    C     !DESCRIPTION:
644    
645    C     !USES:
646          implicit none
647    #include "EEPARAMS.h"
648    #include "SIZE.h"
649    #ifdef ALLOW_EXCH2
650    #include "W2_EXCH2_TOPOLOGY.h"
651    #include "W2_EXCH2_PARAMS.h"
652    #endif
653    
654    C     !INPUT PARAMETERS:
655          integer myThid, bi,bj, uniq_fnum
656    CEOP
657    
658    #ifdef ALLOW_EXCH2
659    
660          uniq_fnum = exch2_myFace( W2_myTileList(bi) )
661    
662    #else
663    
664    C     Global face number for simple (EXCH "1") domains
665          uniq_fnum = -1
666    
667    #endif
668    
669          RETURN
670          END
671    
672    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
673    CBOP 1
674    C     !ROUTINE: MNC_CW_GET_XYFO
675    
676    C     !INTERFACE:
677          SUBROUTINE MNC_CW_GET_XYFO(
678         I     bi, bj,
679         O     ixoff, iyoff,
680         I     myThid )
681    
682    C     !DESCRIPTION:
683    
684    C     !USES:
685          implicit none
686    #include "EEPARAMS.h"
687    #include "SIZE.h"
688    #ifdef ALLOW_EXCH2
689    #include "W2_EXCH2_TOPOLOGY.h"
690    #include "W2_EXCH2_PARAMS.h"
691    #endif
692    
693    C     !INPUT PARAMETERS:
694          integer myThid, bi,bj, ixoff,iyoff
695    CEOP
696    
697    C     !LOCAL VARIABLES:
698          integer uniq_tnum
699    
700    #ifdef ALLOW_EXCH2
701    
702          uniq_tnum = W2_myTileList(bi)
703          ixoff = exch2_tbasex( uniq_tnum )
704          iyoff = exch2_tbasey( uniq_tnum )
705    
706    #else
707    
708    C     Global tile number for simple (non-cube) domains
709    C     iG = bi+(myXGlobalLo-1)/sNx
710    C     jG = bj+(myYGlobalLo-1)/sNy
711    C     uniq_tnum = (jG - 1)*(nPx*nSx) + iG
712          ixoff = myXGlobalLo + bi * sNx
713          iyoff = myYGlobalLo + bj * sNy
714    
715    #endif
716    
717          RETURN
718          END
719    
720    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
721    CBOP 1
722    C     !ROUTINE: MNC_CW_FILE_AORC
723          
724    C     !INTERFACE:
725        SUBROUTINE MNC_CW_FILE_AORC(        SUBROUTINE MNC_CW_FILE_AORC(
726       I     fname,       I     fname,
727       O     indf,       O     indf,
728         I     lbi, lbj, uniq_tnum,
729       I     myThid )       I     myThid )
730    
731    C     !DESCRIPTION:
732    C     Open a NetCDF file, appending to the file if it already exists
733    C     and, if not, creating a new file.
734    
735    C     !USES:
736        implicit none        implicit none
737  #include "netcdf.inc"  #include "netcdf.inc"
738  #include "mnc_common.h"  #include "mnc_common.h"
739  #include "EEPARAMS.h"  #include "EEPARAMS.h"
740    
741  C     Arguments  C     !INPUT PARAMETERS:
742        integer myThid, indf        integer myThid, indf, lbi, lbj, uniq_tnum
743        character*(*) fname        character*(*) fname
744    CEOP
745    
746  C     Local Variables  C     !LOCAL VARIABLES:
747        integer i, ierr        integer ierr
       character*(MAX_LEN_MBUF) msgbuf  
748    
749  C     Check if the file is already open  C     Check if the file is already open
750        CALL MNC_GET_IND(MNC_MAX_ID, fname, mnc_f_names, indf, myThid)        CALL MNC_GET_IND(MNC_MAX_FID, fname, mnc_f_names, indf, myThid)
751        IF (indf .GT. 0) THEN        IF (indf .GT. 0) THEN
752          RETURN          RETURN
753        ENDIF        ENDIF
754    
755  C     Try to open an existing file  C     Try to open an existing file
756        CALL MNC_FILE_TRY_READ(fname, ierr, indf, myThid)        CALL MNC_FILE_TRY_READ(fname, ierr, indf, myThid)
757        IF (ierr .EQ. NF_NOERR) THEN        IF (ierr .NE. NF_NOERR) THEN
758          RETURN  C       Try to create a new one
759            CALL MNC_FILE_OPEN(fname, 0, indf, myThid)
760        ENDIF        ENDIF
761    
762  C     Try to create a new one  C     Add the global attributes
763        CALL MNC_FILE_OPEN(fname, 0, indf, myThid)        CALL MNC_CW_SET_GATTR(fname, lbi,lbj, uniq_tnum, myThid)
764    
765        RETURN        RETURN
766        END        END
767    
768  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
   

Legend:
Removed from v.1.9  
changed lines
  Added in v.1.30

  ViewVC Help
Powered by ViewVC 1.1.22