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

Diff of /MITgcm/pkg/seaice/seaice_ocean_stress.F

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

revision 1.16 by mlosch, Tue Apr 24 18:38:15 2007 UTC revision 1.24 by mlosch, Fri May 29 14:51:21 2009 UTC
# Line 4  C $Name$ Line 4  C $Name$
4  #include "SEAICE_OPTIONS.h"  #include "SEAICE_OPTIONS.h"
5    
6  CStartOfInterface  CStartOfInterface
7        SUBROUTINE SEAICE_OCEAN_STRESS(        SUBROUTINE SEAICE_OCEAN_STRESS(
8       I     myTime, myIter, myThid )       I     myTime, myIter, myThid )
9  C     /==========================================================\  C     /==========================================================\
10  C     | SUBROUTINE SEAICE_OCEAN_STRESS                           |  C     | SUBROUTINE SEAICE_OCEAN_STRESS                           |
# Line 18  C     === Global variables === Line 18  C     === Global variables ===
18  #include "SIZE.h"  #include "SIZE.h"
19  #include "EEPARAMS.h"  #include "EEPARAMS.h"
20  #include "PARAMS.h"  #include "PARAMS.h"
21    #include "DYNVARS.h"
22  #include "GRID.h"  #include "GRID.h"
23  #include "FFIELDS.h"  #include "FFIELDS.h"
24  #include "SEAICE.h"  #include "SEAICE.h"
# Line 32  C     myThid - Thread no. that called th Line 33  C     myThid - Thread no. that called th
33        INTEGER myThid        INTEGER myThid
34  CEndOfInterface  CEndOfInterface
35    
36  #ifdef SEAICE_CGRID  #ifdef SEAICE_CGRID
37  C     === Local variables ===  C     === Local variables ===
38  C     i,j,bi,bj - Loop counters  C     i,j,bi,bj - Loop counters
39    
40        INTEGER i, j, bi, bj        INTEGER i, j, bi, bj
41        _RL  SINWAT, COSWAT, SINWIN, COSWIN        _RL  SINWAT, COSWAT, SINWIN, COSWIN
42        _RL  fuIceLoc, fvIceLoc, FX, FY        _RL  fuIceLoc, fvIceLoc
43        _RL  areaW, areaS        _RL  areaW, areaS
44    
       _RL e11         (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)  
       _RL e22         (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)  
       _RL e12         (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)  
       _RL press       (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)  
       _RL sig11       (1-Olx:sNx+Olx,1-Oly:sNy+Oly)  
       _RL sig22       (1-Olx:sNx+Olx,1-Oly:sNy+Oly)  
       _RL sig12       (1-Olx:sNx+Olx,1-Oly:sNy+Oly)  
       _RL eplus, eminus  
   
45  c     introduce turning angle (default is zero)  c     introduce turning angle (default is zero)
46        SINWAT=SIN(SEAICE_waterTurnAngle*deg2rad)        SINWAT=SIN(SEAICE_waterTurnAngle*deg2rad)
47        COSWAT=COS(SEAICE_waterTurnAngle*deg2rad)        COSWAT=COS(SEAICE_waterTurnAngle*deg2rad)
48        SINWIN=SIN(SEAICE_airTurnAngle*deg2rad)        SINWIN=SIN(SEAICE_airTurnAngle*deg2rad)
49        COSWIN=COS(SEAICE_airTurnAngle*deg2rad)        COSWIN=COS(SEAICE_airTurnAngle*deg2rad)
50    
 C--   Update overlap regions  
       CALL EXCH_UV_XY_RL(WINDX, WINDY, .TRUE., myThid)  
   
 #ifndef SEAICE_EXTERNAL_FLUXES  
 C--   Interpolate wind stress (N/m^2) from C-points of C-grid  
 C     to U and V points of C-grid for forcing the ocean model.  
       DO bj=myByLo(myThid),myByHi(myThid)  
        DO bi=myBxLo(myThid),myBxHi(myThid)  
         DO j=1,sNy  
          DO i=1,sNx  
           fu(I,J,bi,bj)=0.5*(WINDX(I,J,bi,bj) + WINDX(I-1,J,bi,bj))  
           fv(I,J,bi,bj)=0.5*(WINDY(I,J,bi,bj) + WINDY(I,J-1,bi,bj))  
          ENDDO  
         ENDDO  
        ENDDO  
       ENDDO  
 #endif /* ifndef SEAICE_EXTERNAL_FLUXES */  
   
