/[MITgcm]/MITgcm/pkg/mnc/mnc_cw_readwrite.template
ViewVC logotype

Diff of /MITgcm/pkg/mnc/mnc_cw_readwrite.template

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

revision 1.34 by edhill, Sat Sep 24 03:44:54 2005 UTC revision 1.36 by edhill, Fri Mar 10 05:50:23 2006 UTC
# Line 115  C     !LOCAL VARIABLES: Line 115  C     !LOCAL VARIABLES:
115        integer j1,j2,j3,j4,j5,j6,j7, k1,k2,k3,k4,k5,k6,k7        integer j1,j2,j3,j4,j5,j6,j7, k1,k2,k3,k4,k5,k6,k7
116        integer indfg, fg1,fg2, npath        integer indfg, fg1,fg2, npath
117        character*(MAX_LEN_MBUF) msgbuf        character*(MAX_LEN_MBUF) msgbuf
118        character*(MNC_MAX_CHAR) fname        character*(MNC_MAX_PATH) fname
119        character*(MNC_MAX_CHAR) path_fname        character*(MNC_MAX_PATH) path_fname
120        character*(MNC_MAX_CHAR) tmpnm        character*(MNC_MAX_PATH) tmpnm
121          character*(MNC_MAX_PATH) bpath
122          REAL*8  dval, dvm(2)
123          REAL*4  rval, rvm(2)
124          INTEGER ival, ivm(2), irv
125        REAL*8  resh_d( MNC_MAX_BUFF )        REAL*8  resh_d( MNC_MAX_BUFF )
126        REAL*4  resh_r( MNC_MAX_BUFF )        REAL*4  resh_r( MNC_MAX_BUFF )
127        INTEGER resh_i( MNC_MAX_BUFF )        INTEGER resh_i( MNC_MAX_BUFF )
128          LOGICAL write_attributes, use_missing
129  #ifdef HAVE_STAT  #ifdef HAVE_STAT
130        integer ntotenc, ncenc, nbytes, fs_isdone        integer ntotenc, ncenc, nbytes, fs_isdone
131        character*(200) cenc        character*(200) cenc
# Line 134  C     Functions Line 139  C     Functions
139  C     Only do I/O if I am the master thread  C     Only do I/O if I am the master thread
140        _BEGIN_MASTER( myThid )        _BEGIN_MASTER( myThid )
141    
142          DO i = 1,MNC_MAX_PATH
143            bpath(i:i) = ' '
144          ENDDO
145    
146  C     Get the current index for the unlimited dimension from the file  C     Get the current index for the unlimited dimension from the file
147  C     group (or base) name  C     group (or base) name
148        fg1 = IFNBLNK(fbname)        fg1 = IFNBLNK(fbname)
# Line 186  C     Set the bi,bj indicies Line 195  C     Set the bi,bj indicies
195    
196  C         Create the file name  C         Create the file name
197            CALL MNC_CW_GET_TILE_NUM(lbi,lbj, uniq_tnum, myThid)            CALL MNC_CW_GET_TILE_NUM(lbi,lbj, uniq_tnum, myThid)
198            fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)            fname(1:MNC_MAX_PATH) = bpath(1:MNC_MAX_PATH)
199            n1 = IFNBLNK(fbname)            n1 = IFNBLNK(fbname)
200            n2 = ILNBLNK(fbname)            n2 = ILNBLNK(fbname)
201    
# Line 237  C           We have an error--bad flag v Line 246  C           We have an error--bad flag v
246    
247  C         Add the path to the file name  C         Add the path to the file name
248            IF (mnc_use_outdir) THEN            IF (mnc_use_outdir) THEN
249              path_fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)              path_fname(1:MNC_MAX_PATH) = bpath(1:MNC_MAX_PATH)
250              npath = ILNBLNK(mnc_out_path)              npath = ILNBLNK(mnc_out_path)
251              path_fname(1:npath) = mnc_out_path(1:npath)              path_fname(1:npath) = mnc_out_path(1:npath)
252              path_fname((npath+1):(npath+nfname)) = fname(1:nfname)              path_fname((npath+1):(npath+nfname)) = fname(1:nfname)
253              fname(1:MNC_MAX_CHAR) = path_fname(1:MNC_MAX_CHAR)              fname(1:MNC_MAX_PATH) = path_fname(1:MNC_MAX_PATH)
254              nfname = npath + nfname              nfname = npath + nfname
255            ENDIF            ENDIF
256    
# Line 344  C         Ensure that the "grid" is defi Line 353  C         Ensure that the "grid" is defi
353       &        mnc_cw_ndim(igrid), mnc_cw_dn(1,igrid), myThid)       &        mnc_cw_ndim(igrid), mnc_cw_dn(1,igrid), myThid)
354    
355  C         Ensure that the variable is defined  C         Ensure that the variable is defined
356              irv = 0
357            IF (stype(1:1) .EQ. 'D')            IF (stype(1:1) .EQ. 'D')
358       &         CALL MNC_VAR_INIT_DBL(       &         CALL MNC_VAR_INIT_DBL(
359       &         fname, mnc_cw_gname(igrid), vtype, myThid)       &         fname, mnc_cw_gname(igrid), vtype, irv, myThid)
360            IF (stype(1:1) .EQ. 'R')            IF (stype(1:1) .EQ. 'R')
361       &         CALL MNC_VAR_INIT_REAL(       &         CALL MNC_VAR_INIT_REAL(
362       &         fname, mnc_cw_gname(igrid), vtype, myThid)       &         fname, mnc_cw_gname(igrid), vtype, irv, myThid)
363            IF (stype(1:1) .EQ. 'I')            IF (stype(1:1) .EQ. 'I')
364       &         CALL MNC_VAR_INIT_INT(       &         CALL MNC_VAR_INIT_INT(
365       &         fname, mnc_cw_gname(igrid), vtype, myThid)       &         fname, mnc_cw_gname(igrid), vtype, irv, myThid)
366    
367              IF (irv .GT. 0) THEN
368    C           Return value indicates that the variable did not previously
369    C           exist in this file, so we need to write all the attributes
370                write_attributes = .TRUE.
371              ELSE
372                write_attributes = .FALSE.
373              ENDIF
374    
375            DO i = 1,mnc_fv_ids(indf,1)            DO i = 1,mnc_fv_ids(indf,1)
376              j = 2 + 3*(i - 1)              j = 2 + 3*(i - 1)
# Line 445  C         Check the offsets Line 463  C         Check the offsets
463              ENDIF              ENDIF
464            ENDDO            ENDDO
465    
466  C         Add the per-variable attributes            IF (write_attributes) THEN
467            DO i = 1,mnc_cw_vnat(1,indv)  C           Add the per-variable attributes
468              CALL MNC_VAR_ADD_ATTR_STR( fname, vtype,              DO i = 1,mnc_cw_vnat(1,indv)
469       &           mnc_cw_vtnm(i,indv), mnc_cw_vtat(i,indv), myThid)                CALL MNC_VAR_ADD_ATTR_STR( fname, vtype,
470            ENDDO       &             mnc_cw_vtnm(i,indv), mnc_cw_vtat(i,indv), myThid)
471            DO i = 1,mnc_cw_vnat(2,indv)              ENDDO
472              CALL MNC_VAR_ADD_ATTR_INT( fname, vtype,              DO i = 1,mnc_cw_vnat(2,indv)
473       &           mnc_cw_vinm(i,indv), 1, mnc_cw_viat(i,indv), myThid)                CALL MNC_VAR_ADD_ATTR_INT( fname, vtype,
474            ENDDO       &             mnc_cw_vinm(i,indv), 1, mnc_cw_viat(i,indv), myThid)
475            DO i = 1,mnc_cw_vnat(3,indv)              ENDDO
476              CALL MNC_VAR_ADD_ATTR_DBL( fname, vtype,              DO i = 1,mnc_cw_vnat(3,indv)
477       &           mnc_cw_vdnm(i,indv), 1, mnc_cw_vdat(i,indv), myThid)                CALL MNC_VAR_ADD_ATTR_DBL( fname, vtype,
478            ENDDO       &             mnc_cw_vdnm(i,indv), 1, mnc_cw_vdat(i,indv), myThid)
479                ENDDO
480              ENDIF
481    
482    C         Handle missing values
483              use_missing = .FALSE.
484              IF (mnc_cw_vfmv(indv) .EQ. 0) THEN
485                use_missing = .FALSE.
486              ELSE
487                IF (mnc_cw_vfmv(indv) .EQ. 1) THEN
488                  use_missing = .TRUE.
489                  dvm(1)  = mnc_def_dmv(1)
490                  dvm(2)  = mnc_def_dmv(2)
491                  rvm(1)  = mnc_def_rmv(1)
492                  rvm(2)  = mnc_def_rmv(2)
493                  ivm(1)  = mnc_def_imv(1)
494                  ivm(2)  = mnc_def_imv(2)
495                ELSEIF (mnc_cw_vfmv(indv) .EQ. 2) THEN
496                  use_missing = .TRUE.
497                  dvm(1)  = mnc_cw_vmvd(1,indv)
498                  dvm(2)  = mnc_cw_vmvd(2,indv)
499                  rvm(1)  = mnc_cw_vmvr(1,indv)
500                  rvm(2)  = mnc_cw_vmvr(2,indv)
501                  ivm(1)  = mnc_cw_vmvi(1,indv)
502                  ivm(2)  = mnc_cw_vmvi(2,indv)
503                ENDIF
504              ENDIF
505              IF (write_attributes .AND. use_missing) THEN
506                write(msgbuf,'(4a)') 'writing attribute ''missing_value''',
507         &           ' within file ''', fname(1:nfname), ''''
508                IF (stype(1:1) .EQ. 'D') THEN
509                  err = NF_PUT_ATT_DOUBLE(fid, idv, 'missing_value',
510         &             NF_DOUBLE, 1, dvm(2))
511                ELSEIF (stype(1:1) .EQ. 'R') THEN
512                  err = NF_PUT_ATT_REAL(fid, idv, 'missing_value',
513         &             NF_FLOAT, 1, dvm(2))
514                ELSEIF (stype(1:1) .EQ. 'I') THEN
515                  err = NF_PUT_ATT_INT(fid, idv, 'missing_value',
516         &             NF_INT, 1, ivm(2))
517                ENDIF
518                CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
519              ENDIF
520    
521            CALL MNC_FILE_ENDDEF(fname, myThid)            CALL MNC_FILE_ENDDEF(fname, myThid)
522    
# Line 508  C         Write the variable one vector Line 567  C         Write the variable one vector
567          STOP 'ABNORMAL END: S/R MNC_CW_RX_W_OFFSET'          STOP 'ABNORMAL END: S/R MNC_CW_RX_W_OFFSET'
568        ENDIF        ENDIF
569    
570        IF (stype(1:1) .EQ. 'D') THEN        IF (use_missing) THEN
         DO j1 = s(1),e(1)  
           k1 = k2 + j1  
           kr = kr + 1  
           resh_d(kr) = var(k1)  
         ENDDO  
         err = NF_PUT_VARA_DOUBLE(fid, idv, vstart, vcount, resh_d)  
       ENDIF  
       IF (stype(1:1) .EQ. 'R') THEN  
         DO j1 = s(1),e(1)  
           k1 = k2 + j1  
           kr = kr + 1  
           resh_r(kr) = var(k1)  
         ENDDO  
         err = NF_PUT_VARA_REAL(fid, idv, vstart, vcount, resh_r)  
       ENDIF  
       IF (stype(1:1) .EQ. 'I') THEN  
         DO j1 = s(1),e(1)  
           k1 = k2 + j1  
           kr = kr + 1  
           resh_i(kr) = MNC2I( var(k1) )  
         ENDDO  
         err = NF_PUT_VARA_INT(fid, idv, vstart, vcount, resh_i)  
       ENDIF  
571    
572            IF (stype(1:1) .EQ. 'D') THEN
573              DO j1 = s(1),e(1)
574                k1 = k2 + j1
575                kr = kr + 1
576                dval = var(k1)
577                IF (dval .EQ. dvm(1)) THEN
578                  resh_d(kr) = dvm(2)
579                ELSE
580                  resh_d(kr) = dval
581                ENDIF
582              ENDDO
583              err = NF_PUT_VARA_DOUBLE(fid, idv, vstart, vcount, resh_d)
584            ELSEIF (stype(1:1) .EQ. 'R') THEN
585              DO j1 = s(1),e(1)
586                k1 = k2 + j1
587                kr = kr + 1
588                rval = var(k1)
589                IF (rval .EQ. rvm(1)) THEN
590                  resh_r(kr) = rvm(2)
591                ELSE
592                  resh_r(kr) = rval
593                ENDIF
594              ENDDO
595              err = NF_PUT_VARA_REAL(fid, idv, vstart, vcount, resh_r)
596            ELSEIF (stype(1:1) .EQ. 'I') THEN
597              DO j1 = s(1),e(1)
598                k1 = k2 + j1
599                kr = kr + 1
600                ival = MNC2I( var(k1) )
601                IF (ival .EQ. ivm(1)) THEN
602                  resh_i(kr) = ivm(2)
603                ELSE
604                  resh_i(kr) = ival
605                ENDIF
606              ENDDO
607              err = NF_PUT_VARA_INT(fid, idv, vstart, vcount, resh_i)
608            ENDIF
609    
610          ELSE
611            
612            IF (stype(1:1) .EQ. 'D') THEN
613              DO j1 = s(1),e(1)
614                k1 = k2 + j1
615                kr = kr + 1
616                resh_d(kr) = var(k1)
617              ENDDO
618              err = NF_PUT_VARA_DOUBLE(fid, idv, vstart, vcount, resh_d)
619            ELSEIF (stype(1:1) .EQ. 'R') THEN
620              DO j1 = s(1),e(1)
621                k1 = k2 + j1
622                kr = kr + 1
623                resh_r(kr) = var(k1)
624              ENDDO
625              err = NF_PUT_VARA_REAL(fid, idv, vstart, vcount, resh_r)
626            ELSEIF (stype(1:1) .EQ. 'I') THEN
627              DO j1 = s(1),e(1)
628                k1 = k2 + j1
629                kr = kr + 1
630                resh_i(kr) = MNC2I( var(k1) )
631              ENDDO
632              err = NF_PUT_VARA_INT(fid, idv, vstart, vcount, resh_i)
633            ENDIF
634    
635          ENDIF
636        CALL MNC_HANDLE_ERR(err, msgbuf, myThid)        CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
637    
638                      ENDDO                      ENDDO
# Line 631  C     integer f_sNx,f_sNy, alen, atype, Line 731  C     integer f_sNx,f_sNy, alen, atype,
731        integer p(9),s(9),e(9), vstart(9),vcount(9), udo(9)        integer p(9),s(9),e(9), vstart(9),vcount(9), udo(9)
732        integer j1,j2,j3,j4,j5,j6,j7, k1,k2,k3,k4,k5,k6,k7        integer j1,j2,j3,j4,j5,j6,j7, k1,k2,k3,k4,k5,k6,k7
733        character*(MAX_LEN_MBUF) msgbuf        character*(MAX_LEN_MBUF) msgbuf
734        character*(MNC_MAX_CHAR) fname        character*(MNC_MAX_PATH) fname
735        character*(MNC_MAX_CHAR) fname_zs        character*(MNC_MAX_PATH) fname_zs
736        character*(MNC_MAX_CHAR) tmpnm        character*(MNC_MAX_PATH) tmpnm
737        character*(MNC_MAX_CHAR) path_fname        character*(MNC_MAX_PATH) path_fname
738          character*(MNC_MAX_PATH) bpath
739        integer indfg, fg1,fg2        integer indfg, fg1,fg2
740        REAL*8  resh_d( MNC_MAX_BUFF )        REAL*8  resh_d( MNC_MAX_BUFF )
741        REAL*4  resh_r( MNC_MAX_BUFF )        REAL*4  resh_r( MNC_MAX_BUFF )
# Line 646  C     Functions Line 747  C     Functions
747  C     Only do I/O if I am the master thread  C     Only do I/O if I am the master thread
748        _BEGIN_MASTER( myThid )        _BEGIN_MASTER( myThid )
749    
750          DO i = 1,MNC_MAX_PATH
751            bpath(i:i) = ' '
752          ENDDO
753    
754  C     Get the current index for the unlimited dimension from the file  C     Get the current index for the unlimited dimension from the file
755  C     group (or base) name  C     group (or base) name
756        fg1 = IFNBLNK(fbname)        fg1 = IFNBLNK(fbname)
# Line 695  C     Set the bi,bj indicies Line 800  C     Set the bi,bj indicies
800    
801  C         Create the file name  C         Create the file name
802            CALL MNC_CW_GET_TILE_NUM( lbi,lbj, uniq_tnum, myThid)            CALL MNC_CW_GET_TILE_NUM( lbi,lbj, uniq_tnum, myThid)
803            fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)            fname(1:MNC_MAX_PATH) = bpath(1:MNC_MAX_PATH)
804    
805  #ifdef MNC_READ_OLDNAMES  #ifdef MNC_READ_OLDNAMES
806    
# Line 710  C         Create the file name Line 815  C         Create the file name
815    
816  C         Add the path to the file name  C         Add the path to the file name
817            IF (mnc_use_indir) THEN            IF (mnc_use_indir) THEN
818              path_fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)              path_fname(1:MNC_MAX_PATH) = bpath(1:MNC_MAX_PATH)
819              npath = ILNBLNK(mnc_indir_str)              npath = ILNBLNK(mnc_indir_str)
820              path_fname(1:npath) = mnc_indir_str(1:npath)              path_fname(1:npath) = mnc_indir_str(1:npath)
821              path_fname((npath+1):(npath+nfname)) = fname(1:nfname)              path_fname((npath+1):(npath+nfname)) = fname(1:nfname)
822              fname(1:MNC_MAX_CHAR) = path_fname(1:MNC_MAX_CHAR)              fname(1:MNC_MAX_PATH) = path_fname(1:MNC_MAX_PATH)
823              nfname = npath + nfname              nfname = npath + nfname
824            ENDIF            ENDIF
825    
# Line 766  C         Add an iteraton count to the f Line 871  C         Add an iteraton count to the f
871       &            mnc_cw_cit(2,mnc_cw_fgci(indfg)), '.'       &            mnc_cw_cit(2,mnc_cw_fgci(indfg)), '.'
872            ENDIF            ENDIF
873            ntot = ILNBLNK(fname)            ntot = ILNBLNK(fname)
874            path_fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)            path_fname(1:MNC_MAX_PATH) = bpath(1:MNC_MAX_PATH)
875            npath = ILNBLNK(mnc_indir_str)            npath = ILNBLNK(mnc_indir_str)
876  C         Add the face index  C         Add the face index
877            CALL MNC_CW_GET_FACE_NUM( lbi,lbj, uniq_fnum, myThid)            CALL MNC_CW_GET_FACE_NUM( lbi,lbj, uniq_fnum, myThid)
# Line 792  C         WRITE(*,*) 'trying: "', path_f Line 897  C         WRITE(*,*) 'trying: "', path_f
897  C           Create the PER-TILE file name  C           Create the PER-TILE file name
898              CALL MNC_PSNCM(tmpnm, uniq_tnum, MNC_DEF_TMNC)              CALL MNC_PSNCM(tmpnm, uniq_tnum, MNC_DEF_TMNC)
899              k = ILNBLNK(tmpnm)              k = ILNBLNK(tmpnm)
900              path_fname(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)              path_fname(1:MNC_MAX_PATH) = bpath(1:MNC_MAX_PATH)
901              WRITE(path_fname,'(2a,a1,a,a3)')              WRITE(path_fname,'(2a,a1,a,a3)')
902       &           mnc_indir_str(1:npath), fname(1:ntot), 't',       &           mnc_indir_str(1:npath), fname(1:ntot), 't',
903       &           tmpnm(1:k), '.nc'       &           tmpnm(1:k), '.nc'

Legend:
Removed from v.1.34  
changed lines
  Added in v.1.36

  ViewVC Help
Powered by ViewVC 1.1.22