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

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

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


Revision 1.3 - (show annotations) (download)
Sat Jan 23 00:04:03 2010 UTC (14 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63l, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62c, checkpoint62b, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.2: +20 -5 lines
add NH free-surface formulation (selectNHfreeSurf=1) (not fully tested)

1 C $Header: /u/gcmpack/MITgcm/model/src/post_cg3d.F,v 1.1 2009/12/11 04:31:31 jmc Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: POST_CG3D
8 C !INTERFACE:
9 SUBROUTINE POST_CG3D(
10 I zeroPsNH, zeroMeanPnh,
11 I myTime, myIter, myThid )
12
13 C !DESCRIPTION:
14 C Called from SOLVE_FOR_PRESSURE, after 3-D solver (cg3d):
15 C Finish computation of Non-hydrostatic pressure from 3-D solver solution
16
17 C !USES:
18 IMPLICIT NONE
19 C == Global variables
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "PARAMS.h"
23 #include "GRID.h"
24 #include "SURFACE.h"
25 c#include "FFIELDS.h"
26 #include "DYNVARS.h"
27 #ifdef ALLOW_NONHYDROSTATIC
28 #include "NH_VARS.h"
29 #endif
30
31 C === Functions ====
32 LOGICAL DIFFERENT_MULTIPLE
33 EXTERNAL DIFFERENT_MULTIPLE
34
35 C !INPUT/OUTPUT PARAMETERS:
36 C == Routine arguments ==
37 C zeroPsNH :: account for Hyd.component of cg3d_x by updating NH & Surf.Press
38 C zeroMeanPnh :: account for Hyd.component of cg3d_x by updating NH & Surf.Press
39 C myTime :: Current time in simulation
40 C myIter :: Current iteration number in simulation
41 C myThid :: My Thread Id. number
42 LOGICAL zeroPsNH, zeroMeanPnh
43 _RL myTime
44 INTEGER myIter
45 INTEGER myThid
46
47 #ifdef ALLOW_NONHYDROSTATIC
48 C !LOCAL VARIABLES:
49 C == Local variables ==
50 INTEGER i,j,k,bi,bj
51 INTEGER ks
52 CHARACTER*10 sufx
53 c CHARACTER*(MAX_LEN_MBUF) msgBuf
54 _RL tmpSurf
55 CEOP
56
57 C-- Separate the Hydrostatic Surface Pressure adjusment (=> put it in dPhiNH)
58 C from the Non-hydrostatic pressure (since cg3d_x contains both contribution)
59 IF ( nonHydrostatic .AND. exactConserv ) THEN
60 DO bj=myByLo(myThid),myByHi(myThid)
61 DO bi=myBxLo(myThid),myBxHi(myThid)
62 IF ( select_rStar.EQ.0 .AND. usingZCoords ) THEN
63 C- Z coordinate: assume surface @ level k=1
64 DO j=1-OLy,sNy+OLy
65 DO i=1-OLx,sNx+OLx
66 dPhiNH(i,j,bi,bj) = phi_nh(i,j,1,bi,bj)
67 ENDDO
68 ENDDO
69 ELSEIF ( select_rStar.EQ.0 ) THEN
70 C- Other than Z coordinate: no assumption on surface level index
71 DO j=1-OLy,sNy+OLy
72 DO i=1-OLx,sNx+OLx
73 ks = ksurfC(i,j,bi,bj)
74 IF ( ks.LE.Nr ) THEN
75 dPhiNH(i,j,bi,bj) = phi_nh(i,j,ks,bi,bj)
76 ELSE
77 dPhiNH(i,j,bi,bj) = 0.
78 ENDIF
79 ENDDO
80 ENDDO
81 #ifdef NONLIN_FRSURF
82 ELSE
83 C rStar : take vertical average of P_NH as Hyd.Surf.Press adjustment
84 DO j=1-OLy,sNy+OLy
85 DO i=1-OLx,sNx+OLx
86 dPhiNH(i,j,bi,bj) = 0.
87 ENDDO
88 ENDDO
89 DO k=1,Nr
90 DO j=1-OLy,sNy+OLy
91 DO i=1-OLx,sNx+OLx
92 dPhiNH(i,j,bi,bj) = dPhiNH(i,j,bi,bj)
93 & + phi_nh(i,j,k,bi,bj)*drF(k)*h0FacC(i,j,k,bi,bj)
94 ENDDO
95 ENDDO
96 ENDDO
97 DO j=1-OLy,sNy+OLy
98 DO i=1-OLx,sNx+OLx
99 dPhiNH(i,j,bi,bj) = dPhiNH(i,j,bi,bj)*recip_Rcol(i,j,bi,bj)
100 ENDDO
101 ENDDO
102 #endif /* NONLIN_FRSURF */
103 ENDIF
104 IF ( selectNHfreeSurf.GE.1 ) THEN
105 DO j=1,sNy
106 DO i=1,sNx
107 tmpSurf = deltaTMom*deltaTfreesurf
108 & *Bo_surf(i,j,bi,bj)*recip_drC(1)
109 & *implicitNHPress*implicDiv2DFlow
110 dPhiNH(i,j,bi,bj) = ( tmpSurf*dPhiNH(i,j,bi,bj)
111 & + Bo_surf(i,j,bi,bj)*
112 & ( etaH(i,j,bi,bj)-etaN(i,j,bi,bj)
113 & +implicDiv2DFlow*deltaTfreesurf
114 c & *(wVel(i,j,1,bi,bj)+PmE)
115 & *wVel(i,j,1,bi,bj)
116 & ) )/(1. _d 0 + tmpSurf )
117 ENDDO
118 ENDDO
119 ENDIF
120 ENDDO
121 ENDDO
122 IF ( selectNHfreeSurf.GE.1 .AND.
123 & implicitNHPress.LT.1. _d 0 ) THEN
124 CALL EXCH_XY_RL( dPhiNH, myThid )
125 ENDIF
126 ENDIF
127
128 C-- Update surface pressure (account for NH-p @ surface level) and NH pressure:
129 IF ( zeroPsNH .OR. zeroMeanPnh ) THEN
130 IF ( DIFFERENT_MULTIPLE( diagFreq, myTime, deltaTClock) ) THEN
131 WRITE(sufx,'(I10.10)') myIter
132 CALL WRITE_FLD_XYZ_RL( 'cg3d_x.',sufx, phi_nh, myIter, myThid )
133 ENDIF
134 DO bj=myByLo(myThid),myByHi(myThid)
135 DO bi=myBxLo(myThid),myBxHi(myThid)
136
137 DO k=1,Nr
138 DO j=1-OLy,sNy+OLy
139 DO i=1-OLx,sNx+OLx
140 phi_nh(i,j,k,bi,bj) = ( phi_nh(i,j,k,bi,bj)
141 & - dPhiNH(i,j,bi,bj)
142 & )*maskC(i,j,k,bi,bj)
143 ENDDO
144 ENDDO
145 ENDDO
146 DO j=1-OLy,sNy+OLy
147 DO i=1-OLx,sNx+OLx
148 etaN(i,j,bi,bj) = etaN(i,j,bi,bj)
149 & + recip_Bo(i,j,bi,bj)*dPhiNH(i,j,bi,bj)
150 ENDDO
151 ENDDO
152
153 ENDDO
154 ENDDO
155 ENDIF
156 #endif /* ALLOW_NONHYDROSTATIC */
157
158 RETURN
159 END

  ViewVC Help
Powered by ViewVC 1.1.22