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

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

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


Revision 1.2 - (show annotations) (download)
Sun Feb 17 02:29:52 2013 UTC (11 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64o, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint64n, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint65, checkpoint64j, checkpoint64m, checkpoint64l, HEAD
Changes since 1.1: +59 -12 lines
- add new argument to skip the setting of grid-angle at grid-cell center
- also set new projection array for model C-grid velocity

1 C $Header: /u/gcmpack/MITgcm/model/src/calc_grid_angles.F,v 1.1 2011/12/25 22:24:35 jmc Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP
8 C !ROUTINE: CALC_GRID_ANGLES
9 C !INTERFACE:
10 SUBROUTINE CALC_GRID_ANGLES( skipCalcAngleC, myThid )
11
12 C !DESCRIPTION: \bv
13 C *===================================================================*
14 C | SUBROUTINE CALC_GRID_ANGLES
15 C | o calculate the angle between geographical north and model grid
16 C | north, assuming that yG holds the geographical coordinates
17 C *===================================================================*
18 C \ev
19
20 C !USES:
21 IMPLICIT NONE
22 C === Global variables ===
23 #include "SIZE.h"
24 #include "EEPARAMS.h"
25 #include "PARAMS.h"
26 #include "GRID.h"
27
28 C !INPUT/OUTPUT PARAMETERS:
29 C == Routine arguments ==
30 C skipCalcAngleC :: skip setting of grid-angle at cell-center location
31 C myThid :: my Thread Id Number
32 LOGICAL skipCalcAngleC
33 INTEGER myThid
34 CEOP
35
36 C !LOCAL VARIABLES:
37 C == Local variables ==
38 C bi,bj :: Tile indices
39 C i, j :: Loop counters
40 INTEGER bi, bj
41 INTEGER i, j
42 C pseudo velocities
43 _RL uPseudo(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
44 _RL vPseudo(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
45 _RL uC, vC, uNorm, tmpVal
46 CEOP
47
48 C- For each tile ...
49 DO bj = myByLo(myThid), myByHi(myThid)
50 DO bi = myBxLo(myThid), myBxHi(myThid)
51
52 C- compute pseudo velocities from stream function psi = -yG*deg2rad,
53 C that is, zonal flow
54 DO j = 1-OLy,sNy+OLy-1
55 DO i = 1-OLx,sNx+OLx
56 IF ( _dyG(i,j,bi,bj).GT.0. ) THEN
57 uPseudo(i,j) =
58 & - ( yG(i,j,bi,bj) - yG(i,j+1,bi,bj) )*deg2rad
59 & / _dyG(i,j,bi,bj)
60 ELSE
61 uPseudo(i,j) = 0.
62 ENDIF
63 u2zonDir(i,j,bi,bj) = rSphere*uPseudo(i,j)
64 ENDDO
65 ENDDO
66 DO j = 1-OLy,sNy+OLy
67 DO i = 1-OLx,sNx+OLx-1
68 IF ( _dxG(i,j,bi,bj).GT.0. ) THEN
69 vPseudo(i,j) =
70 & + ( yG(i,j,bi,bj) - yG(i+1,j,bi,bj) )*deg2rad
71 & / _dxG(i,j,bi,bj)
72 ELSE
73 vPseudo(i,j) = 0.
74 ENDIF
75 v2zonDir(i,j,bi,bj) = rSphere*vPseudo(i,j)
76 ENDDO
77 ENDDO
78 IF ( .NOT.skipCalcAngleC ) THEN
79 DO j = 1-OLy,sNy+OLy-1
80 DO i = 1-OLx,sNx+OLx-1
81 uC = 0.5*(uPseudo(i,j) + uPseudo(i+1,j))
82 vC = 0.5*(vPseudo(i,j) + vPseudo(i,j+1))
83 uNorm = SQRT(uC*uC+vC*vC)
84 IF ( uNorm .NE. 0. _d 0 ) uNorm = 1. _d 0/uNorm
85 angleCosC(i,j,bi,bj) = uC*uNorm
86 angleSinC(i,j,bi,bj) = -vC*uNorm
87 ENDDO
88 ENDDO
89 ENDIF
90
91 C- To check angular momentum conservation, use an alternative definition
92 C of grid-angles cosine (@ U pt) & sine (@ V pt) (consistent with
93 C stream-function of solid-body velocity field).
94 DO j = 1-OLy,sNy+OLy-1
95 DO i = 1-OLx,sNx+OLx
96 C- Note: most natural way would be to divide by dyG (as below); but scaling by
97 C dxC/rAw ensures that u2zonDir is exactly =1 with current Lat-Lon grid
98 c tmpVal = _dyG(i,j,bi,bj) * COS( deg2rad*
99 tmpVal = _rAw(i,j,bi,bj) * COS( deg2rad*
100 & ( yG(i,j,bi,bj) + yG(i,j+1,bi,bj) )*halfRL )
101 IF ( tmpVal.GT.0. ) THEN
102 u2zonDir(i,j,bi,bj) = rSphere
103 & *( SIN( yG(i,j+1,bi,bj)*deg2rad )
104 & - SIN( yG(i, j, bi,bj)*deg2rad )
105 & )* _dxC(i,j,bi,bj)/tmpVal
106 c & )/tmpVal
107 ELSE
108 u2zonDir(i,j,bi,bj) = 1.
109 ENDIF
110 ENDDO
111 ENDDO
112 DO j = 1-OLy,sNy+OLy
113 DO i = 1-OLx,sNx+OLx-1
114 C- Note: most natural way would be to divide by dxG (as below); for symetry
115 C reason with u2zonDir expression, we use instead dyC/rAs scaling factor
116 c tmpVal = _dxG(i,j,bi,bj) * COS( deg2rad*
117 tmpVal = _rAs(i,j,bi,bj) * COS( deg2rad*
118 & ( yG(i,j,bi,bj) + yG(i+1,j,bi,bj) )*halfRL )
119 IF ( tmpVal.GT.0. ) THEN
120 v2zonDir(i,j,bi,bj) = -rSphere
121 & *( SIN( yG(i+1,j,bi,bj)*deg2rad )
122 & - SIN( yG(i,j,bi,bj)*deg2rad )
123 & )* _dyC(i,j,bi,bj)/tmpVal
124 c & )/tmpVal
125 ELSE
126 v2zonDir(i,j,bi,bj) = 0.
127 ENDIF
128 ENDDO
129 ENDDO
130
131 C- bi,bj-loops
132 ENDDO
133 ENDDO
134
135 RETURN
136 END

  ViewVC Help
Powered by ViewVC 1.1.22