/[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.16 - (show annotations) (download)
Mon Feb 15 18:00:26 2016 UTC (8 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65v, checkpoint65w, checkpoint65u, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, HEAD
Changes since 1.15: +3 -3 lines
rename internal parameter "useDynP_inEos_Zc" to "storePhiHyd4Phys"

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

  ViewVC Help
Powered by ViewVC 1.1.22