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

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

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


Revision 1.4 - (show annotations) (download)
Sun Nov 21 16:06:05 2004 UTC (19 years, 6 months ago) by jmc
Branch: MAIN
Changes since 1.3: +48 -10 lines
change to be valid in the overlap region for CS-grid.

1 C $Header: /u/gcmpack/MITgcm/model/src/grad_sigma.F,v 1.3 2001/09/26 18:09:15 cnh Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: GRAD_SIGMA
8 C !INTERFACE:
9 SUBROUTINE GRAD_SIGMA(
10 I bi, bj, iMin, iMax, jMin, jMax, K,
11 I rhoK, sigKm1, sigKp1,
12 O sigmaX, sigmaY, sigmaR,
13 I myThid )
14 C !DESCRIPTION: \bv
15 C *==========================================================*
16 C | SUBROUTINE CALC_ISOSLOPES
17 C | o Calculate isoneutral gradients
18 C *==========================================================*
19 C \ev
20
21 C !USES:
22 IMPLICIT NONE
23 C == Global variables ==
24 #include "SIZE.h"
25 #include "GRID.h"
26 #include "EEPARAMS.h"
27 #include "PARAMS.h"
28
29 C !INPUT/OUTPUT PARAMETERS:
30 C == Routine arguments ==
31 C rhoK :: density at level k
32 C sigKm1 :: upper level density computed at current pressure
33 C sigKp1 :: lower level density computed at current pressure
34 C sigmaX,Y,R :: iso-neutral gradient of density in 3 directions X,Y,R
35 INTEGER bi,bj,iMin,iMax,jMin,jMax,K
36 _RL rhoK(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
37 _RL sigKm1(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
38 _RL sigKp1(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
39 _RL sigmaX(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
40 _RL sigmaY(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
41 _RL sigmaR(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
42 INTEGER myThid
43
44 C !LOCAL VARIABLES:
45 C == Local variables ==
46 C rhoLoc :: local copy of rhoK
47 INTEGER i,j
48 _RL rhoLoc(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
49 CEOP
50
51 C- safer to work on a local copy of rhoK (before a partial update)
52 DO j=1-Oly,sNy+Oly
53 DO i=1-Olx,sNx+Olx
54 rhoLoc(i,j) = rhoK(i,j)
55 ENDDO
56 ENDDO
57
58 C- Internal exchange for calculations in X
59 IF ( useCubedSphereExchange ) THEN
60 CALL FILL_CS_CORNER_TR_RL( .TRUE., rhoLoc, bi,bj, myThid )
61 ENDIF
62 DO j=1-Oly,sNy+Oly
63 DO i=1-Olx+1,sNx+Olx
64 sigmaX(i,j,k)=_maskW(i,j,k,bi,bj)
65 & *_recip_dxC(i,j,bi,bj)
66 & *(rhoLoc(i,j)-rhoLoc(i-1,j))
67 ENDDO
68 ENDDO
69
70 C- Internal exchange for calculations in Y
71 IF ( useCubedSphereExchange ) THEN
72 CALL FILL_CS_CORNER_TR_RL( .FALSE., rhoLoc, bi,bj, myThid )
73 ENDIF
74 DO j=1-Oly+1,sNy+Oly
75 DO i=1-Olx,sNx+Olx
76 sigmaY(i,j,k)=_maskS(i,j,k,bi,bj)
77 & *_recip_dyC(i,j,bi,bj)
78 & *(rhoLoc(i,j)-rhoLoc(i,j-1))
79 ENDDO
80 ENDDO
81
82 C- jmc: Patrick, will this work for TAF ?
83 IF (K.EQ.1) THEN
84 DO j=1-Oly,sNy+Oly
85 DO i=1-Olx,sNx+Olx
86 sigmaR(i,j,k)=0.
87 ENDDO
88 ENDDO
89 ELSE
90 DO j=1-Oly,sNy+Oly
91 DO i=1-Olx,sNx+Olx
92 sigmaR(i,j,k)= maskC(i,j,k,bi,bj)
93 & *recip_drC(k)*rkFac
94 & *(sigKm1(i,j)-sigKp1(i,j))
95 ENDDO
96 ENDDO
97 ENDIF
98 C- jmc: leave the old code commented (in case ...)
99 c DO j=1-Oly,sNy+Oly
100 c DO i=1-Olx,sNx+Olx
101 c IF (K.NE.1 .AND. hfacC(i,j,k,bi,bj).NE.0.) THEN
102 c sigmaR(i,j,k)=recip_drC(k)*rkFac*(sigKm1(i,j)-sigKp1(i,j))
103 c ELSE
104 c sigmaR(i,j,k)=0.
105 c ENDIF
106 c ENDDO
107 c ENDDO
108
109 RETURN
110 END

  ViewVC Help
Powered by ViewVC 1.1.22