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

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

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


Revision 1.11 - (show annotations) (download)
Mon Mar 22 15:54:03 1999 UTC (25 years, 3 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint20, checkpoint21, checkpoint22, checkpoint23, checkpoint24, checkpoint25, checkpoint27, checkpoint26
Changes since 1.10: +40 -18 lines
Modifications for non-hydrostatic ability + updates for open-boundaries.

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/calc_common_factors.F,v 1.10 1998/11/06 22:44:43 cnh Exp $
2
3 #include "CPP_OPTIONS.h"
4
5 CStartOfInterFace
6 SUBROUTINE CALC_COMMON_FACTORS(
7 I bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
8 O xA,yA,uTrans,vTrans,rTrans,rVel,maskC,maskUp,
9 I myThid)
10
11 C /==========================================================\
12 C | SUBROUTINE CALC_COMMON_FACTORS |
13 C | o Calculate common data (such as volume flux) for use |
14 C | by "Right hand side" subroutines. |
15 C |==========================================================|
16 C | Here, we calculate terms or spatially varying factors |
17 C | that are used at various points in the "RHS" subroutines.|
18 C | This reduces the amount of total work, total memory |
19 C | and therefore execution time and is generally a good |
20 C | idea. |
21 C \==========================================================/
22 IMPLICIT NONE
23
24 C == GLobal variables ==
25 #include "SIZE.h"
26 #include "DYNVARS.h"
27 #include "EEPARAMS.h"
28 #include "PARAMS.h"
29 #include "GRID.h"
30 #ifdef ALLOW_NONHYDROSTATIC
31 #include "GW.h"
32 #endif
33
34 C == Routine arguments ==
35 C bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation
36 C results will be set.
37 C xA - Tracer cell face area normal to X
38 C yA - Tracer cell face area normal to X
39 C uTrans - Zonal volume transport through cell face
40 C vTrans - Meridional volume transport through cell face
41 C rTrans - R-direction volume transport through cell face
42 C rVel - R-direction velocity at cell upper and lower faces
43 C maskC - land/water mask for tracer points
44 C maskUp - land/water mask for Wvel points (above tracer level)
45 C myThid - Instance number for this innvocation of CALC_COMMON_FACTORS
46 C
47 INTEGER bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown
48 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
49 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
50 _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
51 _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
52 _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
53 _RL rVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
54 _RS maskC (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
55 _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56 C
57 INTEGER myThid
58 CEndOfInterface
59
60 C == Local variables ==
61 C I, J, K - Loop counters
62 C kUp, kDown, kM1 - Index for layer above and below. K_UP and K_DOWN
63 C are switched with layer to be the appropriate index
64 C into fluxUD.
65 INTEGER i,j
66 LOGICAL TOP_LAYER
67
68 TOP_LAYER = K .EQ. 1
69
70 C-- Calculate mask for tracer cells (0 => land, 1 => water)
71 DO j=jMin,jMax
72 DO i=iMin,iMax
73 maskC(i,j) = 1.
74 IF (_hFacC(i,j,k,bi,bj).eq.0.) maskC(i,j)=0.
75 maskUp(i,j) = 1.
76 IF (_hFacC(i,j,k,bi,bj).eq.0. .OR. TOP_LAYER )
77 & maskUp(i,j)=0.
78 ENDDO
79 ENDDO
80
81 C-- Calculate tracer cell face open areas
82 DO j=jMin,jMax
83 DO i=iMin,iMax
84 xA(i,j) = _dyG(i,j,bi,bj)
85 & *drF(k)*_hFacW(i,j,k,bi,bj)
86 yA(i,j) = _dxG(i,j,bi,bj)
87 & *drF(k)*_hFacS(i,j,k,bi,bj)
88 ENDDO
89 ENDDO
90
91 C-- Calculate velocity field "volume transports" through
92 C-- tracer cell faces.
93 DO j=jMin,jMax
94 DO i=iMin,iMax
95 uTrans(i,j) = uVel(i,j,k,bi,bj)*xA(i,j)
96 vTrans(i,j) = vVel(i,j,k,bi,bj)*yA(i,j)
97 ENDDO
98 ENDDO
99
100 C-- Calculate vertical "volume transport" through
101 C-- tracer cell face *above* this level.
102 IF (TOP_LAYER .AND. rigidLid) THEN
103 DO j=jMin,jMax
104 DO i=iMin,iMax
105 rTrans(i,j) = 0.
106 ENDDO
107 ENDDO
108 ELSE
109 DO j=jMin,jMax
110 DO i=iMin,iMax
111 rTrans(i,j) =
112 & uTrans(i,j)*recip_rkFac-uTrans(i+1,j)*recip_rkFac
113 & +vTrans(i,j)*recip_rkFac-vTrans(i,j+1)*recip_rkFac
114 & +rTrans(i,j)
115 ENDDO
116 ENDDO
117 ENDIF
118
119 C-- Vertical velocity at upper face
120 DO j=jMin,jMax
121 DO i=iMin,iMax
122 rVel(i,j,kUp) = rTrans(i,j)/_rA(i,j,bi,bj)
123 ENDDO
124 ENDDO
125
126 #ifdef ALLOW_NONHYDROSTATIC
127 C-- Vertical velocity at upper face
128 C IF ( nonHydrostatic ) THEN
129 DO j=jMin,jMax
130 DO i=iMin,iMax
131 wVel(i,j,k,bi,bj)=rVel(i,j,kUp)
132 ENDDO
133 ENDDO
134 C ENDIF
135 #endif
136
137 RETURN
138 END

  ViewVC Help
Powered by ViewVC 1.1.22