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

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

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

revision 1.14 by jmc, Tue May 12 19:56:36 2009 UTC revision 1.15 by jmc, Sun Jun 28 01:08:25 2009 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3          
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 1  CBOP 1
8  C     !ROUTINE: MNC_CW_WRITE_CVAR  C     !ROUTINE: MNC_CW_WRITE_CVAR
9          
10  C     !INTERFACE:  C     !INTERFACE:
11        SUBROUTINE MNC_CW_WRITE_CVAR(        SUBROUTINE MNC_CW_WRITE_CVAR(
12       I     fname,       I     fname,
13       I     cvname,       I     cvname,
14       I     fid,       I     fid,
15       I     did,       I     did,
16       I     bi, bj,       I     bi, bj,
17       I     myThid )       I     myThid )
18    
19  C     !DESCRIPTION:  C     !DESCRIPTION:
# Line 66  C     variables for text attributes Line 66  C     variables for text attributes
66        xtmin = 0        xtmin = 0
67        ytmin = 0        ytmin = 0
68  #ifdef ALLOW_EXCH2  #ifdef ALLOW_EXCH2
69        xtmin = exch2_tbasex(W2_myTileList(bi))        xtmin = exch2_tbasex(W2_myTileList(bi,bj))
70        ytmin = exch2_tbasey(W2_myTileList(bi))        ytmin = exch2_tbasey(W2_myTileList(bi,bj))
71  #else  #else
72        IF ( .NOT. useCubedSphereExchange ) THEN        IF ( .NOT. useCubedSphereExchange ) THEN
73  C     make sure for a non-cubed-sphere curvi-linear grid,  C     make sure for a non-cubed-sphere curvi-linear grid,
# Line 106  C     Check all the coordinate variables Line 106  C     Check all the coordinate variables
106           long_name = 'X-coordinate of cell center'           long_name = 'X-coordinate of cell center'
107           units     = 'meters'           units     = 'meters'
108          ELSEIF ( usingCurvilinearGrid .OR. rotateGrid ) THEN          ELSEIF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
109           long_name = 'i-index of cell center'           long_name = 'i-index of cell center'
110           units     = 'none'           units     = 'none'
111          ELSEIF ( usingSphericalPolarGrid ) THEN          ELSEIF ( usingSphericalPolarGrid ) THEN
112           long_name = 'longitude of cell center'           long_name = 'longitude of cell center'
# Line 142  C       unknown grid type Line 142  C       unknown grid type
142           long_name = 'X-Coordinate of cell corner'           long_name = 'X-Coordinate of cell corner'
143           units     = 'meters'           units     = 'meters'
144          ELSEIF ( usingCurvilinearGrid .OR. rotateGrid ) THEN          ELSEIF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
145           long_name = 'i-index of cell corner'           long_name = 'i-index of cell corner'
146           units     = 'none'           units     = 'none'
147          ELSEIF ( usingSphericalPolarGrid ) THEN          ELSEIF ( usingSphericalPolarGrid ) THEN
148           long_name = 'longitude of cell corner'           long_name = 'longitude of cell corner'
# Line 179  CML????          rtmp(i) = xC(i-Olx,1,bi Line 179  CML????          rtmp(i) = xC(i-Olx,1,bi
179           long_name = 'X-Coordinate of cell center including overlaps'           long_name = 'X-Coordinate of cell center including overlaps'
180           units     = 'meters'           units     = 'meters'
181          ELSEIF ( usingCurvilinearGrid .OR. rotateGrid ) THEN          ELSEIF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
182           long_name = 'i-index of cell center including overlaps'           long_name = 'i-index of cell center including overlaps'
183           units     = 'none'           units     = 'none'
184          ELSEIF ( usingSphericalPolarGrid ) THEN          ELSEIF ( usingSphericalPolarGrid ) THEN
185           long_name = 'longitude of cell center including overlaps'           long_name = 'longitude of cell center including overlaps'
186           units     = 'degrees_east'           units     = 'degrees_east'
187          ELSEIF ( usingCylindricalGrid ) THEN          ELSEIF ( usingCylindricalGrid ) THEN
188           long_name =           long_name =
189       &        'polar angle coordinate of cell center including overlaps'       &        'polar angle coordinate of cell center including overlaps'
190           units     = 'degrees'           units     = 'degrees'
191          ELSE          ELSE
192  C       unknown grid type  C       unknown grid type
193           print *, 'S/R MNC_CW_CVARS: Ooops, unknown horizontal grid!'           print *, 'S/R MNC_CW_CVARS: Ooops, unknown horizontal grid!'
194          ENDIF          ENDIF
195            
196        ELSEIF (cvname(nnf:nnl) .EQ. 'Y') THEN        ELSEIF (cvname(nnf:nnl) .EQ. 'Y') THEN
197    
198          cv_start(1) = 1          cv_start(1) = 1
# Line 216  C       unknown grid type Line 216  C       unknown grid type
216           long_name = 'Y-Coordinate of cell center'           long_name = 'Y-Coordinate of cell center'
217           units     = 'meters'           units     = 'meters'
218          ELSEIF ( usingCurvilinearGrid .OR. rotateGrid ) THEN          ELSEIF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
219           long_name = 'j-index of cell center'           long_name = 'j-index of cell center'
220           units     = 'none'           units     = 'none'
221          ELSEIF ( usingSphericalPolarGrid ) THEN          ELSEIF ( usingSphericalPolarGrid ) THEN
222           long_name = 'latitude of cell center'           long_name = 'latitude of cell center'
# Line 252  C       unknown grid type Line 252  C       unknown grid type
252           long_name = 'Y-Coordinate of cell corner'           long_name = 'Y-Coordinate of cell corner'
253           units     = 'meters'           units     = 'meters'
254          ELSEIF ( usingCurvilinearGrid .OR. rotateGrid ) THEN          ELSEIF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
255           long_name = 'j-index of cell corner'           long_name = 'j-index of cell corner'
256           units     = 'none'           units     = 'none'
257          ELSEIF ( usingSphericalPolarGrid ) THEN          ELSEIF ( usingSphericalPolarGrid ) THEN
258           long_name = 'latitude of cell corner'           long_name = 'latitude of cell corner'
# Line 288  C       unknown grid type Line 288  C       unknown grid type
288           long_name = 'Y-Coordinate of cell center including overlaps'           long_name = 'Y-Coordinate of cell center including overlaps'
289           units     = 'meters'           units     = 'meters'
290          ELSEIF ( usingCurvilinearGrid .OR. rotateGrid ) THEN          ELSEIF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
291           long_name = 'j-index of cell center including overlaps'           long_name = 'j-index of cell center including overlaps'
292           units     = 'none'           units     = 'none'
293          ELSEIF ( usingSphericalPolarGrid ) THEN          ELSEIF ( usingSphericalPolarGrid ) THEN
294           long_name = 'latitude of cell center including overlaps'           long_name = 'latitude of cell center including overlaps'
295           units     = 'degrees_north'           units     = 'degrees_north'
296          ELSEIF ( usingCylindricalGrid ) THEN          ELSEIF ( usingCylindricalGrid ) THEN
297           long_name =           long_name =
298       &        'radial coordinate of cell center including overlaps'       &        'radial coordinate of cell center including overlaps'
299           units     = 'meters'           units     = 'meters'
300          ELSE          ELSE
# Line 309  C       unknown grid type Line 309  C       unknown grid type
309          DO i = cv_start(1),cv_count(1)          DO i = cv_start(1),cv_count(1)
310            rtmp(i) = rC(i)            rtmp(i) = rC(i)
311          ENDDO          ENDDO
312  C      C
313          long_name = 'vertical coordinate of cell center'          long_name = 'vertical coordinate of cell center'
314          IF ( usingZCoords ) THEN          IF ( usingZCoords ) THEN
315           units     = 'meters'           units     = 'meters'
# Line 410  C       unknown grid type Line 410  C       unknown grid type
410    
411          CALL MNC_FILE_REDEF(fname, myThid)          CALL MNC_FILE_REDEF(fname, myThid)
412  #ifdef REAL4_IS_SLOW  #ifdef REAL4_IS_SLOW
413          err = NF_DEF_VAR(fid, cvname, NF_DOUBLE,          err = NF_DEF_VAR(fid, cvname, NF_DOUBLE,
414       &       nids, cv_did, vid)       &       nids, cv_did, vid)
415  #else  #else
416          err = NF_DEF_VAR(fid, cvname, NF_FLOAT,          err = NF_DEF_VAR(fid, cvname, NF_FLOAT,
417       &       nids, cv_did, vid)       &       nids, cv_did, vid)
418  #endif /* REAL4_IS_SLOW */  #endif /* REAL4_IS_SLOW */
419          i = ILNBLNK( fname )          i = ILNBLNK( fname )
420          write(msgbuf,'(5a)') 'defining coordinate variable ''',          write(msgbuf,'(5a)') 'defining coordinate variable ''',
421       &       cvname(nnf:nnl), ''' in file ''', fname(1:i), ''''       &       cvname(nnf:nnl), ''' in file ''', fname(1:i), ''''
422          CALL MNC_HANDLE_ERR(err, msgbuf, myThid)          CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
423  C     add attributes if set  C     add attributes if set
424          ia = ILNBLNK(long_name)          ia = ILNBLNK(long_name)
425          IF ( ia .GT. 0 ) THEN          IF ( ia .GT. 0 ) THEN
426           err = NF_PUT_ATT_TEXT(fid, vid, 'long_name', ia, long_name)           err = NF_PUT_ATT_TEXT(fid, vid, 'long_name', ia, long_name)
427           write(msgbuf,'(5a)')           write(msgbuf,'(5a)')
428       &     'adding attribute ''long_name'' to coordinate variable ''',       &     'adding attribute ''long_name'' to coordinate variable ''',
429       &     cvname(nnf:nnl), ''' in file ''', fname(1:i), ''''       &     cvname(nnf:nnl), ''' in file ''', fname(1:i), ''''
430           CALL MNC_HANDLE_ERR(err, msgbuf, myThid)           CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
431          ENDIF          ENDIF
432          ia = ILNBLNK(units)          ia = ILNBLNK(units)
433          IF ( ia .GT. 0 ) THEN          IF ( ia .GT. 0 ) THEN
434           err = NF_PUT_ATT_TEXT(fid, vid, 'units', ia, units)           err = NF_PUT_ATT_TEXT(fid, vid, 'units', ia, units)
435           write(msgbuf,'(5a)')           write(msgbuf,'(5a)')
436       &     'adding attribute ''units'' to coordinate variable ''',       &     'adding attribute ''units'' to coordinate variable ''',
437       &     cvname(nnf:nnl), ''' in file ''', fname(1:i), ''''       &     cvname(nnf:nnl), ''' in file ''', fname(1:i), ''''
438           CALL MNC_HANDLE_ERR(err, msgbuf, myThid)           CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
439          ENDIF          ENDIF
440          ia = ILNBLNK(positive)          ia = ILNBLNK(positive)
441          IF ( ia .GT. 0 ) THEN          IF ( ia .GT. 0 ) THEN
442           err = NF_PUT_ATT_TEXT(fid, vid, 'positive', ia, positive)           err = NF_PUT_ATT_TEXT(fid, vid, 'positive', ia, positive)
443           write(msgbuf,'(5a)')           write(msgbuf,'(5a)')
444       &     'adding attribute ''positive'' to coordinate variable ''',       &     'adding attribute ''positive'' to coordinate variable ''',
445       &     cvname(nnf:nnl), ''' in file ''', fname(1:i), ''''       &     cvname(nnf:nnl), ''' in file ''', fname(1:i), ''''
446           CALL MNC_HANDLE_ERR(err, msgbuf, myThid)           CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
447          ENDIF          ENDIF
448  C      C
449          CALL MNC_FILE_ENDDEF(fname, myThid)          CALL MNC_FILE_ENDDEF(fname, myThid)
450  #ifdef REAL4_IS_SLOW  #ifdef REAL4_IS_SLOW
451          err = NF_PUT_VARA_DOUBLE(fid, vid,          err = NF_PUT_VARA_DOUBLE(fid, vid,
452       &       cv_start, cv_count, rtmp)       &       cv_start, cv_count, rtmp)
453  #else  #else
454          err = NF_PUT_VARA_REAL(fid, vid,          err = NF_PUT_VARA_REAL(fid, vid,
455       &       cv_start, cv_count, rtmp)       &       cv_start, cv_count, rtmp)
456  #endif /* REAL4_IS_SLOW */  #endif /* REAL4_IS_SLOW */
457          write(msgbuf,'(5a)') 'writing coordinate variable ''',          write(msgbuf,'(5a)') 'writing coordinate variable ''',
458       &       cvname(nnf:nnl), ''' in file ''', fname(1:i), ''''       &       cvname(nnf:nnl), ''' in file ''', fname(1:i), ''''
459          CALL MNC_HANDLE_ERR(err, msgbuf, myThid)          CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
460            
461        ENDIF        ENDIF
462    
463        RETURN        RETURN

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

  ViewVC Help
Powered by ViewVC 1.1.22