/[MITgcm]/MITgcm/model/src/ini_grid.F
ViewVC logotype

Diff of /MITgcm/model/src/ini_grid.F

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

revision 1.21 by edhill, Wed Sep 15 21:23:32 2004 UTC revision 1.32 by jmc, Fri Sep 5 20:15:28 2008 UTC
# Line 15  C     integrals and spatial avarages. Th Line 15  C     integrals and spatial avarages. Th
15  C     by each thread and initializes only the region of the domain it is  C     by each thread and initializes only the region of the domain it is
16  C     "responsible" for.  C     "responsible" for.
17    
18    C     !CALLING SEQUENCE:
19    C     INI_GRID
20    C      |   -- LOAD_GRID_SPACING
21    C      |   -- INI_VERTICAL_GRID
22    C      |    / INI_CARTESIAN_GRID
23    C      |   /  INI_SPHERICAL_POLAR_GRID
24    C      |   \  INI_CURVILINEAR_GRID
25    C      |    \ INI_CYLINDER_GRID
26    
27  C     !USES:  C     !USES:
28        IMPLICIT NONE        IMPLICIT NONE
29  #include "SIZE.h"  #include "SIZE.h"
30  #include "EEPARAMS.h"  #include "EEPARAMS.h"
31  #include "PARAMS.h"  #include "PARAMS.h"
32  #include "GRID.h"  #include "GRID.h"
 #ifdef ALLOW_MONITOR  
 #include "MONITOR.h"  
 #endif  