51        IF ( useHB87StressCoupling ) THEN        IF ( useHB87StressCoupling ) THEN
52  C  C
53  C     use an intergral over ice and ocean surface layer to define  C     use an intergral over ice and ocean surface layer to define
54  C     surface stresses on ocean following Hibler and Bryan (1987, JPO)  C     surface stresses on ocean following Hibler and Bryan (1987, JPO)
55  C      C
 C     recompute strain rates, viscosities, etc. from updated ice velocities  
        IF ( .NOT. SEAICEuseEVP ) THEN  
 C     only for EVP we already have the stress components otherwise we need  
 C     to recompute them here  
         CALL SEAICE_CALC_STRAINRATES(  
      I       uIce(1-Olx,1-Oly,1,1,1), vIce(1-Olx,1-Oly,1,1,1),  
      O       e11, e22, e12,  
      I       myThid )  
   
         CALL SEAICE_CALC_VISCOSITIES(  
      I       e11, e22, e12, zMin, zMax, hEffM, press0,  
      O       eta, zeta, press,  
      I       myThid )  
        ENDIF  
 C     re-compute internal stresses with updated ice velocities  
56         DO bj=myByLo(myThid),myByHi(myThid)         DO bj=myByLo(myThid),myByHi(myThid)
57          DO bi=myBxLo(myThid),myBxHi(myThid)          DO bi=myBxLo(myThid),myBxHi(myThid)
58           IF ( .NOT. SEAICEuseEVP ) THEN           DO J=1,sNy
59  C     only for EVP we already have computed the stress divergences, for            DO I=1,sNx
60  C     anything else we have to do it here  C     average wind stress over ice and ocean and apply averaged wind
           DO j=1-Oly,sNy+Oly  
            DO i=1-Olx,sNx+Olx  
             sig11(I,J) = 0. _d 0  
             sig22(I,J) = 0. _d 0  
             sig12(I,J) = 0. _d 0  
            ENDDO  
           ENDDO  
   
           DO j=1-Oly+1,sNy+Oly-1  
            DO i=1-Olx+1,sNx+Olx-1  
             eplus = e11(I,J,bi,bj) + e22(I,J,bi,bj)  
             eminus= e11(I,J,bi,bj) - e22(I,J,bi,bj)  
             sig11(I,J) = zeta(I,J,bi,bj)*eplus + eta(I,J,bi,bj)*eminus  
      &           - 0.5 _d 0 * PRESS(I,J,bi,bj)  
             sig22(I,J) = zeta(I,J,bi,bj)*eplus - eta(I,J,bi,bj)*eminus  
      &           - 0.5 _d 0 * PRESS(I,J,bi,bj)  
             sig12(I,J) = 2. _d 0 * e12(I,J,bi,bj) *  
      &           ( eta(I,J  ,bi,bj) + eta(I-1,J  ,bi,bj)  
      &           + eta(I,J-1,bi,bj) + eta(I-1,J-1,bi,bj) )  
      &           /MAX(1. _d 0,  
      &             hEffM(I,J  ,bi,bj) + hEffM(I-1,J  ,bi,bj)  
      &           + hEffM(I,J-1,bi,bj) + hEffM(I-1,J-1,bi,bj))  
            ENDDO  
           ENDDO  
 C     evaluate divergence of stress and apply to forcing  
           DO J=1,sNy  
            DO I=1,sNx  
             FX = ( sig11(I  ,J  ) * _dyF(I  ,J  ,bi,bj)  
      &           - sig11(I-1,J  ) * _dyF(I-1,J  ,bi,bj)  
      &           + sig12(I  ,J+1) * _dxV(I  ,J+1,bi,bj)  
      &           - sig12(I  ,J  ) * _dxV(I  ,J  ,bi,bj)  
      &           ) * recip_rAw(I,J,bi,bj)  
      &           -  
      &           ( sig12(I,J) + sig12(I,J+1) )  
      &           * _tanPhiAtU(I,J,bi,bj) * recip_rSphere  
      &           +  
      &           ( sig22(I,J) + sig22(I-1,J) ) * 0.5 _d 0  
      &           * _tanPhiAtU(I,J,bi,bj) * recip_rSphere  
 C     one metric term  missing for general curvilinear coordinates  
             FY = ( sig22(I  ,J  ) * _dxF(I  ,J  ,bi,bj)  
      &           - sig22(I  ,J-1) * _dxF(I  ,J-1,bi,bj)  
      &           + sig12(I+1,J  ) * _dyU(I+1,J  ,bi,bj)  
      &           - sig12(I  ,J  ) * _dyU(I  ,J  ,bi,bj)  
      &           ) * recip_rAs(I,J,bi,bj)  
      &           -  
      &           ( sig22(I,J) + sig22(I,J-1) ) * 0.5 _d 0  
      &           * _tanPhiAtV(I,J,bi,bj) * recip_rSphere  
 C     two metric terms missing for general curvilinear coordinates  
 C     average wind stress over ice and ocean and apply averaged wind  
