/[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.13 by edhill, Mon Apr 5 06:01:07 2004 UTC revision 1.14 by edhill, Tue Jul 6 03:55:53 2004 UTC
# Line 115  C     !LOCAL VARIABLES: Line 115  C     !LOCAL VARIABLES:
115                        
116            ntot = ntot + 1            ntot = ntot + 1
117            s1(1:NBLNK) = blnk(1:NBLNK)            s1(1:NBLNK) = blnk(1:NBLNK)
118            write(s1,'(a5,2i5,a3,a20,i3,a3,5i4,a4,5i4,a4,5i4,6a4)')            write(s1,'(a5,2i5,a3,a20,i3,a3,5i4,a4,5i4,a4,5i4,6a8)')
119       &         'MNC: ',       &         'MNC: ',
120       &         j, ntot, ' : ', mnc_cw_gname(j)(1:20), mnc_cw_ndim(j),       &         j, ntot, ' : ', mnc_cw_gname(j)(1:20), mnc_cw_ndim(j),
121       &         ' : ', (mnc_cw_dims(i,j), i=1,5),       &         ' : ', (mnc_cw_dims(i,j), i=1,5),
122       &         '  | ', (mnc_cw_is(i,j), i=1,5),       &         '  | ', (mnc_cw_is(i,j), i=1,5),
123       &         '  | ', (mnc_cw_ie(i,j), i=1,5),       &         '  | ', (mnc_cw_ie(i,j), i=1,5),
124       &         '  | ', (mnc_cw_dn(i,j)(1:4), i=1,5)       &         '  | ', (mnc_cw_dn(i,j)(1:7), i=1,5)
125            CALL PRINT_MESSAGE(            CALL PRINT_MESSAGE(
126       &         s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)       &         s1, standardMessageUnit, SQUEEZE_RIGHT, mythid)
127                        
# Line 194  C     !ROUTINE: MNC_CW_INIT Line 194  C     !ROUTINE: MNC_CW_INIT
194    
195  C     !INTERFACE:  C     !INTERFACE:
196        SUBROUTINE MNC_CW_INIT(        SUBROUTINE MNC_CW_INIT(
197       I     sNx,sNy, OLx,OLy, nSx,nSy, nPx,nPy, Nr,       I     sNx,sNy, OLx,OLy, nSx,nSy, nPx,nPy, Nr, NrPhys,
198       I     myThid )       I     myThid )
199    
200  C     !DESCRIPTION:  C     !DESCRIPTION:
# Line 230  C     !USES: Line 230  C     !USES:
230  C     !INPUT PARAMETERS:  C     !INPUT PARAMETERS:
231        integer myThid        integer myThid
232        integer sNx,sNy, OLx,OLy, nSx,nSy, nPx,nPy, Nr        integer sNx,sNy, OLx,OLy, nSx,nSy, nPx,nPy, Nr
233          integer NrPhys
234  CEOP  CEOP
235    
236  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
237        integer CW_MAX_LOC        integer CW_MAX_LOC
238        parameter ( CW_MAX_LOC = 5 )        parameter ( CW_MAX_LOC = 5 )
239        integer i, ihorz,ihsub,ivert,itime,ihalo, is,ih, n,ntot        integer i, ihorz,ihsub,ivert,itime,ihalo, is,ih, n,ntot
240        integer ndim, ncomb        integer ndim, ncomb, nvch, NrPh
       character*(MAX_LEN_MBUF) msgbuf  
241        character*(MNC_MAX_CHAR) name        character*(MNC_MAX_CHAR) name
242        character*(MNC_MAX_CHAR) dn(CW_MAX_LOC)        character*(MNC_MAX_CHAR) dn(CW_MAX_LOC)
243        character*(5) horz_dat(CW_MAX_LOC), hsub_dat(CW_MAX_LOC),        character*(5) horz_dat(CW_MAX_LOC), hsub_dat(CW_MAX_LOC),
# Line 246  C     !LOCAL VARIABLES: Line 246  C     !LOCAL VARIABLES:
246        integer dim(CW_MAX_LOC), ib(CW_MAX_LOC), ie(CW_MAX_LOC)        integer dim(CW_MAX_LOC), ib(CW_MAX_LOC), ie(CW_MAX_LOC)
247    
248  C     Functions  C     Functions
249        integer IFNBLNK, ILNBLNK        integer ILNBLNK
250          external ILNBLNK
251    
252  C     ......12345....12345....12345....12345....12345...  C     ......12345....12345....12345....12345....12345...
253        data horz_dat /        data horz_dat /
# Line 256  C     ......12345....12345....12345....1 Line 257  C     ......12345....12345....12345....1
257        data halo_dat /        data halo_dat /
258       &     'Hn   ', 'Hy   ', '--   ', '     ', '     '  /       &     'Hn   ', 'Hy   ', '--   ', '     ', '     '  /
259        data vert_dat /        data vert_dat /
260       &     '-    ', 'C    ', 'I    ', '     ', '     '  /       &     '-    ', 'C    ', 'I    ', 'Phys ', 'PhysI'  /
261        data time_dat /        data time_dat /
262       &     '-    ', 't    ', '     ', '     ', '     '  /       &     '-    ', 't    ', '     ', '     ', '     '  /
263    
264          if (NrPhys .lt. 1) then
265            NrPh = Nr
266          else
267            NrPh = NrPhys
268          endif
269    
270        ncomb = 0        ncomb = 0
271        DO ihorz = 1,5        DO ihorz = 1,5
272          DO is = 1,3          DO is = 1,3
# Line 277  C           Loop just ONCE if the Horiz Line 284  C           Loop just ONCE if the Horiz
284                ENDIF                ENDIF
285              ENDIF              ENDIF
286                            
287              DO ivert = 1,3              DO ivert = 1,5
288                DO itime = 1,2                DO itime = 1,2
289                                    
290  C               horiz and hsub  C               horiz and hsub
# Line 290  C               horiz and hsub Line 297  C               horiz and hsub
297                  name((ntot+1):(ntot+n)) = hsub_dat(ihsub)(1:n)                  name((ntot+1):(ntot+n)) = hsub_dat(ihsub)(1:n)
298                  ntot = ntot + n                  ntot = ntot + n
299    
300  C               vert, time, and halo  C               halo, vert, and time
301                  write(name((ntot+1):(ntot+9)), '(a1,2a2,a1,a2,a1)')                  write(name((ntot+1):(ntot+5)), '(a1,2a2)')
302       &               '_', halo_dat(ihalo)(1:2), '__',       &               '_', halo_dat(ihalo)(1:2), '__'
303       &               vert_dat(ivert)(1:1), '__',                  nvch = ILNBLNK(vert_dat(ivert))
304       &               time_dat(itime)(1:1)                  n = ntot+6+nvch-1
305                    name((ntot+6):(n)) = vert_dat(ivert)(1:nvch)
306                    write(name((n+1):(n+3)), '(a2,a1)')
307         &               '__', time_dat(itime)(1:1)
308    
309                  ndim = 0                  ndim = 0
310                  DO i = 1,CW_MAX_LOC                  DO i = 1,CW_MAX_LOC
# Line 378  C               Vertical dimension Line 388  C               Vertical dimension
388                    ib(ndim)  = 1                    ib(ndim)  = 1
389                    ie(ndim)  = Nr + 1                    ie(ndim)  = Nr + 1
390                  ENDIF                  ENDIF
391                    IF (vert_dat(ivert)(1:5) .EQ. 'Phys ') THEN
392                      ndim = ndim + 1
393                      dn(ndim)(1:5) = 'Zphys'
394                      dim(ndim) = NrPh
395                      ib(ndim)  = 1
396                      ie(ndim)  = NrPh
397                    ENDIF
398                    IF (vert_dat(ivert)(1:5) .EQ. 'PhysI') THEN
399                      ndim = ndim + 1
400                      dn(ndim)(1:7) = 'Zphysm1'
401                      dim(ndim) = NrPh - 1
402                      ib(ndim)  = 1
403                      ie(ndim)  = NrPh - 1
404                    ENDIF
405    
406  C               Time dimension  C               Time dimension
407                  IF (time_dat(itime)(1:1) .EQ. 't') THEN                  IF (time_dat(itime)(1:1) .EQ. 't') THEN
# Line 780  C     !INPUT PARAMETERS: Line 804  C     !INPUT PARAMETERS:
804  CEOP  CEOP
805    
806  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
807        integer i, ierr        integer ierr
       character*(MAX_LEN_MBUF) msgbuf  
808    
809  C     Check if the file is already open  C     Check if the file is already open
810        CALL MNC_GET_IND(MNC_MAX_ID, fname, mnc_f_names, indf, myThid)        CALL MNC_GET_IND(MNC_MAX_ID, fname, mnc_f_names, indf, myThid)

Legend:
Removed from v.1.13  
changed lines
  Added in v.1.14

  ViewVC Help
Powered by ViewVC 1.1.22