/[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.31 - (hide annotations) (download)
Tue Nov 28 22:47:13 2006 UTC (17 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59, checkpoint58y_post, checkpoint58t_post, checkpoint60, checkpoint61, checkpoint58w_post, mitgcm_mapl_00, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint58v_post, checkpoint58x_post, checkpoint59j, checkpoint58u_post, checkpoint58s_post, checkpoint61b, checkpoint61c, checkpoint61a
Changes since 1.30: +16 -10 lines
allow to read vertical arrays: tRef,sRef,delR & delRc from (binary) file ;
   + start adding anelastic-code parameters

1 jmc 1.31 C $Header: /u/gcmpack/MITgcm/model/src/ini_grid.F,v 1.30 2006/10/17 18:20:18 jmc 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     #include "PARAMS.h"
23 jmc 1.28 #include "GRID.h"
24 edhill 1.23 #ifdef ALLOW_MNC
25     #include "MNC_PARAMS.h"
26     #endif
27 edhill 1.21 #ifdef ALLOW_MONITOR
28     #include "MONITOR.h"
29     #endif
30 cnh 1.1
31 cnh 1.10 C !INPUT/OUTPUT PARAMETERS:
32 jmc 1.31 C myThid :: my Thread Id number
33 cnh 1.1 INTEGER myThid
34 edhill 1.21 CEOP
35 cnh 1.1
36 jmc 1.30 C === Functions ====
37     LOGICAL MASTER_CPU_IO
38     EXTERNAL MASTER_CPU_IO
39    
40 cnh 1.10 C !LOCAL VARIABLES:
41 jmc 1.31 C msgBuf :: Informational/error message buffer
42 cnh 1.1 CHARACTER*(MAX_LEN_MBUF) msgBuf
43 jmc 1.26 #ifdef ALLOW_MNC
44 edhill 1.21 INTEGER i
45 jmc 1.26 #endif
46 cnh 1.1
47 jmc 1.25 C load grid spacing (vector) from files
48     CALL LOAD_GRID_SPACING( myThid )
49    
50 jmc 1.31 C Set up reference vertical profile (vector) for state variables
51     C jmc: this call will not stay here but will move to S/R INITIALISE_FIXED
52     C (a better place) once anelatic initialisation is cleaned-up.
53     CALL INI_REFERENCE_STATE( myThid )
54    
55 edhill 1.21 C Set up vertical grid and coordinate system
56 adcroft 1.4 CALL INI_VERTICAL_GRID( myThid )
57    
58 edhill 1.21 C Two examples are shown in this code. One illustrates the
59     C initialization of a cartesian grid. The other shows the
60     C inialization of a spherical polar grid. Other orthonormal grids
61     C can be fitted into this design. In this case custom metric terms
62     C also need adding to account for the projections of velocity
63     C vectors onto these grids. The structure used here also makes it
64     C possible to implement less regular grid mappings. In particular:
65 jmc 1.31 C o Schemes which leave out blocks of the domain that are
66     C all land could be supported.
67     C o Multi-level schemes such as icosohedral or cubic
68     C grid projectedions onto a sphere can also be fitted
69     C within the strategy we use.
70     C Both of the above also require modifying the support
71     C routines that map computational blocks to simulation
72     C domain blocks.
73 edhill 1.21
74     C Set up horizontal grid and coordinate system
75 cnh 1.1 IF ( usingCartesianGrid ) THEN
76 edhill 1.21 CALL INI_CARTESIAN_GRID( myThid )
77 cnh 1.1 ELSEIF ( usingSphericalPolarGrid ) THEN
78 edhill 1.21 CALL INI_SPHERICAL_POLAR_GRID( myThid )
79 adcroft 1.8 ELSEIF ( usingCurvilinearGrid ) THEN
80 edhill 1.21 CALL INI_CURVILINEAR_GRID( myThid )
81 afe 1.17 ELSEIF ( usingCylindricalGrid ) THEN
82 jmc 1.24 CALL INI_CYLINDER_GRID( myThid )
83 cnh 1.1 ELSE
84 edhill 1.21 _BEGIN_MASTER(myThid)
85     WRITE(msgBuf,'(2A)') 'S/R INI_GRID: ',
86     & 'No grid coordinate system has been selected'
87     CALL PRINT_ERROR( msgBuf , myThid)
88     STOP 'ABNORMAL END: S/R INI_GRID'
89     _END_MASTER(myThid)
90 cnh 1.1 ENDIF
91 dimitri 1.15
92 adcroft 1.20 #ifdef ALLOW_MONITOR
93 jmc 1.30 IF ( MASTER_CPU_IO(myThid) ) THEN
94 jmc 1.28 C-- only the master thread is allowed to switch On/Off mon_write_stdout
95     C & mon_write_mnc (since it's the only thread that uses those flags):
96    
97     IF (monitor_stdio) THEN
98     mon_write_stdout = .TRUE.
99     ELSE
100     mon_write_stdout = .FALSE.
101     ENDIF
102     mon_write_mnc = .FALSE.
103 edhill 1.21 #ifdef ALLOW_MNC
104 jmc 1.28 IF (useMNC .AND. monitor_mnc) THEN
105     DO i = 1,MAX_LEN_MBUF
106     mon_fname(i:i) = ' '
107     ENDDO
108     mon_fname(1:12) = 'monitor_grid'
109     CALL MNC_CW_SET_UDIM(mon_fname, 1, myThid)
110     mon_write_mnc = .TRUE.
111     ENDIF
112     #endif /* ALLOW_MNC */
113    
114 edhill 1.21 ENDIF
115 jmc 1.28
116 edhill 1.21 C Print out statistics of each horizontal grid array (helps when
117     C debugging)
118 jmc 1.28 CALL MON_PRINTSTATS_RS(1,xC,'XC',myThid)
119     CALL MON_PRINTSTATS_RS(1,xG,'XG',myThid)
120     CALL MON_PRINTSTATS_RS(1,dxC,'DXC',myThid)
121     CALL MON_PRINTSTATS_RS(1,dxF,'DXF',myThid)
122     CALL MON_PRINTSTATS_RS(1,dxG,'DXG',myThid)
123     CALL MON_PRINTSTATS_RS(1,dxV,'DXV',myThid)
124     CALL MON_PRINTSTATS_RS(1,yC,'YC',myThid)
125     CALL MON_PRINTSTATS_RS(1,yG,'YG',myThid)
126     CALL MON_PRINTSTATS_RS(1,dyC,'DYC',myThid)
127     CALL MON_PRINTSTATS_RS(1,dyF,'DYF',myThid)
128     CALL MON_PRINTSTATS_RS(1,dyG,'DYG',myThid)
129     CALL MON_PRINTSTATS_RS(1,dyU,'DYU',myThid)
130     CALL MON_PRINTSTATS_RS(1,rA,'RA',myThid)
131     CALL MON_PRINTSTATS_RS(1,rAw,'RAW',myThid)
132     CALL MON_PRINTSTATS_RS(1,rAs,'RAS',myThid)
133     CALL MON_PRINTSTATS_RS(1,rAz,'RAZ',myThid)
134 jmc 1.24 CALL MON_PRINTSTATS_RS(1,angleCosC,'AngleCS',myThid)
135     CALL MON_PRINTSTATS_RS(1,angleSinC,'AngleSN',myThid)
136 edhill 1.21
137 jmc 1.30 IF ( MASTER_CPU_IO(myThid) ) THEN
138 jmc 1.28 mon_write_stdout = .FALSE.
139     mon_write_mnc = .FALSE.
140     ENDIF
141     #endif /* ALLOW_MONITOR */
142 jmc 1.30
143     C-- Everyone else must wait for the grid to be set
144     _BARRIER
145 adcroft 1.8
146 cnh 1.1 RETURN
147     END

  ViewVC Help
Powered by ViewVC 1.1.22