33  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
34  #include "MNC_PARAMS.h"  #include "MNC_PARAMS.h"
35  #endif  #endif
36    #ifdef ALLOW_MONITOR
37    #include "MONITOR.h"
38    #endif
39    
40  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
41    C     myThid  :: my Thread Id number
42        INTEGER myThid        INTEGER myThid
43  CEOP  CEOP
44    
45    C     === Functions ====
46          LOGICAL  MASTER_CPU_IO
47          EXTERNAL MASTER_CPU_IO
48    
49  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
50  C     msgBuf - Used for informational I/O.  C     msgBuf  :: Informational/error message buffer
51        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
52    #ifdef ALLOW_MNC
53        INTEGER i        INTEGER i
54    #endif
55    
56    C     load grid spacing (vector) from files
57          CALL LOAD_GRID_SPACING( myThid )
58    
59  C     Set up vertical grid and coordinate system  C     Set up vertical grid and coordinate system
60        CALL INI_VERTICAL_GRID( myThid )        CALL INI_VERTICAL_GRID( myThid )
# Line 47  C     can be fitted into this design. In Line 66  C     can be fitted into this design. In
66  C     also need adding to account for the projections of velocity  C     also need adding to account for the projections of velocity
67  C     vectors onto these grids.  The structure used here also makes it  C     vectors onto these grids.  The structure used here also makes it
68  C     possible to implement less regular grid mappings. In particular:  C     possible to implement less regular grid mappings. In particular:
69  C      o Schemes which leave out blocks of the domain that are    C      o Schemes which leave out blocks of the domain that are
70  C        all land could be supported.                              C        all land could be supported.
71  C      o Multi-level schemes such as icosohedral or cubic          C      o Multi-level schemes such as icosohedral or cubic
72  C        grid projectedions onto a sphere can also be fitted      C        grid projectedions onto a sphere can also be fitted
73  C       within the strategy we use.                              C       within the strategy we use.
74  C        Both of the above also require modifying the support      C        Both of the above also require modifying the support
75  C        routines that map computational blocks to simulation      C        routines that map computational blocks to simulation
76  C        domain blocks.                                            C        domain blocks.
77    
78  C     Set up horizontal grid and coordinate system  C     Set up horizontal grid and coordinate system
79        IF ( usingCartesianGrid ) THEN        IF ( usingCartesianGrid ) THEN
# Line 64  C     Set up horizontal grid and coordin Line 83  C     Set up horizontal grid and coordin
83        ELSEIF ( usingCurvilinearGrid ) THEN        ELSEIF ( usingCurvilinearGrid ) THEN
84          CALL INI_CURVILINEAR_GRID( myThid )          CALL INI_CURVILINEAR_GRID( myThid )
85        ELSEIF ( usingCylindricalGrid ) THEN        ELSEIF ( usingCylindricalGrid ) THEN
86          CALL INI_CYLINDER( myThid )          CALL INI_CYLINDER_GRID( myThid )
87        ELSE        ELSE
88          _BEGIN_MASTER(myThid)          _BEGIN_MASTER(myThid)
89          WRITE(msgBuf,'(2A)') 'S/R INI_GRID: ',          WRITE(msgBuf,'(2A)') 'S/R INI_GRID: ',
# Line 75  C     Set up horizontal grid and coordin Line 94  C     Set up horizontal grid and coordin
94        ENDIF        ENDIF
95    
96  #ifdef ALLOW_MONITOR  #ifdef ALLOW_MONITOR
97        mon_write_stdout = .FALSE.        IF ( MASTER_CPU_IO(myThid) ) THEN
98        mon_write_mnc    = .FALSE.  C--   only the master thread is allowed to switch On/Off mon_write_stdout
99        IF (monitor_stdio) THEN  C     & mon_write_mnc (since it's the only thread that uses those flags):
100          mon_write_stdout = .TRUE.  
101        ENDIF          IF (monitor_stdio) THEN
102                    mon_write_stdout = .TRUE.
103            ELSE
104              mon_write_stdout = .FALSE.
105            ENDIF
106            mon_write_mnc = .FALSE.
107  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
108        IF (useMNC .AND. monitor_mnc) THEN          IF (useMNC .AND. monitor_mnc) THEN
109          DO i = 1,MAX_LEN_MBUF            DO i = 1,MAX_LEN_MBUF
110            mon_fname(i:i) = ' '              mon_fname(i:i) = ' '
111          ENDDO            ENDDO
112          mon_fname(1:12) = 'monitor_grid'            mon_fname(1:12) = 'monitor_grid'
113          CALL MNC_CW_SET_UDIM(mon_fname, 1, myThid)            CALL MNC_CW_SET_UDIM(mon_fname, 1, myThid)
114          mon_write_mnc = .TRUE.            mon_write_mnc = .TRUE.
115        ENDIF          ENDIF
116  #endif /*  ALLOW_MNC  */  #endif /*  ALLOW_MNC  */
117          
118          ENDIF
119    
120  C     Print out statistics of each horizontal grid array (helps when  C     Print out statistics of each horizontal grid array (helps when
121  C     debugging)  C     debugging)
122        CALL MON_PRINTSTATS_RS(1,XC,'XC',myThid)        CALL MON_PRINTSTATS_RS(1,xC,'XC',myThid)
123        CALL MON_PRINTSTATS_RS(1,XG,'XG',myThid)        CALL MON_PRINTSTATS_RS(1,xG,'XG',myThid)
124        CALL MON_PRINTSTATS_RS(1,DXC,'DXC',myThid)        CALL MON_PRINTSTATS_RS(1,dxC,'DXC',myThid)
125        CALL MON_PRINTSTATS_RS(1,DXF,'DXF',myThid)        CALL MON_PRINTSTATS_RS(1,dxF,'DXF',myThid)
126        CALL MON_PRINTSTATS_RS(1,DXG,'DXG',myThid)        CALL MON_PRINTSTATS_RS(1,dxG,'DXG',myThid)
127        CALL MON_PRINTSTATS_RS(1,DXV,'DXV',myThid)        CALL MON_PRINTSTATS_RS(1,dxV,'DXV',myThid)
128        CALL MON_PRINTSTATS_RS(1,YC,'YC',myThid)        CALL MON_PRINTSTATS_RS(1,yC,'YC',myThid)
129        CALL MON_PRINTSTATS_RS(1,YG,'YG',myThid)        CALL MON_PRINTSTATS_RS(1,yG,'YG',myThid)
130        CALL MON_PRINTSTATS_RS(1,DYC,'DYC',myThid)        CALL MON_PRINTSTATS_RS(1,dyC,'DYC',myThid)
131        CALL MON_PRINTSTATS_RS(1,DYF,'DYF',myThid)        CALL MON_PRINTSTATS_RS(1,dyF,'DYF',myThid)
132        CALL MON_PRINTSTATS_RS(1,DYG,'DYG',myThid)        CALL MON_PRINTSTATS_RS(1,dyG,'DYG',myThid)
133        CALL MON_PRINTSTATS_RS(1,DYU,'DYU',myThid)        CALL MON_PRINTSTATS_RS(1,dyU,'DYU',myThid)
134        CALL MON_PRINTSTATS_RS(1,RA,'RA',myThid)        CALL MON_PRINTSTATS_RS(1,rA,'RA',myThid)
135        CALL MON_PRINTSTATS_RS(1,RAW,'RAW',myThid)        CALL MON_PRINTSTATS_RS(1,rAw,'RAW',myThid)
136        CALL MON_PRINTSTATS_RS(1,RAS,'RAS',myThid)        CALL MON_PRINTSTATS_RS(1,rAs,'RAS',myThid)
137        CALL MON_PRINTSTATS_RS(1,RAZ,'RAZ',myThid)        CALL MON_PRINTSTATS_RS(1,rAz,'RAZ',myThid)
138          CALL MON_PRINTSTATS_RS(1,angleCosC,'AngleCS',myThid)
139          CALL MON_PRINTSTATS_RS(1,angleSinC,'AngleSN',myThid)
140    
141          IF ( MASTER_CPU_IO(myThid) ) THEN
142            mon_write_stdout = .FALSE.
143            mon_write_mnc    = .FALSE.
144          ENDIF
145    #endif /* ALLOW_MONITOR */
146    
147        mon_write_stdout = .FALSE.  C--   Everyone else must wait for the grid to be set
148        mon_write_mnc    = .FALSE.        _BARRIER
 #endif  
149    
150        RETURN        RETURN
151        END        END

Legend:
Removed from v.1.21  
changed lines
  Added in v.1.32

  ViewVC Help
Powered by ViewVC 1.1.22