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

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

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

revision 1.8 by edhill, Sat Jan 31 04:13:09 2004 UTC revision 1.24 by mlosch, Thu May 22 08:29:06 2008 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_INIT
9    
10        SUBROUTINE MNC_INIT()  C     !INTERFACE:
11          SUBROUTINE MNC_INIT( myThid )
12    
13    C     !DESCRIPTION:
14    C     Initialize (zero) the look-up tables.  This routine should
15    C     \textbf{always} be run before any other MNC subroutines to ensure
16    C     that the lookup tables start in a well-defined state.
17          
18    C     !USES:
19    #include "SIZE.h"
20    #include "EEPARAMS.h"
21    #include "EESUPPORT.h"
22    #include "PARAMS.h"
23  #include "mnc_common.h"  #include "mnc_common.h"
24    #include "MNC_PARAMS.h"
25    
26  C     Arguments  C     !INPUT PARAMETERS:
27          integer myThid
28    CEOP
29    
30  C     Local Variables  C     !LOCAL VARIABLES:
31        integer i,j, g, v        integer i,j, g
32        character blank*(MNC_MAX_CHAR)        character blank*(MNC_MAX_CHAR)
33          character bpath*(MNC_MAX_PATH)
34    
35  C     Write blanks or zeros to all the internal names and ID tables  C     Write blanks or zeros to all the internal names and ID tables
36        DO i = 1,mnc_max_char        DO i = 1,MNC_MAX_CHAR
37          blank(i:i) = ' ';          blank(i:i) = ' '
38          ENDDO
39          DO i = 1,MNC_MAX_PATH
40            bpath(i:i) = ' '
41        ENDDO        ENDDO
42    
43        mnc_blank_name(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)        mnc_blank_name(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)
44        DO i = 1,MNC_MAX_ID        DO i = 1,MNC_MAX_FID
45          mnc_d_size(i) = 0          mnc_f_names(i)(1:MNC_MAX_PATH) = bpath(1:MNC_MAX_PATH)
         mnc_d_ids(i)  = 0  
         mnc_f_names(i)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)  
         mnc_g_names(i)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)  
         mnc_v_names(i)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)  
         mnc_d_names(i)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)  
