/[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.12 - (show annotations) (download)
Fri Jun 9 14:26:30 2000 UTC (24 years ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint28, checkpoint29, branch-atmos-merge-start, checkpoint33, checkpoint32, checkpoint31, checkpoint30, checkpoint34, branch-atmos-merge-phase1
Branch point for: branch-atmos-merge
Changes since 1.11: +6 -1 lines
Included initialisations required for TAMC compatibility.

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/calc_common_factors.F,v 1.12 2000/06/08 19:01:22 heimbach 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 #ifdef ALLOW_AUTODIFF_TAMC
69 C-- rvel(:,:kDown) is still required
70 rVel(1,1,kDown) = rVel(1,1,kDown)
71 #endif
72
73 TOP_LAYER = K .EQ. 1
74
75 C-- Calculate mask for tracer cells (0 => land, 1 => water)
76 DO j=jMin,jMax
77 DO i=iMin,iMax
78 maskC(i,j) = 1.
79 IF (_hFacC(i,j,k,bi,bj).eq.0.) maskC(i,j)=0.
80 maskUp(i,j) = 1.
81 IF (_hFacC(i,j,k,bi,bj).eq.0. .OR. TOP_LAYER )
82 & maskUp(i,j)=0.
83 ENDDO
84 ENDDO
85
86 C-- Calculate tracer cell face open areas
87 DO j=jMin,jMax
88 DO i=iMin,iMax
89 xA(i,j) = _dyG(i,j,bi,bj)
90 & *drF(k)*_hFacW(i,j,k,bi,bj)
91 yA(i,j) = _dxG(i,j,bi,bj)
92 & *drF(k)*_hFacS(i,j,k,bi,bj)
93 ENDDO
94 ENDDO
95
96 C-- Calculate velocity field "volume transports" through
97 C-- tracer cell faces.
98 DO j=jMin,jMax
99 DO i=iMin,iMax
100 uTrans(i,j) = uVel(i,j,k,bi,bj)*xA(i,j)
101 vTrans(i,j) = vVel(i,j,k,bi,bj)*yA(i,j)
102 ENDDO
103 ENDDO
104
105 C-- Calculate vertical "volume transport" through
106 C-- tracer cell face *above* this level.
107 IF (TOP_LAYER .AND. rigidLid) THEN
108 DO j=jMin,jMax
109 DO i=iMin,iMax
110 rTrans(i,j) = 0.
111 ENDDO
112 ENDDO
113 ELSE
114 DO j=jMin,jMax
115 DO i=iMin,iMax
116 rTrans(i,j) =
117 & uTrans(i,j)*recip_rkFac-uTrans(i+1,j)*recip_rkFac
118 & +vTrans(i,j)*recip_rkFac-vTrans(i,j+1)*recip_rkFac
119 & +rTrans(i,j)
120 ENDDO
121 ENDDO
122 ENDIF
123
124 C-- Vertical velocity at upper face
125 DO j=jMin,jMax
126 DO i=iMin,iMax
127 rVel(i,j,kUp) = rTrans(i,j)/_rA(i,j,bi,bj)
128 ENDDO
129 ENDDO
130
131 #ifdef ALLOW_NONHYDROSTATIC
132 C-- Vertical velocity at upper face
133 C IF ( nonHydrostatic ) THEN
134 DO j=jMin,jMax
135 DO i=iMin,iMax
136 wVel(i,j,k,bi,bj)=rVel(i,j,kUp)
137 ENDDO
138 ENDDO
139 C ENDIF
140 #endif
141
142 RETURN
143 END

  ViewVC Help
Powered by ViewVC 1.1.22