/[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.2 - (show annotations) (download)
Sun Apr 22 19:56:22 2007 UTC (17 years, 5 months ago) by mlosch
Branch: MAIN
Changes since 1.1: +30 -12 lines
- add no slip conditions for evp solver (off by default), lsr-version
  may follow
- fix exchange for shear at Z-points (does not change lab_sea)
- retire SEAICEuseEVP, instead turn on EVP by setting SEAICE_deltaTevp
  (to force the user to pick a time step since there is not "safe" way
   of choosing it)

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_calc_strainrates.F,v 1.1 2007/04/20 18:29:58 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 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 myThid - Thread no. that called this routine.
32 INTEGER myThid
33 C ice velocities
34 _RL uFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
35 _RL vFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
36 C strain rate tensor
37 _RL e11 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
38 _RL e22 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
39 _RL e12 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
40 CEndOfInterface
41
42 #ifdef SEAICE_CGRID
43 #ifdef SEAICE_ALLOW_DYNAMICS
44 C === Local variables ===
45 C i,j,bi,bj - Loop counters
46 INTEGER i, j, bi, bj
47 C hFacU, hFacV - determine the no-slip boundary condition
48 INTEGER k
49 _RS hFacU, hFacV
50
51
52 C
53 DO bj=myByLo(myThid),myByHi(myThid)
54 DO bi=myBxLo(myThid),myBxHi(myThid)
55 DO j=1-Oly+1,sNy+Oly-1
56 DO i=1-Olx+1,sNx+Olx-1
57 C NOW EVALUATE STRAIN RATES
58 e11(I,J,bi,bj)= _recip_dxF(I,J,bi,bj) *
59 & (uFld(I+1,J,bi,bj)-uFld(I,J,bi,bj))
60 & -HALF*
61 & (vFld(I,J,bi,bj)+vFld(I,J+1,bi,bj))
62 & * _tanPhiAtU(I,J,bi,bj)*recip_rSphere
63 e22(I,J,bi,bj)= _recip_dyF(I,J,bi,bj) *
64 & (vFld(I,J+1,bi,bj)-vFld(I,J,bi,bj))
65 C one metric term is missing
66 e12(I,J,bi,bj)=HALF*(
67 & (uFld(I ,J ,bi,bj) * _dxC(I ,J ,bi,bj)
68 & -uFld(I ,J-1,bi,bj) * _dxC(I ,J-1,bi,bj)
69 & +vFld(I ,J ,bi,bj) * _dyC(I ,J ,bi,bj)
70 & -vFld(I-1,J ,bi,bj) * _dyC(I-1,J ,bi,bj))
71 & * recip_rAz(I,J,bi,bj)
72 & +
73 & 0.25 _d 0 * (uFld(I,J,bi,bj)+uFld(I ,J-1,bi,bj))
74 & * ( _tanPhiAtU(I,J,bi,bj) + _tanPhiAtU(I,J-1,bi,bj) )
75 & *recip_rSphere
76 & )
77 C one metric term is missing
78 ENDDO
79 ENDDO
80 IF ( SEAICE_no_slip ) THEN
81 C no slip boundary conditions are applied as a body force
82 C following mom_u/v_sidedrag
83 k = 1
84 DO j=1-Oly+1,sNy+Oly-1
85 DO i=1-Olx+1,sNx+Olx-1
86 hFacU = _maskW(i,j,k,bi,bj) - _maskW(i,j-1,k,bi,bj)
87 hFacV = _maskS(i,j,k,bi,bj) - _maskS(i-1,j,k,bi,bj)
88
89 e12(I,J,bi,bj)= e12(I,J,bi,bj)
90 & + HALF*( recip_rAz(i,j,bi,bj)
91 & *( hFacU * ( _dxC(i,j ,bi,bj)*uFld(i,j ,bi,bj)
92 & + _dxC(i,j-1,bi,bj)*uFld(i,j-1,bi,bj) )
93 & + hFacV * ( _dyC(i ,j,bi,bj)*vFld(i ,j,bi,bj)
94 & + _dyC(i-1,j,bi,bj)*vFld(i-1,j,bi,bj) ) )
95 & - hFacU
96 & * 0.25 _d 0 * (uFld(I,J,bi,bj)+uFld(I ,J-1,bi,bj))
97 & * ( _tanPhiAtU(I,J,bi,bj) + _tanPhiAtU(I,J-1,bi,bj) )
98 & *recip_rSphere
99 & )
100 C one metric term is missing
101 ENDDO
102 ENDDO
103
104 ENDIF
105 ENDDO
106 ENDDO
107 #endif /* SEAICE_ALLOW_DYNAMICS */
108 #endif /* SEAICE_CGRID */
109 RETURN
110 END

  ViewVC Help
Powered by ViewVC 1.1.22