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

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

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

revision 1.7 by edhill, Fri Mar 19 03:28:36 2004 UTC revision 1.15 by edhill, Fri Mar 10 22:01:53 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_DIM_INIT
9    
10    C     !INTERFACE:
11        SUBROUTINE MNC_DIM_INIT(        SUBROUTINE MNC_DIM_INIT(
12       I     fname,       I     fname,
13       I     dname,       I     dname,
14       I     dlen,       I     dlen,
15       I     myThid )       I     myThid )
16    
17  C     Arguments  C     !DESCRIPTION:
18    C     Create a dimension within the MNC look-up tables.
19    
20    C     !INPUT PARAMETERS:
21        integer myThid, dlen        integer myThid, dlen
22        character*(*) fname, dname        character*(*) fname, dname
23    CEOP
24    
25        CALL MNC_DIM_INIT_ALL(fname, dname, dlen, 'Y', myThid)        CALL MNC_DIM_INIT_ALL(fname, dname, dlen, 'Y', myThid)
26    
27        RETURN        RETURN
28        END        END
29    
   
30  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
31    CBOP 1
32    C     !ROUTINE: MNC_DIM_INIT_ALL
33    
34    C     !INTERFACE:
35        SUBROUTINE MNC_DIM_INIT_ALL(        SUBROUTINE MNC_DIM_INIT_ALL(
36       I     fname,       I     fname,
37       I     dname,       I     dname,
# Line 30  C---+----1----+----2----+----3----+----4 Line 39  C---+----1----+----2----+----3----+----4
39       I     doWrite,       I     doWrite,
40       I     myThid )       I     myThid )
41    
42    C     !DESCRIPTION:
43    C     Create a dimension within the MNC look-up tables.
44    
45    C     !USES:
46          implicit none
47    
48    C     !INPUT PARAMETERS:
49          integer myThid, dlen
50          character*(*) fname, dname
51          character*(1) doWrite
52    CEOP
53    
54          CALL MNC_DIM_INIT_ALL_CV(fname,dname,dlen,doWrite,-1,-1,myThid)
55          
56          RETURN
57          END
58    
59    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
60    CBOP 1
61    C     !ROUTINE: MNC_DIM_INIT_ALL_CV
62    
63    C     !INTERFACE:
64          SUBROUTINE MNC_DIM_INIT_ALL_CV(
65         I     fname,
66         I     dname,
67         I     dlen,
68         I     doWrite,
69         I     bi,bj,
70         I     myThid )
71    
72    C     !DESCRIPTION:
73    C     Create a dimension within the MNC look-up tables.
74    
75    C     !USES:
76        implicit none        implicit none
77  #include "netcdf.inc"  #include "netcdf.inc"
78  #include "mnc_common.h"  #include "mnc_common.h"
79  #include "EEPARAMS.h"  #include "EEPARAMS.h"
80    
81  C     Arguments  C     !INPUT PARAMETERS:
82        integer myThid, dlen        integer myThid, dlen, bi,bj
83        character*(*) fname, dname        character*(*) fname, dname
84        character*(1) doWrite        character*(1) doWrite
85    CEOP
86    
87    C     !LOCAL VARIABLES:
88          integer i,j, indf,indd, n,nf, dnf,dnl
89          integer ntmp, idd, err, tlen
90          character*(MAX_LEN_MBUF) msgbuf
91    
92  C     Functions  C     Functions
93        integer ILNBLNK, IFNBLNK        integer ILNBLNK, IFNBLNK
94    
 C     Local Variables  
       integer i,j, indf,indd, n,nf, dnf,dnl, ntmp, idd, err, tlen  
       character*(MAX_LEN_MBUF) msgbuf  
   
