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

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

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


Revision 1.28 - (hide annotations) (download)
Tue Jul 25 22:23:36 2006 UTC (17 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58o_post, checkpoint58n_post
Changes since 1.27: +59 -36 lines
standard way to switch monitor flags

1 jmc 1.28 C $Header: /u/gcmpack/MITgcm/model/src/ini_grid.F,v 1.27 2005/11/07 18:26:02 cnh Exp $
2 adcroft 1.8 C $Name: $
3 cnh 1.1
4 jmc 1.19 #include "PACKAGES_CONFIG.h"
5 cnh 1.5 #include "CPP_OPTIONS.h"
6 cnh 1.1
7 cnh 1.10 CBOP
8     C !ROUTINE: INI_GRID
9 edhill 1.21
10 cnh 1.10 C !INTERFACE:
11 cnh 1.1 SUBROUTINE INI_GRID( myThid )
12 edhill 1.21 C !DESCRIPTION:
13     C These arrays are used throughout the code in evaluating gradients,
14     C integrals and spatial avarages. This routine is called separately
15     C by each thread and initializes only the region of the domain it is
16     C "responsible" for.
17 cnh 1.10
18     C !USES:
19 adcroft 1.6 IMPLICIT NONE
20 cnh 1.1 #include "SIZE.h"
21     #include "EEPARAMS.h"
22 jmc 1.28 #include "EESUPPORT.h"
23 cnh 1.1 #include "PARAMS.h"
24 jmc 1.28 #include "GRID.h"
25 edhill 1.23 #ifdef ALLOW_MNC
26     #include "MNC_PARAMS.h"
27     #endif
28 edhill 1.21 #ifdef ALLOW_MONITOR
29     #include "MONITOR.h"
30     #endif
31 cnh 1.1
32 cnh 1.10 C !INPUT/OUTPUT PARAMETERS:
33 cnh 1.1 INTEGER myThid
34 edhill 1.21 CEOP
35 cnh 1.1
36 cnh 1.10 C !LOCAL VARIABLES:
37 cnh 1.1 C msgBuf - Used for informational I/O.
38     CHARACTER*(MAX_LEN_MBUF) msgBuf
39 jmc 1.26 #ifdef ALLOW_MNC
40 edhill 1.21 INTEGER i
41 jmc 1.26 #endif
42 cnh 1.1
43 jmc 1.25 C load grid spacing (vector) from files
44 cnh 1.27 _BARRIER
45 jmc 1.25 CALL LOAD_GRID_SPACING( myThid )
46 cnh 1.27 _BARRIER
47 jmc 1.25
48 edhill 1.21 C Set up vertical grid and coordinate system
49 adcroft 1.4 CALL INI_VERTICAL_GRID( myThid )
50    
51 edhill 1.21 C Two examples are shown in this code. One illustrates the
52     C initialization of a cartesian grid. The other shows the
53     C inialization of a spherical polar grid. Other orthonormal grids
54     C can be fitted into this design. In this case custom metric terms
55     C also need adding to account for the projections of velocity
56     C vectors onto these grids. The structure used here also makes it
57     C possible to implement less regular grid mappings. In particular:
58     C o Schemes which leave out blocks of the domain that are
59     C all land could be supported.
60     C o Multi-level schemes such as icosohedral or cubic
61     C grid projectedions onto a sphere can also be fitted
62     C within the strategy we use.
63     C Both of the above also require modifying the support
64     C routines that map computational blocks to simulation
65     C domain blocks.
66    
67     C Set up horizontal grid and coordinate system
68 cnh 1.1 IF ( usingCartesianGrid ) THEN
69 edhill 1.21 CALL INI_CARTESIAN_GRID( myThid )
70 cnh 1.1 ELSEIF ( usingSphericalPolarGrid ) THEN
71 edhill 1.21 CALL INI_SPHERICAL_POLAR_GRID( myThid )
72 adcroft 1.8 ELSEIF ( usingCurvilinearGrid ) THEN
73 edhill 1.21 CALL INI_CURVILINEAR_GRID( myThid )
74 afe 1.17 ELSEIF ( usingCylindricalGrid ) THEN
75 jmc 1.24 CALL INI_CYLINDER_GRID( myThid )
76 cnh 1.1 ELSE
77 edhill 1.21 _BEGIN_MASTER(myThid)
78     WRITE(msgBuf,'(2A)') 'S/R INI_GRID: ',
79     & 'No grid coordinate system has been selected'
80     CALL PRINT_ERROR( msgBuf , myThid)
81     STOP 'ABNORMAL END: S/R INI_GRID'
82     _END_MASTER(myThid)
83 cnh 1.1 ENDIF
84 dimitri 1.15
85 adcroft 1.20 #ifdef ALLOW_MONITOR
86 jmc 1.28 #ifdef ALLOW_USE_MPI
87     IF ( .NOT.useSingleCPUIO .OR. mpiMyId.EQ.0 ) THEN
88     #endif /* ALLOW_USE_MPI */
89     _BEGIN_MASTER(myThid)
90     C-- only the master thread is allowed to switch On/Off mon_write_stdout
91     C & mon_write_mnc (since it's the only thread that uses those flags):
92    
93     IF (monitor_stdio) THEN
94     mon_write_stdout = .TRUE.
95     ELSE
96     mon_write_stdout = .FALSE.
97     ENDIF
98     mon_write_mnc = .FALSE.
99 edhill 1.21 #ifdef ALLOW_MNC
100 jmc 1.28 IF (useMNC .AND. monitor_mnc) THEN
101     DO i = 1,MAX_LEN_MBUF
102     mon_fname(i:i) = ' '
103     ENDDO
104     mon_fname(1:12) = 'monitor_grid'
105     CALL MNC_CW_SET_UDIM(mon_fname, 1, myThid)
106     mon_write_mnc = .TRUE.
107     ENDIF
108     #endif /* ALLOW_MNC */
109    
110     _END_MASTER(myThid)
111     #ifdef ALLOW_USE_MPI
112 edhill 1.21 ENDIF
113 jmc 1.28 #endif /* ALLOW_USE_MPI */
114    
115 edhill 1.21 C Print out statistics of each horizontal grid array (helps when
116     C debugging)
117 jmc 1.28 CALL MON_PRINTSTATS_RS(1,xC,'XC',myThid)
118     CALL MON_PRINTSTATS_RS(1,xG,'XG',myThid)
119     CALL MON_PRINTSTATS_RS(1,dxC,'DXC',myThid)
120     CALL MON_PRINTSTATS_RS(1,dxF,'DXF',myThid)
121     CALL MON_PRINTSTATS_RS(1,dxG,'DXG',myThid)
122     CALL MON_PRINTSTATS_RS(1,dxV,'DXV',myThid)
123     CALL MON_PRINTSTATS_RS(1,yC,'YC',myThid)
124     CALL MON_PRINTSTATS_RS(1,yG,'YG',myThid)
125     CALL MON_PRINTSTATS_RS(1,dyC,'DYC',myThid)
126     CALL MON_PRINTSTATS_RS(1,dyF,'DYF',myThid)
127     CALL MON_PRINTSTATS_RS(1,dyG,'DYG',myThid)
128     CALL MON_PRINTSTATS_RS(1,dyU,'DYU',myThid)
129     CALL MON_PRINTSTATS_RS(1,rA,'RA',myThid)
130     CALL MON_PRINTSTATS_RS(1,rAw,'RAW',myThid)
131     CALL MON_PRINTSTATS_RS(1,rAs,'RAS',myThid)
132     CALL MON_PRINTSTATS_RS(1,rAz,'RAZ',myThid)
133 jmc 1.24 CALL MON_PRINTSTATS_RS(1,angleCosC,'AngleCS',myThid)
134     CALL MON_PRINTSTATS_RS(1,angleSinC,'AngleSN',myThid)
135 edhill 1.21
136 jmc 1.28 #ifdef ALLOW_USE_MPI
137     IF ( .NOT.useSingleCPUIO .OR. mpiMyId.EQ.0 ) THEN
138     #endif /* ALLOW_USE_MPI */
139     _BEGIN_MASTER(myThid)
140    
141     mon_write_stdout = .FALSE.
142     mon_write_mnc = .FALSE.
143    
144     _END_MASTER(myThid)
145     #ifdef ALLOW_USE_MPI
146     ENDIF
147     #endif /* ALLOW_USE_MPI */
148     #endif /* ALLOW_MONITOR */
149 adcroft 1.8
150 cnh 1.1 RETURN
151     END

  ViewVC Help
Powered by ViewVC 1.1.22