/[MITgcm]/MITgcm/pkg/gmredi/gmredi_calc_psi_b.F
ViewVC logotype

Contents of /MITgcm/pkg/gmredi/gmredi_calc_psi_b.F

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


Revision 1.4 - (show annotations) (download)
Sun Jan 12 21:27:20 2003 UTC (21 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint47i_post
Changes since 1.3: +2 -2 lines
* correct constant Lrho (ldd97 taper scheme)
* change S/R name so that it correspond to the file name.

1 C $Header: /u/gcmpack/MITgcm/pkg/gmredi/gmredi_calc_psi_b.F,v 1.3 2003/01/10 23:41:15 heimbach Exp $
2 C $Name: $
3
4 #include "GMREDI_OPTIONS.h"
5
6 CStartOfInterface
7 SUBROUTINE GMREDI_CALC_PSI_B(
8 I bi, bj, iMin, iMax, jMin, jMax,
9 I sigmaX, sigmaY, sigmaR,
10 I myThid )
11 C /==========================================================\
12 C | SUBROUTINE GMREDI_CALC_PSI_B |
13 C | o Calculate stream-functions for GM bolus velocity |
14 C |==========================================================|
15 C \==========================================================/
16 IMPLICIT NONE
17
18 C == Global variables ==
19 #include "SIZE.h"
20 #include "GRID.h"
21 #include "DYNVARS.h"
22 #include "EEPARAMS.h"
23 #include "PARAMS.h"
24 #include "GMREDI.h"
25 #include "GMREDI_DIAGS.h"
26
27 #ifdef ALLOW_AUTODIFF_TAMC
28 #include "tamc.h"
29 #include "tamc_keys.h"
30 #endif /* ALLOW_AUTODIFF_TAMC */
31
32 C == Routine arguments ==
33 C
34 _RL sigmaX(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
35 _RL sigmaY(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
36 _RL sigmaR(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
37 INTEGER bi,bj,iMin,iMax,jMin,jMax
38 INTEGER myThid
39 CEndOfInterface
40
41 #ifdef ALLOW_GMREDI
42 #ifdef GM_BOLUS_ADVEC
43
44 C == Local variables ==
45 INTEGER i,j,k, km1
46 _RL SlopeX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
47 _RL SlopeY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
48 _RL dSigmaDrW(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
49 _RL dSigmaDrS(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
50 _RL taperX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
51 _RL taperY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
52
53 C- Initialization : <= done in S/R gmredi_init
54
55 #ifdef ALLOW_AUTODIFF_TAMC
56 act1 = bi - myBxLo(myThid)
57 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
58 act2 = bj - myByLo(myThid)
59 max2 = myByHi(myThid) - myByLo(myThid) + 1
60 act3 = myThid - 1
61 max3 = nTx*nTy
62 act4 = ikey_dynamics - 1
63 ikey = (act1 + 1) + act2*max1
64 & + act3*max1*max2
65 & + act4*max1*max2*max3
66 #endif /* ALLOW_AUTODIFF_TAMC */
67
68 #ifdef ALLOW_AUTODIFF_TAMC
69 # ifdef GM_VISBECK_VARIABLE_K
70 CADJ STORE VisbeckK(:,:,bi,bj) = comlev1_bibj, key=ikey, byte=isbyte
71 # endif
72 #endif
73 IF (GM_AdvForm) THEN
74 DO k=2,Nr
75 km1 = k-1
76
77 #ifdef ALLOW_AUTODIFF_TAMC
78 kkey = (ikey-1)*Nr + k
79 DO j=1-Oly,sNy+Oly
80 DO i=1-Olx,sNx+Olx
81 SlopeX(i,j) = 0. _d 0
82 SlopeY(i,j) = 0. _d 0
83 dSigmaDrW(i,j) = 0. _d 0
84 dSigmaDrS(i,j) = 0. _d 0
85 ENDDO
86 ENDDO
87 #endif
88
89 DO j=1-Oly+1,sNy+Oly-1
90 DO i=1-Olx+1,sNx+Olx-1
91
92 C Gradient of Sigma below U and V points
93 SlopeX(i,j)=0.5*( sigmaX(i,j,km1)+sigmaX(i,j,k) )
94 & *maskW(i,j,k,bi,bj)
95 dSigmaDrW(i,j)=0.5*( sigmaR(i-1,j,k)+sigmaR(i,j,k) )
96 & *maskW(i,j,k,bi,bj)
97 SlopeY(i,j)=0.5*( sigmaY(i,j,km1)+sigmaY(i,j,k) )
98 & *maskS(i,j,k,bi,bj)
99 dSigmaDrS(i,j)=0.5*( sigmaR(i,j-1,k)+sigmaR(i,j,k) )
100 & *maskS(i,j,k,bi,bj)
101
102 ENDDO
103 ENDDO
104
105 C Calculate slopes , taper and/or clip
106 CALL GMREDI_SLOPE_PSI(
107 I dSigmaDrW, dSigmaDrS,
108 I rF(K),K,
109 U SlopeX, SlopeY,
110 O taperX, taperY,
111 I bi, bj, myThid )
112
113 #ifdef ALLOW_AUTODIFF_TAMC
114 CADJ STORE SlopeX(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
115 CADJ STORE SlopeY(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
116 CADJ STORE taperX(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
117 CADJ STORE taperY(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
118 #endif /* ALLOW_AUTODIFF_TAMC */
119
120 DO j=1-Oly+1,sNy+Oly-1
121 DO i=1-Olx+1,sNx+Olx-1
122
123 C- Compute the 2 stream-function Components ( GM bolus vel.)
124 GM_PsiX(i,j,k,bi,bj) = SlopeX(i,j)*taperX(i,j)
125 & *( GM_background_K
126 #ifdef GM_VISBECK_VARIABLE_K
127 & +0.5*(VisbeckK(i-1,j,bi,bj)+VisbeckK(i,j,bi,bj))
128 #endif
129 & )*maskW(i,j,k,bi,bj)
130 GM_PsiY(i,j,k,bi,bj) = SlopeY(i,j)*taperY(i,j)
131 & *( GM_background_K
132 #ifdef GM_VISBECK_VARIABLE_K
133 & +0.5*(VisbeckK(i,j-1,bi,bj)+VisbeckK(i,j,bi,bj))
134 #endif
135 & )*maskS(i,j,k,bi,bj)
136
137 #ifdef ALLOW_TIMEAVE
138 C-- Time-average
139 GM_PsiXtave(i,j,k,bi,bj)=GM_PsiXtave(i,j,k,bi,bj)
140 & +GM_PsiX(i,j,k,bi,bj)*deltaTclock
141 GM_PsiYtave(i,j,k,bi,bj)=GM_PsiYtave(i,j,k,bi,bj)
142 & +GM_PsiY(i,j,k,bi,bj)*deltaTclock
143 #endif /* ALLOW_TIMEAVE */
144
145 ENDDO
146 ENDDO
147
148 C-----
149 ENDDO
150 ENDIF
151 #endif /* GM_BOLUS_ADVEC */
152 #endif /* ALLOW_GMREDI */
153
154 RETURN
155 END

  ViewVC Help
Powered by ViewVC 1.1.22