61  C     stress and internal ice stresses to surface layer of ocean  C     stress and internal ice stresses to surface layer of ocean
62              areaW = 0.5 * (AREA(I,J,1,bi,bj) + AREA(I-1,J,1,bi,bj))             areaW = 0.5 * (AREA(I,J,1,bi,bj) + AREA(I-1,J,1,bi,bj))
63       &           * SEAICEstressFactor       &          * SEAICEstressFactor
64              areaS = 0.5 * (AREA(I,J,1,bi,bj) + AREA(I,J-1,1,bi,bj))             areaS = 0.5 * (AREA(I,J,1,bi,bj) + AREA(I,J-1,1,bi,bj))
65       &           * SEAICEstressFactor       &          * SEAICEstressFactor
66              fu(I,J,bi,bj)=(ONE-areaW)*fu(I,J,bi,bj)             fu(I,J,bi,bj)=(ONE-areaW)*fu(I,J,bi,bj)
67       &           + areaW*taux(I,J,bi,bj)       &          + areaW*taux(I,J,bi,bj)
68       &           + FX * SEAICEstressFactor       &          + stressDivergenceX(I,J,bi,bj) * SEAICEstressFactor
69              fv(I,J,bi,bj)=(ONE-areaS)*fv(I,J,bi,bj)             fv(I,J,bi,bj)=(ONE-areaS)*fv(I,J,bi,bj)
70       &           + areaS*tauy(I,J,bi,bj)       &          + areaS*tauy(I,J,bi,bj)
71       &           + FY * SEAICEstressFactor       &          + stressDivergenceY(I,J,bi,bj) * SEAICEstressFactor
 C     save stress divergence for later  
 #ifdef SEAICE_ALLOW_EVP  
             stressDivergenceX(I,J,bi,bj) = FX  
             stressDivergenceY(I,J,bi,bj) = FY  
 #endif /* SEAICE_ALLOW_EVP */  
            ENDDO  
72            ENDDO            ENDDO
73           ELSE           ENDDO
 #ifdef SEAICE_ALLOW_EVP  
           DO J=1,sNy  
            DO I=1,sNx  
 C     average wind stress over ice and ocean and apply averaged wind  
 C     stress and internal ice stresses to surface layer of ocean  
             areaW = 0.5 * (AREA(I,J,1,bi,bj) + AREA(I-1,J,1,bi,bj))  
      &           * SEAICEstressFactor  
             areaS = 0.5 * (AREA(I,J,1,bi,bj) + AREA(I,J-1,1,bi,bj))  
      &           * SEAICEstressFactor  
             fu(I,J,bi,bj)=(ONE-areaW)*fu(I,J,bi,bj)  
      &           + areaW*taux(I,J,bi,bj)  
      &           + stressDivergenceX(I,J,bi,bj) * SEAICEstressFactor  
             fv(I,J,bi,bj)=(ONE-areaS)*fv(I,J,bi,bj)  
      &           + areaS*tauy(I,J,bi,bj)  
      &           + stressDivergenceY(I,J,bi,bj) * SEAICEstressFactor  
            ENDDO  
           ENDDO  
 #endif /* SEAICE_ALLOW_EVP */  
          ENDIF  
