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

Annotation of /MITgcm/model/src/integrate_for_w.F

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


Revision 1.6 - (hide annotations) (download)
Tue May 29 14:01:37 2001 UTC (23 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint40pre3, checkpoint40pre1, checkpoint40pre7, checkpoint40pre6, checkpoint40pre9, checkpoint40pre8, checkpoint40pre2, checkpoint40pre4, checkpoint40pre5, checkpoint40
Changes since 1.5: +55 -25 lines
Merge from branch pre38:
 o essential mods for cubed sphere
 o debugged atmosphere, dynamcis + physics (aim)
 o new packages (mom_vecinv, mom_fluxform, ...)

1 adcroft 1.6 C $Header: /u/gcmpack/models/MITgcmUV/model/src/integrate_for_w.F,v 1.5.2.1 2001/03/30 23:09:36 jmc Exp $
2 cnh 1.4 C $Name: $
3 adcroft 1.2
4     #include "CPP_OPTIONS.h"
5    
6     CStartOfInterFace
7     SUBROUTINE INTEGRATE_FOR_W(
8     I bi,bj,k,uFld,vFld,
9     O wFld,
10     I myThid)
11    
12     C /==========================================================\
13     C | SUBROUTINE CALC_COMMON_FACTORS |
14     C | o Calculate common data (such as volume flux) for use |
15     C | by "Right hand side" subroutines. |
16     C |==========================================================|
17     C | Here, we calculate terms or spatially varying factors |
18     C | that are used at various points in the "RHS" subroutines.|
19     C | This reduces the amount of total work, total memory |
20     C | and therefore execution time and is generally a good |
21     C | idea. |
22     C \==========================================================/
23     IMPLICIT NONE
24    
25     C == GLobal variables ==
26     #include "SIZE.h"
27     #include "EEPARAMS.h"
28     #include "PARAMS.h"
29     #include "GRID.h"
30    
31     C == Routine arguments ==
32     INTEGER bi,bj,k
33     _RL uFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
34     _RL vFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
35     _RL wFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
36     INTEGER myThid
37     CEndOfInterface
38    
39     C == Local variables ==
40     INTEGER i,j
41     _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
42     _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
43    
44     C-- Calculate velocity field "volume transports" through
45     C tracer cell faces.
46     DO j=1-Oly,sNy+Oly
47     DO i=1-Olx,sNx+Olx
48     uTrans(i,j) = uFld(i,j,k,bi,bj)*
49     & _dyG(i,j,bi,bj)
50     & *drF(k)*_hFacW(i,j,k,bi,bj)
51     vTrans(i,j) = vFld(i,j,k,bi,bj)*
52     & _dxG(i,j,bi,bj)
53     & *drF(k)*_hFacS(i,j,k,bi,bj)
54     ENDDO
55     ENDDO
56    
57 adcroft 1.6 C-- Calculate vertical "volume transport" through face k
58     C between tracer cell k-1 & k
59     IF (rigidLid) THEN
60     C- o Rigid-Lid case: zero at lower and upper boundaries
61     IF (k.eq.1) THEN
62     DO j=1-Oly,sNy+Oly-1
63     DO i=1-Olx,sNx+Olx-1
64     wFld(i,j,k,bi,bj) = 0.
65     ENDDO
66 adcroft 1.2 ENDDO
67 adcroft 1.6 ELSEIF (k.eq.Nr) THEN
68     DO j=1-Oly,sNy+Oly-1
69     DO i=1-Olx,sNx+Olx-1
70     wFld(i,j,k,bi,bj) =
71     & -( uTrans(i+1,j)-uTrans(i,j)
72     & +vTrans(i,j+1)-vTrans(i,j)
73     & )*recip_rA(i,j,bi,bj)
74     & *maskC(i,j,k,bi,bj)*maskC(i,j,k-1,bi,bj)
75     ENDDO
76     ENDDO
77     ELSE
78     DO j=1-Oly,sNy+Oly-1
79     DO i=1-Olx,sNx+Olx-1
80     wFld(i,j,k,bi,bj) =
81     & ( wFld(i,j,k+1,bi,bj)
82     & -( uTrans(i+1,j)-uTrans(i,j)
83     & +vTrans(i,j+1)-vTrans(i,j)
84     & )*recip_rA(i,j,bi,bj)
85     & )*maskC(i,j,k,bi,bj)*maskC(i,j,k-1,bi,bj)
86     ENDDO
87 adcroft 1.2 ENDDO
88 adcroft 1.6 ENDIF
89 adcroft 1.2 ELSE
90 adcroft 1.6 C- o Linear Free Surface case:
91     C non zero at surface ; zero under-ground and at r_lower boundary
92     IF (k.eq.Nr) THEN
93     DO j=1-Oly,sNy+Oly-1
94     DO i=1-Olx,sNx+Olx-1
95     wFld(i,j,k,bi,bj) =
96     & -( uTrans(i+1,j)-uTrans(i,j)
97     & +vTrans(i,j+1)-vTrans(i,j)
98     & )*recip_rA(i,j,bi,bj)
99     & *maskC(i,j,k,bi,bj)
100     ENDDO
101 adcroft 1.2 ENDDO
102 adcroft 1.6 ELSE
103     DO j=1-Oly,sNy+Oly-1
104     DO i=1-Olx,sNx+Olx-1
105     wFld(i,j,k,bi,bj) =
106     & ( wFld(i,j,k+1,bi,bj)
107     & -( uTrans(i+1,j)-uTrans(i,j)
108     & +vTrans(i,j+1)-vTrans(i,j)
109     & )*recip_rA(i,j,bi,bj)
110     & )*maskC(i,j,k,bi,bj)
111     ENDDO
112     ENDDO
113     ENDIF
114     C- endif - rigid-lid / linear Free-Surf.
115 adcroft 1.2 ENDIF
116    
117     RETURN
118     END

  ViewVC Help
Powered by ViewVC 1.1.22