/[MITgcm]/MITgcm/pkg/aim_compon_interf/atm_store_taux.F
ViewVC logotype

Diff of /MITgcm/pkg/aim_compon_interf/atm_store_taux.F

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

revision 1.1 by jmc, Mon Dec 15 02:44:48 2003 UTC revision 1.2 by jmc, Fri May 21 20:00:48 2004 UTC
# Line 5  C $Name$ Line 5  C $Name$
5    
6  CStartOfInterface  CStartOfInterface
7        SUBROUTINE ATM_STORE_TAUX( bi,bj,        SUBROUTINE ATM_STORE_TAUX( bi,bj,
8       I                           myCurrentTime,       I                           myTime,
9       I                           myCurrentIter,       I                           myIter,
10       I                           myThid )       I                           myThid )
11  C     /==========================================================\  C     /==========================================================\
12  C     | SUBROUTINE ATM_STORE_TAUX                                |  C     | SUBROUTINE ATM_STORE_TAUX                                |
# Line 25  C     == Global variables == Line 25  C     == Global variables ==
25  #include "GRID.h"  #include "GRID.h"
26  #include "DYNVARS.h"  #include "DYNVARS.h"
27  #include "AIM2DYN.h"  #include "AIM2DYN.h"
28    c #include "AIM_FFIELDS.h"
29    #ifdef ALLOW_THSICE
30    # include "THSICE_PARAMS.h"
31    # include "THSICE_VARS.h"
32    #endif
33  C     == Global variables for coupling interface ==  C     == Global variables for coupling interface ==
34  #include "ATMCPL.h"  #include "ATMCPL.h"
 C     == AIMPHYS specific global data ==  
 #include "com_physvar.h"  
35    
36    
37  C     == Routine arguments ==  C     == Routine arguments ==
38  C     bi,bj         - Tile index  C     bi,bj  - Tile index
39  C     myThid        - Thread number for this instance of the routine  C     myThid - Thread number for this instance of the routine
40  C     myCurrentIter - Current timestep number  C     myIter - Current timestep number
41  C     myCurrentTime - Current model time  C     myTime - Current model time
42        INTEGER bi, bj        INTEGER bi, bj
43        _RL     myCurrentTime        _RL     myTime
44        INTEGER myCurrentIter        INTEGER myIter
45        INTEGER myThid        INTEGER myThid
46  CEndOfInterface  CEndOfInterface
47    
48    #ifdef COMPONENT_MODULE
49  C     == Local variables ==  C     == Local variables ==
50  C     I,J,kLev,II - Loop counters  C     i,j,k - Loop counters
51        INTEGER I,J,kLev,II        INTEGER i,j,k
52        _RL uStr_tmp        _RL uStr_tmp
53        _RL cplTimeFraction        _RL cplTimeFraction
54    
55  C     o Accumulate zonal momentum flux that will be exported to the  C     o Accumulate zonal momentum flux that will be exported to the
56  C       coupling layer. Momentum flux is in N/m^2 with same sign as the  C       coupling layer. Momentum flux is in N/m^2 with same sign as the
57  C       wind. Momentum flux is in COMMON /FLUXES/, com_physvar.h.  C       wind. Momentum flux is in COMMON /FLUXES/, com_physvar.h.
58        cplTimeFraction = 1. _d 0 / DFLOAT(cplSendFrq_iter)         cplTimeFraction = 1. _d 0 / DFLOAT(cplSendFrq_iter)
59        kLev=1         k = 1
60  c     DO bj=myByLo(myThid),myByHi(myThid)         tauXTime(bi,bj) = tauXTime(bi,bj) + cplTimeFraction
61  c      DO bi=myBxLo(myThid),myBxHi(myThid)  #ifdef ALLOW_THSICE
62          tauXTime(bi,bj) = tauXTime(bi,bj) + cplTimeFraction        IF ( useThSIce .AND. stressReduction.GT. 0. _d 0 ) THEN
63          DO J=1,sNy  C--   Reduce wind stress applied to ocean where sea-ice is present
64           DO I=1,sNx         DO j=1,sNy
65            IF ( hFacW(i,j,kLev,bi,bj) .NE. 0. ) THEN           DO i=1,sNx
66    c         IF ( aim_landFr(i-1,j,bi,bj)*aim_landFr(i,j,bi,bj) .NE. 1. ) THEN
67              IF ( hFacW(i,j,k,bi,bj) .NE. 0. ) THEN
68               uStr_tmp =
69         &      ( aim_drag(i-1,j,bi,bj)
70         &       *(1. _d 0 - iceMask(i-1,j,bi,bj)*stressReduction)
71         &      + aim_drag( i ,j,bi,bj)
72         &       *(1. _d 0 - iceMask( i ,j,bi,bj)*stressReduction)
73         &      )* 0.5 _d 0 * uVel(i,j,k,bi,bj)
74               tauX(i,j,bi,bj) = tauX(i,j,bi,bj)
75         &                     + uStr_tmp*cplTimeFraction
76              ENDIF
77             ENDDO
78           ENDDO
79          ELSE
80    #else  /*ALLOW_THSICE*/
81          IF (.TRUE.) THEN
82    #endif  /*ALLOW_THSICE*/
83           DO j=1,sNy
84             DO i=1,sNx
85    c         IF ( aim_landFr(i-1,j,bi,bj)*aim_landFr(i,j,bi,bj) .NE. 1. ) THEN
86              IF ( hFacW(i,j,k,bi,bj) .NE. 0. ) THEN
87             uStr_tmp =             uStr_tmp =
88       &      ( aim_drag(i-1,j,bi,bj)+aim_drag(i,j,bi,bj) )       &      ( aim_drag(i-1,j,bi,bj)+aim_drag(i,j,bi,bj) )
89       &       * 0.5 _d 0 * uVel(i,j,kLev,bi,bj)       &       * 0.5 _d 0 * uVel(i,j,k,bi,bj)
90             tauX(I,J,bi,bj) =             tauX(i,j,bi,bj) = tauX(i,j,bi,bj)
91       &     tauX(I,J,bi,bj) + uStr_tmp*cplTimeFraction       &                     + uStr_tmp*cplTimeFraction
92            ENDIF            ENDIF
93           ENDDO           ENDDO
94          ENDDO         ENDDO
95  c      ENDDO        ENDIF
96  c     ENDDO  
97    #endif /* COMPONENT_MODULE */
98    
99        RETURN        RETURN
100        END        END

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.2

  ViewVC Help
Powered by ViewVC 1.1.22