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

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

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


Revision 1.13 - (show annotations) (download)
Thu Aug 12 21:49:55 2010 UTC (13 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62k, checkpoint62j, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62w, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint63g, checkpoint63, checkpoint63p, checkpoint63q, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c
Changes since 1.12: +2 -2 lines
remove tabs

1 C $Header: /u/gcmpack/MITgcm/model/src/ini_pressure.F,v 1.12 2009/04/28 18:01:14 jmc Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: INI_PRESSURE
8 C !INTERFACE:
9 SUBROUTINE INI_PRESSURE( myThid )
10 C !DESCRIPTION: \bv
11 C *==========================================================*
12 C | SUBROUTINE INI_PRESSURE
13 C | o initialise the pressure field consistently with
14 C | temperature and salinity
15 C | - needs to be called after ini_theta, ini_salt, and
16 C | ini_psurf
17 C | - does not include surface pressure loading, because
18 C | that is only available until after
19 C | CALL packages_init_variables
20 C *==========================================================*
21 C \ev
22
23 C !USES:
24 IMPLICIT NONE
25 C == Global variables ==
26 #include "SIZE.h"
27 #include "EEPARAMS.h"
28 #include "PARAMS.h"
29 #include "EOS.h"
30 #include "GRID.h"
31 #include "DYNVARS.h"
32
33 C !INPUT/OUTPUT PARAMETERS:
34 C == Routine arguments ==
35 C myThid - Number of this instance of INI_PRESSURE
36 INTEGER myThid
37
38 C !LOCAL VARIABLES:
39 C == Local variables ==
40 C dPhiHydX,Y :: Gradient (X & Y directions) of Hyd. Potential
41 C bi,bj :: tile indices
42 C i,j,k :: Loop counters
43 INTEGER bi, bj
44 INTEGER i, j, k
45 INTEGER iMin, iMax, jMin, jMax, npiter
46 _RL PhiHydF (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
47 _RL PhiHydC (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
48 _RL dPhiHydX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
49 _RL dPhiHydY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
50 _RL oldPhi (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
51 _RL count, rmspp, rmsppold
52 _RL sumTile, rmsTile
53
54 CHARACTER*(MAX_LEN_MBUF) msgBuf
55 CEOP
56 iMin = 1-OLx
57 iMax = sNx+OLx
58 jMin = 1-OLy
59 jMax = sNy+OLy
60
61 _BEGIN_MASTER( myThid )
62 WRITE(msgBuf,'(a)')
63 & 'Start initial hydrostatic pressure computation'
64 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
65 & SQUEEZE_RIGHT , myThid)
66 _END_MASTER( myThid )
67
68 DO bj = myByLo(myThid), myByHi(myThid)
69 DO bi = myBxLo(myThid), myBxHi(myThid)
70 DO k = 1,Nr
71 DO j=1-OLy,sNy+OLy
72 DO i=1-OLx,sNx+OLx
73 totPhiHyd(i,j,k,bi,bj) = 0. _d 0
74 ENDDO
75 ENDDO
76 ENDDO
77 ENDDO
78 ENDDO
79
80 IF ( useDynP_inEos_Zc ) THEN
81
82 #ifndef ALLOW_AUTODIFF_TAMC
83 cph-- deal with this iterative loop for AD once it will
84 cph-- really be needed;
85 cph-- would need storing of totPhiHyd for each npiter
86
87 rmspp = 1. _d 0
88 rmsppold = 0. _d 0
89 npiter = 0
90
91 C iterate pressure p = integral of (g*rho(p)*dz)
92 DO npiter= 1, 15
93 rmsppold = rmspp
94 rmspp = 0. _d 0
95 count = 0. _d 0
96 DO bj = myByLo(myThid), myByHi(myThid)
97 DO bi = myBxLo(myThid), myBxHi(myThid)
98 rmsTile = 0. _d 0
99 sumTile = 0. _d 0
100 DO j=1-OLy,sNy+OLy
101 DO i=1-OLx,sNx+OLx
102 phiHydF(i,j) = 0. _d 0
103 ENDDO
104 ENDDO
105 DO k = 1, Nr
106 C for each level save old pressure and compute new pressure
107 DO j=jMin,jMax
108 DO i=iMin,iMax
109 oldPhi(i,j) = totPhiHyd(i,j,k,bi,bj)
110 ENDDO
111 ENDDO
112 CALL CALC_PHI_HYD(
113 I bi, bj, iMin, iMax, jMin, jMax, k,
114 I theta, salt,
115 U phiHydF,
116 O phiHydC, dPhiHydX, dPhiHydY,
117 I startTime, -1, myThid )
118 C compute convergence criterion
119 DO j=1,sNy
120 DO i=1,sNx
121 rmsTile = rmsTile
122 & + (totPhiHyd(i,j,k,bi,bj)-oldPhi(i,j))**2
123 & * maskC(i,j,k,bi,bj)
124 sumTile = sumTile + maskC(i,j,k,bi,bj)
125 ENDDO
126 ENDDO
127 C -- end k loop
128 ENDDO
129 rmspp = rmspp + rmsTile
130 count = count + sumTile
131 ENDDO
132 ENDDO
133 Cml WRITE(msgBuf,'(I10.10)') npiter
134 Cml CALL WRITE_FLD_XYZ_RL( 'POLD.',msgBuf,pold,npiter,myThid)
135 Cml CALL WRITE_FLD_XYZ_RL( 'PINI.',msgBuf,pressure,npiter,myThid)
136 _GLOBAL_SUM_RL( rmspp, myThid )
137 _GLOBAL_SUM_RL( count, myThid )
138 IF ( count .EQ. 0. ) THEN
139 rmspp = 0. _d 0
140 ELSE
141 rmspp = SQRT(rmspp/count)
142 ENDIF
143 _BEGIN_MASTER( myThid )
144 WRITE(msgBuf,'(A,I4,A,1PE20.12)')
145 & 'Iteration', npiter, ', RMS-difference =', rmspp
146 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
147 & SQUEEZE_RIGHT , myThid)
148 _END_MASTER( myThid )
149
150 C -- end npiter loop
151 ENDDO
152 C print some diagnostics
153 _BEGIN_MASTER( myThid )
154 IF ( rmspp .NE. 0. ) THEN
155 IF ( rmspp .EQ. rmsppold ) THEN
156 WRITE(msgBuf,'(A)')
157 & 'Initial hydrostatic pressure did not converge perfectly,'
158 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
159 & SQUEEZE_RIGHT , myThid)
160 WRITE(msgBuf,'(A)')
161 & 'but the RMS-difference is constant, indicating that the'
162 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
163 & SQUEEZE_RIGHT , myThid)
164 WRITE(msgBuf,'(A)')
165 & 'algorithm converged within machine precision.'
166 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
167 & SQUEEZE_RIGHT , myThid)
168 ELSE
169 WRITE(msgBuf,'(A,I2,A)')
170 & 'Initial hydrostatic pressure did not converge after ',
171 & npiter-1, ' steps'
172 CALL PRINT_ERROR( msgBuf, myThid )
173 STOP 'ABNORMAL END: S/R INI_PRESSURE'
174 ENDIF
175 ENDIF
176 WRITE(msgBuf,'(A)')
177 & 'Initial hydrostatic pressure converged.'
178 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
179 & SQUEEZE_RIGHT , myThid)
180 _END_MASTER( myThid )
181
182 #endif /* ALLOW_AUTODIFF_TAMC */
183
184 c-- else of if useDynP_inEos_Zc
185 ELSE
186 C print a message and DO nothing
187 _BEGIN_MASTER( myThid )
188 WRITE(msgBuf,'(A,A)')
189 & 'Pressure is predetermined for buoyancyRelation ',
190 & buoyancyRelation(1:11)
191 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
192 & SQUEEZE_RIGHT , myThid)
193 _END_MASTER( myThid )
194
195 ENDIF
196
197 _BEGIN_MASTER( myThid )
198 WRITE(msgBuf,'(A)') ' '
199 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
200 & SQUEEZE_RIGHT , myThid)
201 _END_MASTER( myThid )
202
203 RETURN
204 END

  ViewVC Help
Powered by ViewVC 1.1.22