46          DO j = 1,MNC_MAX_INFO          DO j = 1,MNC_MAX_INFO
47            mnc_f_info(i,j) = 0            mnc_f_info(i,j) = 0
48            mnc_fv_ids(i,j) = 0            mnc_fv_ids(i,j) = 0
# Line 34  C     Write blanks or zeros to all the i Line 50  C     Write blanks or zeros to all the i
50            mnc_f_alld(i,j) = 0            mnc_f_alld(i,j) = 0
51          ENDDO          ENDDO
52        ENDDO        ENDDO
53          DO i = 1,MNC_MAX_ID
54            mnc_d_size(i) = 0
55            mnc_d_ids(i)  = 0
56            mnc_g_names(i)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)
57            mnc_v_names(i)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)
58            mnc_d_names(i)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)
59          ENDDO
60    
61  C     The outer tables  C     Blank the CW tables
62        DO g = 1,MNC_MAX_ID        DO g = 1,MNC_MAX_ID
63          mnc_cw_gname(g)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)          mnc_cw_gname(g)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)
64          mnc_cw_vname(g)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)          mnc_cw_vname(g)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)
65          mnc_cw_vgind(g) = 0          mnc_cw_vgind(g) = 0
66            mnc_cw_vfmv(g) = 0
67          mnc_cw_ndim(g) = 0          mnc_cw_ndim(g) = 0
68            mnc_cw_fgnm(g)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)
69            mnc_cw_fgud(g) = 0
70            mnc_cw_fgis(g) = 0
71            mnc_cw_fgci(g) = 1
72    C       mnc_cw_cvnm(g)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)
73          DO i = 1,MNC_CW_MAX_I          DO i = 1,MNC_CW_MAX_I
74            mnc_cw_dn(i,g)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)            mnc_cw_dn(i,g)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)
75            mnc_cw_vtnm(i,g)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)            mnc_cw_vtnm(i,g)(1:MNC_MAX_CHAR) = blank(1:MNC_MAX_CHAR)
# Line 56  C     The outer tables Line 85  C     The outer tables
85          DO i = 1,3          DO i = 1,3
86            mnc_cw_vnat(i,g) = 0            mnc_cw_vnat(i,g) = 0
87          ENDDO          ENDDO
88            DO i = 1,2
89               mnc_cw_vbij(i,g) = 0
90               mnc_cw_vmvi(i,g) = 0
91               mnc_cw_vmvr(i,g) = 0.0
92               mnc_cw_vmvd(i,g) = 0.0D0
93    C          mnc_cw_cvse(i,g) = 0
94            ENDDO
95        ENDDO        ENDDO
96    
97        RETURN        DO i = 1,MNC_MAX_INFO
98        END          mnc_cw_cit(1,i) = 0
99            mnc_cw_cit(2,i) = 0
100  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|          mnc_cw_cit(3,i) = -1
101          ENDDO
102        SUBROUTINE MNC_DUMP()  
103          DO i = 1,2
104  #include "mnc_common.h"         mnc_def_imv(i) = UNSET_I
105           mnc_def_rmv(i) = UNSET_FLOAT4
106  C     Arguments         mnc_def_dmv(i) = UNSET_FLOAT8
107          ENDDO
108  C     Local Variables  
109        integer i,j, n_id  C     The default for all file types is to add the iter to the name and
110    C     grow them in "lock step" together
111  C     n_id = mnc_max_id        mnc_cw_cit(1,1) = 1
112        n_id = 5        mnc_cw_cit(2,1) = nIter0
113    
114        write(*,*) 'mnc_f_names :'  C     Here, we do not add the iter to the file name
115        DO i = 1,n_id        mnc_cw_cit(1,2) = -1
116          write(*,'(a,a40)') '  :', mnc_f_names(i)        mnc_cw_cit(2,2) = -1
117        ENDDO  
118        write(*,*) 'mnc_g_names :'  C     For checkpoint files, we want to use the current iter but we do
119        DO i = 1,n_id  C     not (by default, anyway) want to update the current iter for
120          write(*,'(a,a40)') '  :', mnc_g_names(i)  C     everything else
121        ENDDO        mnc_cw_cit(1,3) = 3
122        write(*,*) 'mnc_v_names :'        mnc_cw_cit(2,3) = nIter0
123        DO i = 1,n_id  
124          write(*,'(a,a40)') '  :', mnc_v_names(i)  C     DO i = 1,MNC_CW_CVDAT
125        ENDDO  C     mnc_cw_cvdt(i) = 0.0D0
126        write(*,*) 'mnc_d_names :'  C     ENDDO
       DO i = 1,n_id  
         write(*,'(a,a40)') '  :', mnc_d_names(i)  
       ENDDO  
   
       write(*,*) 'mnc_d_ids, mnc_d_size :'  
       DO i = 1,n_id  
         write(*,*) mnc_d_ids(i), mnc_d_size(i)  
       ENDDO  
   
       write(*,*) 'mnc_f_info :'  
       DO i = 1,n_id  
         write(*,*) (mnc_f_info(i,j), j=1,30)  
       ENDDO  
       write(*,*) 'mnc_fd_ind :'  
       DO i = 1,n_id  
         write(*,*) (mnc_fd_ind(i,j), j=1,30)  
       ENDDO  
       write(*,*) 'mnc_fv_ids :'  
       DO i = 1,n_id  
         write(*,*) (mnc_fv_ids(i,j), j=1,30)  
       ENDDO  
       write(*,*) 'mnc_f_alld :'  
       DO i = 1,n_id  
         write(*,*) (mnc_f_alld(i,j), j=1,30)  
       ENDDO  
127    
128        RETURN        RETURN
129        END        END

Legend:
Removed from v.1.8  
changed lines
  Added in v.1.24

  ViewVC Help
Powered by ViewVC 1.1.22