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

Contents of /MITgcm/model/src/ini_cori.F

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


Revision 1.27 - (show annotations) (download)
Wed May 28 03:06:57 2008 UTC (16 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59r, checkpoint61f, checkpoint61n, checkpoint61e, checkpoint61g, checkpoint61d, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i
Changes since 1.26: +49 -5 lines
reading of Coriolis from files & cubed-sphere case: read fCoriG from
 6 faced-files (like grid-files) to get the 2 missing corners right.

1 C $Header: /u/gcmpack/MITgcm/model/src/ini_cori.F,v 1.26 2006/10/17 18:20:18 jmc Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: INI_CORI
9
10 C !INTERFACE:
11 SUBROUTINE INI_CORI( myThid )
12 C !DESCRIPTION:
13 C Initialise coriolis term.
14
15 C !USES:
16 IMPLICIT NONE
17 #include "SIZE.h"
18 #include "EEPARAMS.h"
19 #include "PARAMS.h"
20 #include "GRID.h"
21 #ifdef ALLOW_EXCH2
22 # include "W2_EXCH2_TOPOLOGY.h"
23 # include "W2_EXCH2_PARAMS.h"
24 #endif
25 #ifdef ALLOW_MNC
26 # include "MNC_PARAMS.h"
27 #endif
28 #ifdef ALLOW_MONITOR
29 # include "MONITOR.h"
30 #endif
31
32 C !INPUT/OUTPUT PARAMETERS:
33 INTEGER myThid
34 CEOP
35
36 C === Functions ====
37 LOGICAL MASTER_CPU_IO
38 EXTERNAL MASTER_CPU_IO
39
40 C !LOCAL VARIABLES:
41 C bi,bj :: Tile Indices counters
42 C i, j :: Loop counters
43 C facGrid :: Factor for grid to meter conversion
44 INTEGER bi,bj
45 INTEGER i, j
46 _RL facGrid
47 #ifndef OLD_GRID_IO
48 INTEGER myTile, iG, iLen
49 CHARACTER*(MAX_LEN_FNAM) fName
50 CHARACTER*(MAX_LEN_MBUF) msgBuf
51 INTEGER ILNBLNK
52 EXTERNAL ILNBLNK
53 #endif
54
55
56 C Initialise coriolis parameter
57 IF ( useConstantF ) THEN
58 C Constant F case
59 DO bj = myByLo(myThid), myByHi(myThid)
60 DO bi = myBxLo(myThid), myBxHi(myThid)
61 DO j=1-Oly,sNy+Oly
62 DO i=1-Olx,sNx+Olx
63 fCori(i,j,bi,bj) = f0
64 fCoriG(i,j,bi,bj) = f0
65 fCoriCos(i,j,bi,bj)=0. _d 0
66 ENDDO
67 ENDDO
68 ENDDO
69 ENDDO
70 ELSEIF ( useBetaPlaneF ) THEN
71 C Beta plane case
72 facGrid = 1. _d 0
73 IF ( usingSphericalPolarGrid
74 & .OR. usingCurvilinearGrid ) facGrid = deg2rad*rSphere
75 DO bj = myByLo(myThid), myByHi(myThid)
76 DO bi = myBxLo(myThid), myBxHi(myThid)
77 DO j=1-Oly,sNy+Oly
78 DO i=1-Olx,sNx+Olx
79 fCori(i,j,bi,bj) = f0+beta*_yC(i,j,bi,bj)*facGrid
80 fCoriG(i,j,bi,bj) = f0+beta* yG(i,j,bi,bj)*facGrid
81 fCoriCos(i,j,bi,bj)=0. _d 0
82 ENDDO
83 ENDDO
84 ENDDO
85 ENDDO
86 ELSEIF ( useSphereF ) THEN
87 C Spherical case
88 C Note in this case we assume yC is in degrees.
89 DO bj = myByLo(myThid), myByHi(myThid)
90 DO bi = myBxLo(myThid), myBxHi(myThid)
91 DO j=1-Oly,sNy+Oly
92 DO i=1-Olx,sNx+Olx
93 fCori(i,j,bi,bj) =
94 & 2. _d 0*omega*sin(_yC(i,j,bi,bj)*deg2rad)
95 fCoriG(i,j,bi,bj) =
96 & 2. _d 0*omega*sin(yG(i,j,bi,bj)*deg2rad)
97 fCoriCos(i,j,bi,bj)=
98 & 2. _d 0*omega*cos(_yC(i,j,bi,bj)*deg2rad)
99 ENDDO
100 ENDDO
101 ENDDO
102 ENDDO
103 c CALL WRITE_FLD_XY_RL('fCoriC',' ',fCori , 0,myThid)
104 c CALL WRITE_FLD_XY_RL('fCoriG',' ',fCoriG , 0,myThid)
105 c CALL WRITE_FLD_XY_RL('fCorCs',' ',fCoriCos,0,myThid)
106 ELSE
107 C Special custom form
108 DO bj = myByLo(myThid), myByHi(myThid)
109 DO bi = myBxLo(myThid), myBxHi(myThid)
110 DO j=1-Oly,sNy+Oly
111 DO i=1-Olx,sNx+Olx
112 fCori(i,j,bi,bj) = 0. _d 0
113 fCoriG(i,j,bi,bj) = 0. _d 0
114 fCoriCos(i,j,bi,bj)=0. _d 0
115 ENDDO
116 ENDDO
117 ENDDO
118 ENDDO
119 _BARRIER
120 CALL READ_REC_XY_RS( 'fCoriC.bin', fCori, 1, 0, myThid )
121 CALL READ_REC_XY_RS( 'fCorCs.bin', fCoriCos,1, 0, myThid )
122 IF ( .NOT.useCubedSphereExchange ) THEN
123 CALL READ_REC_XY_RS('fCoriG.bin', fCoriG, 1, 0, myThid )
124 ELSE
125 #ifdef OLD_GRID_IO
126 CALL READ_REC_XY_RS('fCoriG.bin', fCoriG, 1, 0, myThid )
127 _BARRIER
128 C- deal with the 2 missing corners (for fCoriG):
129 DO bj = myByLo(myThid), myByHi(myThid)
130 DO bi = myBxLo(myThid), myBxHi(myThid)
131 C- Notes: this will only works with 6 tiles (1 per face) and
132 C with 2 polar faces + 4 equatorials:
133 IF (bi.LE.3 .OR. bi.GE.5) THEN
134 fCoriG(sNx+1,1,bi,bj) = fCoriG(1,1,bi,bj)
135 ELSE
136 fCoriG(sNx+1,1,bi,bj) = -fCoriG(1,1,bi,bj)
137 ENDIF
138 IF (bi.GE.3) THEN
139 fCoriG(1,sNy+1,bi,bj) = fCoriG(1,1,bi,bj)
140 fCoriG(sNx+1,sNy+1,bi,bj) = fCoriG(sNx+1,1,bi,bj)
141 ELSE
142 fCoriG(1,sNy+1,bi,bj) = -fCoriG(1,1,bi,bj)
143 fCoriG(sNx+1,sNy+1,bi,bj) = -fCoriG(sNx+1,1,bi,bj)
144 ENDIF
145 ENDDO
146 ENDDO
147 #else /* OLD_GRID_IO */
148 _BEGIN_MASTER(myThid)
149 DO bj = 1,nSy
150 DO bi = 1,nSx
151 iG = bi+(myXGlobalLo-1)/sNx
152 myTile = iG
153 #ifdef ALLOW_EXCH2
154 myTile = W2_myTileList(bi)
155 iG = exch2_myface(myTile)
156 #endif
157 WRITE(fName,'(2A,I3.3,A)') 'fCoriG','.face',iG,'.bin'
158 iLen = ILNBLNK(fName)
159 WRITE(msgBuf,'(A,I6,2A)')
160 & ' Reading tile:', myTile, ' from file ', fName(1:iLen)
161 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
162 & SQUEEZE_RIGHT , myThid )
163 #ifdef ALLOW_MDSIO
164 CALL MDS_FACEF_READ_RS( fName, readBinaryPrec, 1,
165 & fCoriG, bi, bj, myThid )
166 #else /* ALLOW_MDSIO */
167 WRITE(msgBuf,'(A)') 'INI_CORI: Needs to compile MDSIO pkg'
168 CALL PRINT_ERROR( msgBuf, myThid )
169 STOP 'ABNORMAL END: S/R INI_CORI'
170 #endif /* ALLOW_MDSIO */
171
172 ENDDO
173 ENDDO
174 _END_MASTER(myThid)
175 #endif /* OLD_GRID_IO */
176 ENDIF
177
178 CALL EXCH_XY_RS( fCori, myThid )
179 CALL EXCH_XY_RS( fCoriCos, myThid )
180 CALL EXCH_Z_3D_RS( fCoriG, 1, myThid )
181 ENDIF
182
183 #ifdef ALLOW_MONITOR
184 IF ( MASTER_CPU_IO(myThid) ) THEN
185 C-- only the master thread is allowed to switch On/Off mon_write_stdout
186 C & mon_write_mnc (since it's the only thread that uses those flags):
187
188 IF (monitor_stdio) THEN
189 mon_write_stdout = .TRUE.
190 ELSE
191 mon_write_stdout = .FALSE.
192 ENDIF
193 mon_write_mnc = .FALSE.
194 #ifdef ALLOW_MNC
195 IF (useMNC .AND. monitor_mnc) THEN
196 DO i = 1,MAX_LEN_MBUF
197 mon_fname(i:i) = ' '
198 ENDDO
199 mon_fname(1:12) = 'monitor_grid'
200 CALL MNC_CW_SET_UDIM(mon_fname, 1, myThid)
201 mon_write_mnc = .TRUE.
202 ENDIF
203 #endif /* ALLOW_MNC */
204
205 ENDIF
206
207 CALL MON_PRINTSTATS_RS(1,fCori,'fCori',myThid)
208 CALL MON_PRINTSTATS_RS(1,fCoriG,'fCoriG',myThid)
209 CALL MON_PRINTSTATS_RS(1,fCoriCos,'fCoriCos',myThid)
210
211 IF ( MASTER_CPU_IO(myThid) ) THEN
212 mon_write_stdout = .FALSE.
213 mon_write_mnc = .FALSE.
214 ENDIF
215 #endif /* ALLOW_MONITOR */
216
217 RETURN
218 END

  ViewVC Help
Powered by ViewVC 1.1.22