/[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.10 by edhill, Sat Mar 20 23:51:23 2004 UTC
# Line 63  C     Check that this name is not alread Line 63  C     Check that this name is not alread
63    
64  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
65    
66        SUBROUTINE MNC_CW_DUMP()        SUBROUTINE MNC_CW_DUMP( myThid )
67    
68        implicit none        implicit none
69  #include "mnc_common.h"  #include "mnc_common.h"
70    #include "SIZE.h"
71    #include "EEPARAMS.h"
72    #include "PARAMS.h"
73    
74    C     Arguments
75          integer myThid
76    
77  C     Local Variables  C     Local Variables
78        integer i,j, ntot        integer i,j, ntot
79          integer NBLNK
80          parameter ( NBLNK = 150 )
81          character s1*(NBLNK), blnk*(NBLNK)
82    
83    
84        write(*,'(a)') 'The currently defined Grid Types are:'        _BEGIN_MASTER(myThid)
85          
86          DO i = 1,NBLNK
87            blnk(i:i) = ' '
88          ENDDO
89          
90          s1(1:NBLNK) = blnk(1:NBLNK)
91          write(s1,'(a5,a)') 'MNC: ',
92         &     'The currently defined Grid Types are:'
93          CALL PRINT_MESSAGE(
94         &     s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
95        ntot = 0        ntot = 0
96        DO j = 1,MNC_MAX_ID        DO j = 1,MNC_MAX_ID
97          IF (mnc_cw_gname(j)(1:MNC_MAX_CHAR)          IF (mnc_cw_gname(j)(1:MNC_MAX_CHAR)
98       &       .NE. mnc_blank_name(1:MNC_MAX_CHAR)) THEN       &       .NE. mnc_blank_name(1:MNC_MAX_CHAR)) THEN
99                        
100            ntot = ntot + 1            ntot = ntot + 1
101            write(*,'(2i5,a3,a20,i3,a3,5i4,a4,5i4,a4,5i4,6a4)')            s1(1:NBLNK) = blnk(1:NBLNK)
102              write(s1,'(a5,2i5,a3,a20,i3,a3,5i4,a4,5i4,a4,5i4,6a4)')
103         &         'MNC: ',
104       &         j, ntot, ' : ', mnc_cw_gname(j)(1:20), mnc_cw_ndim(j),       &         j, ntot, ' : ', mnc_cw_gname(j)(1:20), mnc_cw_ndim(j),
105       &         ' : ', (mnc_cw_dims(i,j), i=1,5),       &         ' : ', (mnc_cw_dims(i,j), i=1,5),
106       &         '  | ', (mnc_cw_is(i,j), i=1,5),       &         '  | ', (mnc_cw_is(i,j), i=1,5),
107       &         '  | ', (mnc_cw_ie(i,j), i=1,5),       &         '  | ', (mnc_cw_ie(i,j), i=1,5),
108       &         '  | ', (mnc_cw_dn(i,j)(1:4), i=1,5)       &         '  | ', (mnc_cw_dn(i,j)(1:4), i=1,5)
109              CALL PRINT_MESSAGE(
110         &         s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
111              
112          ENDIF          ENDIF
113        ENDDO        ENDDO
114          
115        write(*,'(a)') 'The currently defined Variable Types are:'        s1(1:NBLNK) = blnk(1:NBLNK)
116          write(s1,'(a5,a)') 'MNC: ',
117         &     'The currently defined Variable Types are:'
118          CALL PRINT_MESSAGE(
119         &     s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
120        ntot = 0        ntot = 0
121        DO j = 1,MNC_MAX_ID        DO j = 1,MNC_MAX_ID
122          IF (mnc_cw_vname(j)(1:MNC_MAX_CHAR)          IF (mnc_cw_vname(j)(1:MNC_MAX_CHAR)
123       &       .NE. mnc_blank_name(1:MNC_MAX_CHAR)) THEN       &       .NE. mnc_blank_name(1:MNC_MAX_CHAR)) THEN
124              
125            ntot = ntot + 1            ntot = ntot + 1
126            write(*,'(2i5,a3,a25,a3,i4)') j, ntot, ' : ',            s1(1:NBLNK) = blnk(1:NBLNK)
127       &         mnc_cw_vname(j)(1:20), ' : ', mnc_cw_vgind(j)            write(s1,'(a5,2i5,a3,a25,a3,i4)') 'MNC: ',
128         &         j, ntot, ' | ',
129         &         mnc_cw_vname(j)(1:20), ' | ', mnc_cw_vgind(j)
130              CALL PRINT_MESSAGE(
131         &         s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
132              
133            DO i = 1,mnc_cw_vnat(1,j)            DO i = 1,mnc_cw_vnat(1,j)
134              write(*,'(a14,i4,a3,a25,a3,a55)') '      text_at:',i,              s1(1:NBLNK) = blnk(1:NBLNK)
135                write(s1,'(a5,a14,i4,a3,a25,a3,a55)')
136         &           'MNC: ','      text_at:',i,
137       &           ' : ', mnc_cw_vtnm(i,j)(1:25), ' : ',       &           ' : ', mnc_cw_vtnm(i,j)(1:25), ' : ',
138       &           mnc_cw_vtat(i,j)(1:55)       &           mnc_cw_vtat(i,j)(1:55)
139                CALL PRINT_MESSAGE(
140         &           s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
141            ENDDO            ENDDO
142            DO i = 1,mnc_cw_vnat(2,j)            DO i = 1,mnc_cw_vnat(2,j)
143              write(*,'(a14,i4,a3,a25,a3,i20)') '      int__at:',i,              s1(1:NBLNK) = blnk(1:NBLNK)
144                write(s1,'(a5,a14,i4,a3,a25,a3,i20)')
145         &           'MNC: ','      int__at:',i,
146       &           ' : ', mnc_cw_vinm(i,j)(1:25), ' : ',       &           ' : ', mnc_cw_vinm(i,j)(1:25), ' : ',
147       &           mnc_cw_viat(i,j)       &           mnc_cw_viat(i,j)
148                CALL PRINT_MESSAGE(
149         &           s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
150            ENDDO            ENDDO
151            DO i = 1,mnc_cw_vnat(3,j)            DO i = 1,mnc_cw_vnat(3,j)
152              write(*,'(a14,i4,a3,a25,a3,f25.10)') '      dbl__at:',i,              s1(1:NBLNK) = blnk(1:NBLNK)
153                write(s1,'(a5,a14,i4,a3,a25,a3,f25.10)')
154         &           'MNC: ','      dbl__at:',i,
155       &           ' : ', mnc_cw_vdnm(i,j)(1:25), ' : ',       &           ' : ', mnc_cw_vdnm(i,j)(1:25), ' : ',
156       &           mnc_cw_vdat(i,j)       &           mnc_cw_vdat(i,j)
157            ENDDO              CALL PRINT_MESSAGE(
158         &           s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
159            ENDDO
160            
161          ENDIF          ENDIF
162        ENDDO        ENDDO
163        IF (ntot .EQ. 0) THEN        IF (ntot .EQ. 0) THEN
164          write(*,'(a)') '   None defined!'          s1(1:NBLNK) = blnk(1:NBLNK)
165            write(s1,'(a)') 'MNC:    None defined!'
166            CALL PRINT_MESSAGE(
167         &       s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
168        ENDIF        ENDIF
169          
170          _END_MASTER(myThid)
171    
172        RETURN        RETURN
173        END        END

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

  ViewVC Help
Powered by ViewVC 1.1.22