74          ENDDO          ENDDO
75         ENDDO         ENDDO
76    
77        ELSE        ELSE
78    C     else: useHB87StressCoupling=F
79    
80  C--   Compute ice-affected wind stress (interpolate to U/V-points)  C--   Compute ice-affected wind stress (interpolate to U/V-points)
81  C     by averaging wind stress and ice-ocean stress according to  C     by averaging wind stress and ice-ocean stress according to
82  C     ice cover  C     ice cover
83        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
84         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
85          DO j=1,sNy          DO j=1,sNy
86           DO i=1,sNx           DO i=1,sNx
87            fuIceLoc=HALF*( DWATN(I,J,bi,bj)+DWATN(I,J+1,bi,bj) )*            fuIceLoc=HALF*( DWATN(I,J,bi,bj)+DWATN(I-1,J,bi,bj) )*
88       &         COSWAT *       &         COSWAT *
89       &         ( UICE(I,J,1,bi,bj)-GWATX(I,J,bi,bj) )       &         ( UICE(I,J,1,bi,bj)-uVel(I,J,1,bi,bj) )
90       &         - SIGN(SINWAT, _fCori(I,J,bi,bj)) * 0.5 _d 0 *       &         - SIGN(SINWAT, _fCori(I,J,bi,bj)) * 0.5 _d 0 *
91       &         ( DWATN(I  ,J,bi,bj) *       &         ( DWATN(I  ,J,bi,bj) *
92       &         0.5 _d 0*(vIce(I  ,J  ,1,bi,bj)-GWATY(I  ,J  ,bi,bj)       &         0.5 _d 0*(vIce(I  ,J  ,1,bi,bj)-vVel(I  ,J  ,1,bi,bj)
93       &                  +vIce(I  ,J+1,1,bi,bj)-GWATY(I  ,J+1,bi,bj))       &                  +vIce(I  ,J+1,1,bi,bj)-vVel(I  ,J+1,1,bi,bj))
94       &         + DWATN(I-1,J,bi,bj) *       &         + DWATN(I-1,J,bi,bj) *
95       &         0.5 _d 0*(vIce(I-1,J  ,1,bi,bj)-GWATY(I-1,J  ,bi,bj)       &         0.5 _d 0*(vIce(I-1,J  ,1,bi,bj)-vVel(I-1,J  ,1,bi,bj)
96       &                  +vIce(I-1,J+1,1,bi,bj)-GWATY(I-1,J+1,bi,bj))       &                  +vIce(I-1,J+1,1,bi,bj)-vVel(I-1,J+1,1,bi,bj))
97       &         )       &         )
98            fvIceLoc=HALF*( DWATN(I,J,bi,bj)+DWATN(I+1,J,bi,bj) )*            fvIceLoc=HALF*( DWATN(I,J,bi,bj)+DWATN(I,J-1,bi,bj) )*
99       &         COSWAT *       &         COSWAT *
100       &         ( VICE(I,J,1,bi,bj)-GWATY(I,J,bi,bj) )       &         ( VICE(I,J,1,bi,bj)-vVel(I,J,1,bi,bj) )
101       &         + SIGN(SINWAT,  _fCori(I,J,bi,bj)) * 0.5 _d 0 *       &         + SIGN(SINWAT,  _fCori(I,J,bi,bj)) * 0.5 _d 0 *
102       &         ( DWATN(I,J  ,bi,bj) *       &         ( DWATN(I,J  ,bi,bj) *
103       &         0.5 _d 0*(uIce(I  ,J  ,1,bi,bj)-GWATX(I  ,J  ,bi,bj)       &         0.5 _d 0*(uIce(I  ,J  ,1,bi,bj)-uVel(I  ,J  ,1,bi,bj)
104       &                  +uIce(I+1,J  ,1,bi,bj)-GWATX(I+1,J  ,bi,bj))       &                  +uIce(I+1,J  ,1,bi,bj)-uVel(I+1,J  ,1,bi,bj))
105       &         + DWATN(I,J-1,bi,bj) *       &         + DWATN(I,J-1,bi,bj) *
106       &         0.5 _d 0*(uIce(I  ,J-1,1,bi,bj)-GWATX(I  ,J-1,bi,bj)       &         0.5 _d 0*(uIce(I  ,J-1,1,bi,bj)-uVel(I  ,J-1,1,bi,bj)
107       &                  +uIce(I+1,J-1,1,bi,bj)-GWATX(I+1,J-1,bi,bj))       &                  +uIce(I+1,J-1,1,bi,bj)-uVel(I+1,J-1,1,bi,bj))
108       &         )       &         )
109            areaW = 0.5 _d 0 * (AREA(I,J,1,bi,bj) + AREA(I-1,J,1,bi,bj))            areaW = 0.5 _d 0 * (AREA(I,J,1,bi,bj) + AREA(I-1,J,1,bi,bj))
110       &         * SEAICEstressFactor       &         * SEAICEstressFactor
# Line 232  C     ice cover Line 119  C     ice cover
119        ENDIF        ENDIF
120        CALL EXCH_UV_XY_RS(fu, fv, .TRUE., myThid)        CALL EXCH_UV_XY_RS(fu, fv, .TRUE., myThid)
121    
122  #endif /* not SEAICE_CGRID */  #endif /* SEAICE_CGRID */
123    
124        RETURN        RETURN
125        END        END

Legend:
Removed from v.1.16  
changed lines
  Added in v.1.24

  ViewVC Help
Powered by ViewVC 1.1.22