/[MITgcm]/MITgcm/pkg/thsice/thsice_do_advect.F
ViewVC logotype

Diff of /MITgcm/pkg/thsice/thsice_do_advect.F

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

revision 1.1 by jmc, Wed Apr 4 02:40:42 2007 UTC revision 1.2 by jmc, Mon Jan 21 22:58:06 2013 UTC
# Line 7  CBOP Line 7  CBOP
7  C     !ROUTINE: THSICE_DO_ADVECT  C     !ROUTINE: THSICE_DO_ADVECT
8  C     !INTERFACE:  C     !INTERFACE:
9        SUBROUTINE THSICE_DO_ADVECT(        SUBROUTINE THSICE_DO_ADVECT(
10       I                     bi, bj, myTime, myIter, myThid )       I                  biArg, bjArg, myTime, myIter, myThid )
11    
12  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
13  C     *==========================================================*  C     *==========================================================*
# Line 22  C     === Global variables === Line 22  C     === Global variables ===
22  #include "SIZE.h"  #include "SIZE.h"
23  #include "EEPARAMS.h"  #include "EEPARAMS.h"
24  #include "PARAMS.h"  #include "PARAMS.h"
25    #include "FFIELDS.h"
26    #include "THSICE_SIZE.h"
27  #include "THSICE_PARAMS.h"  #include "THSICE_PARAMS.h"
28    #include "THSICE_VARS.h"
29    
30  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
31  C     === Routine arguments ===  C     === Routine arguments ===
32  C     bi,bj     :: Tile indices  C     biArg     :: Tile 1rst index argument
33    C     bjArg     :: Tile 2nd  index argument
34  C     myTime    :: Current time in simulation (s)  C     myTime    :: Current time in simulation (s)
35  C     myIter    :: Current iteration number  C     myIter    :: Current iteration number
36  C     myThid    :: My Thread Id. number  C     myThid    :: My Thread Id. number
37        INTEGER bi,bj        INTEGER biArg, bjArg
38        _RL     myTime        _RL     myTime
39        INTEGER myIter        INTEGER myIter
40        INTEGER myThid        INTEGER myThid
# Line 38  CEOP Line 42  CEOP
42    
43  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
44  C     === Local variables ===  C     === Local variables ===
45    C     bi, bj    :: Tile indices
46  C     uIce/vIce :: ice velocity on C-grid [m/s]  C     uIce/vIce :: ice velocity on C-grid [m/s]
47          INTEGER bi, bj
48    #ifndef OLD_THSICE_CALL_SEQUENCE
49          INTEGER i, j
50          INTEGER iMin, iMax, jMin, jMax
51    #endif
52        _RL  uIce(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL  uIce(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
53        _RL  vIce(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL  vIce(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
54    
55        IF ( thSIceAdvScheme.GT.0 ) THEN        IF ( thSIceAdvScheme.GT.0 .AND. biArg.EQ.0 .AND. bjArg.EQ.0 ) THEN
56    #ifndef OLD_THSICE_CALL_SEQUENCE
57    c      iMin = 1
58    c      iMax = sNx
59    c      jMin = 1
60    c      jMax = sNy
61           iMin = 1-OLx
62           iMax = sNx+OLx-1
63           jMin = 1-OLy
64           jMax = sNy+OLy-1
65           DO bj = myByLo(myThid), myByHi(myThid)
66            DO bi = myBxLo(myThid), myBxHi(myThid)
67             CALL THSICE_GET_VELOCITY(
68         O                        uIce, vIce,
69         I                        bi,bj, myTime, myIter, myThid )
70             CALL THSICE_ADVDIFF(
71         U                        uIce, vIce,
72         I                        bi,bj, myTime, myIter, myThid )
73             DO j = jMin, jMax
74              DO i = iMin, iMax
75               IF ( hOceMxL(i,j,bi,bj).GT.0. _d 0 ) THEN
76                Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj) - oceQnet(i,j,bi,bj)
77                EmPmR(i,j,bi,bj)= EmPmR(i,j,bi,bj)- oceFWfx(i,j,bi,bj)
78                saltFlux(i,j,bi,bj)=saltFlux(i,j,bi,bj) - oceSflx(i,j,bi,bj)
79               ENDIF
80    C--     Compute Sea-Ice Loading (= mass of sea-ice + snow / area unit)
81               sIceLoad(i,j,bi,bj) = ( snowHeight(i,j,bi,bj)*rhos
82         &                           + iceHeight(i,j,bi,bj)*rhoi
83         &                           )*iceMask(i,j,bi,bj)
84              ENDDO
85             ENDDO
86    
87            ENDDO
88           ENDDO
89    
90           IF ( stressReduction.GT. 0. _d 0 )
91         &   _EXCH_XY_RL( iceMask, myThid )
92    #ifdef ATMOSPHERIC_LOADING
93           IF ( useRealFreshWaterFlux )
94         &  _EXCH_XY_RS( sIceLoad, myThid )
95    #endif
96    #endif /* ndef OLD_THSICE_CALL_SEQUENCE */
97    
98    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
99    
100          ELSEIF ( thSIceAdvScheme.GT.0 ) THEN
101             bi = biArg
102             bj = bjArg
103           CALL THSICE_GET_VELOCITY(           CALL THSICE_GET_VELOCITY(
104       O                        uIce, vIce,       O                        uIce, vIce,
105       I                        bi,bj, myTime, myIter, myThid )       I                        bi,bj, myTime, myIter, myThid )

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

  ViewVC Help
Powered by ViewVC 1.1.22