95        nf = ILNBLNK(fname)        nf = ILNBLNK(fname)
96    
97        dnf = IFNBLNK(dname)        dnf = IFNBLNK(dname)
98        dnl = ILNBLNK(dname)        dnl = ILNBLNK(dname)
99    
100  C     Verify that the file exists  C     Verify that the file exists
101        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)
102        IF ( indf .LT. 1 ) THEN        IF ( indf .LT. 1 ) THEN
103          write(msgbuf,'(3a)') 'MNC ERROR: file ''', fname(1:nf),          write(msgbuf,'(3a)') 'MNC ERROR: file ''', fname(1:nf),
104       &       ''' does not exist'       &       ''' does not exist'
# Line 87  C           Its OK, the names and sizes Line 132  C           Its OK, the names and sizes
132          ENDIF          ENDIF
133        ENDDO        ENDDO
134    
135        CALL MNC_GET_NEXT_EMPTY_IND(MNC_MAX_ID, mnc_d_names, indd, myThid)        CALL MNC_GET_NEXT_EMPTY_IND(MNC_MAX_ID, mnc_d_names,
136         &     'mnc_d_names', indd, myThid)
137    
138  C     Create the dim within the file  C     Create the dim within the file
139        IF (doWrite(1:1) .EQ. 'Y') THEN        IF (doWrite(1:1) .EQ. 'Y') THEN
# Line 101  C     Create the dim within the file Line 147  C     Create the dim within the file
147       &       'dim ''', dname(dnf:dnl), ''' in file ''', fname(1:nf)       &       'dim ''', dname(dnf:dnl), ''' in file ''', fname(1:nf)
148          CALL MNC_HANDLE_ERR(err, msgbuf, myThid)          CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
149    
150    C       Create and write the associated CF-convention
151    C       coordinate variable
152            IF (bi .GT. -1) THEN
153              CALL MNC_CW_WRITE_CVAR(fname, dname(dnf:dnl),
154         &         mnc_f_info(indf,2), idd, bi, bj, myThid)
155            ENDIF
156    
157        ENDIF        ENDIF
158    
159  C     Add to tables  C     Add to tables
# Line 114  C     Add to tables Line 167  C     Add to tables
167        END        END
168    
169  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
170    CBOP 1
171    C     !ROUTINE: MNC_DIM_UNLIM_SIZE
172    
173    C     !INTERFACE:
174        SUBROUTINE MNC_DIM_UNLIM_SIZE(        SUBROUTINE MNC_DIM_UNLIM_SIZE(
175       I     fname,       I     fname,
176       I     unlim_sz,       I     unlim_sz,
177       I     myThid )       I     myThid )
178    
179    C     !DESCRIPTION:
180    C     Get the size of the unlimited dimension.
181          
182    C     !USES:
183        implicit none        implicit none
184  #include "netcdf.inc"  #include "netcdf.inc"
185  #include "mnc_common.h"  #include "mnc_common.h"
186  #include "EEPARAMS.h"  #include "EEPARAMS.h"
187    
188  C     Arguments  C     !INPUT PARAMETERS:
189        integer myThid, unlim_sz        integer myThid, unlim_sz
190        character*(*) fname        character*(*) fname
191    CEOP
192    
193  C     Functions  C     !LOCAL VARIABLES:
       integer ILNBLNK, IFNBLNK  
   
 C     Local Variables  
194        integer i,j, nf, indf, fid, unlimid, err        integer i,j, nf, indf, fid, unlimid, err
195        character*(MAX_LEN_MBUF) msgbuf        character*(MAX_LEN_MBUF) msgbuf
196    
197    C     Functions
198          integer ILNBLNK
199    
200        nf = ILNBLNK(fname)        nf = ILNBLNK(fname)
201    
202  C     Verify that the file exists  C     Verify that the file exists
203        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)
204        IF (indf .LT. 1) THEN        IF (indf .LT. 1) THEN
205          write(msgbuf,'(3a)') 'MNC ERROR: file ''', fname(1:nf),          write(msgbuf,'(3a)') 'MNC ERROR: file ''', fname(1:nf),
206       &       ''' does not exist'       &       ''' does not exist'

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

  ViewVC Help
Powered by ViewVC 1.1.22