/[MITgcm]/MITgcm/pkg/seaice/seaice_calc_strainrates.F
ViewVC logotype

Contents of /MITgcm/pkg/seaice/seaice_calc_strainrates.F

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


Revision 1.8 - (show annotations) (download)
Tue Nov 13 19:26:25 2007 UTC (16 years, 10 months ago) by jmc
Branch: MAIN
Changes since 1.7: +13 -7 lines
add arguments myTime, myIter & iStep (= sub-time-step) (easier for debugging)
 to S/R SEAICE_CALC_STRAINRATES & SEAICE_CALC_VISCOSITIES

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_calc_strainrates.F,v 1.7 2007/09/19 08:48:21 mlosch Exp $
2 C $Name: $
3
4 #include "SEAICE_OPTIONS.h"
5
6 CStartOfInterface
7 SUBROUTINE SEAICE_CALC_STRAINRATES(
8 I uFld, vFld,
9 O e11, e22, e12,
10 I iStep, myTime, myIter, myThid )
11 C /==========================================================\
12 C | SUBROUTINE SEAICE_CALC_STRAINRATES |
13 C | o compute strain rates from ice velocities |
14 C |==========================================================|
15 C | written by Martin Losch, Apr 2007 |
16 C \==========================================================/
17 IMPLICIT NONE
18
19 C === Global variables ===
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "PARAMS.h"
23 #include "GRID.h"
24 #include "SEAICE_PARAMS.h"
25
26 #ifdef ALLOW_AUTODIFF_TAMC
27 # include "tamc.h"
28 #endif
29
30 C === Routine arguments ===
31 C iStep :: Sub-time-step number
32 C myTime :: Simulation time
33 C myIter :: Simulation timestep number
34 C myThid :: My Thread Id. number
35 INTEGER iStep
36 _RL myTime
37 INTEGER myIter
38 INTEGER myThid
39 C ice velocities
40 _RL uFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
41 _RL vFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
42 C strain rate tensor
43 _RL e11 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
44 _RL e22 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
45 _RL e12 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
46 CEndOfInterface
47
48 #ifdef SEAICE_CGRID
49 #ifdef SEAICE_ALLOW_DYNAMICS
50 C === Local variables ===
51 C i,j,bi,bj - Loop counters
52 INTEGER i, j, bi, bj
53 C hFacU, hFacV - determine the no-slip boundary condition
54 INTEGER k
55 _RS hFacU, hFacV
56
57 k = 1
58 C
59 DO bj=myByLo(myThid),myByHi(myThid)
60 DO bi=myBxLo(myThid),myBxHi(myThid)
61 DO j=1-Oly,sNy+Oly-1
62 DO i=1-Olx,sNx+Olx-1
63 C evaluate strain rates
64 e11(I,J,bi,bj) = _recip_dxF(I,J,bi,bj) *
65 & (uFld(I+1,J,bi,bj)-uFld(I,J,bi,bj))
66 & -HALF*
67 & (vFld(I,J,bi,bj)+vFld(I,J+1,bi,bj))
68 & * _tanPhiAtU(I,J,bi,bj)*recip_rSphere
69 e22(I,J,bi,bj) = _recip_dyF(I,J,bi,bj) *
70 & (vFld(I,J+1,bi,bj)-vFld(I,J,bi,bj))
71 C one metric term is missing
72 ENDDO
73 ENDDO
74 DO j=1-Oly+1,sNy+Oly
75 DO i=1-Olx+1,sNx+Olx
76 e12(I,J,bi,bj) = HALF*(
77 & (uFld(I ,J ,bi,bj) * _dxC(I ,J ,bi,bj)
78 & -uFld(I ,J-1,bi,bj) * _dxC(I ,J-1,bi,bj)
79 & +vFld(I ,J ,bi,bj) * _dyC(I ,J ,bi,bj)
80 & -vFld(I-1,J ,bi,bj) * _dyC(I-1,J ,bi,bj))
81 & * recip_rAz(I,J,bi,bj)
82 & +
83 & 0.25 _d 0 * (uFld(I,J,bi,bj)+uFld(I ,J-1,bi,bj))
84 & * ( _tanPhiAtU(I,J,bi,bj) + _tanPhiAtU(I,J-1,bi,bj) )
85 & *recip_rSphere
86 & )
87 & *maskC(I ,J ,k,bi,bj)*maskC(I-1,J ,k,bi,bj)
88 & *maskC(I ,J-1,k,bi,bj)*maskC(I-1,J-1,k,bi,bj)
89 C one metric term is missing
90 ENDDO
91 ENDDO
92 IF ( SEAICE_no_slip ) THEN
93 C no slip boundary conditions apply only to e12
94 DO j=1-Oly+1,sNy+Oly
95 DO i=1-Olx+1,sNx+Olx
96 hFacU = _maskW(i,j,k,bi,bj) - _maskW(i,j-1,k,bi,bj)
97 hFacV = _maskS(i,j,k,bi,bj) - _maskS(i-1,j,k,bi,bj)
98
99 e12(I,J,bi,bj) = e12(I,J,bi,bj)
100 & + recip_rAz(i,j,bi,bj) *
101 & ( hFacU * ( _dxC(i,j-1,bi,bj)*uFld(i,j ,bi,bj)
102 & + _dxC(i,j, bi,bj)*uFld(i,j-1,bi,bj) )
103 & + hFacV * ( _dyC(i-1,j,bi,bj)*vFld(i ,j,bi,bj)
104 & + _dyC(i, j,bi,bj)*vFld(i-1,j,bi,bj) ) )
105 & - hFacU
106 & * 0.25 _d 0 * (uFld(I,J,bi,bj)+uFld(I ,J-1,bi,bj))
107 & * ( _tanPhiAtU(I,J,bi,bj) + _tanPhiAtU(I,J-1,bi,bj) )
108 & *recip_rSphere
109 C one metric term is missing
110 ENDDO
111 ENDDO
112
113 ENDIF
114 ENDDO
115 ENDDO
116 #endif /* SEAICE_ALLOW_DYNAMICS */
117 #endif /* SEAICE_CGRID */
118 RETURN
119 END

  ViewVC Help
Powered by ViewVC 1.1.22