Back to home page

MITgcm

 
 

    


File indexing completed on 2023-02-03 06:10:34 UTC

view on githubraw file Latest commit edb66560 on 2023-02-02 23:32:31 UTC
a4eca6e929 Jean*0001 #include "THSICE_OPTIONS.h"
6b47d550f4 Mart*0002 #ifdef ALLOW_AUTODIFF
                0003 # include "AUTODIFF_OPTIONS.h"
                0004 #endif
a4eca6e929 Jean*0005 
                0006 CBOP
                0007 C     !ROUTINE: THSICE_DO_ADVECT
                0008 C     !INTERFACE:
                0009       SUBROUTINE THSICE_DO_ADVECT(
28f449a461 Jean*0010      I                  biArg, bjArg, myTime, myIter, myThid )
a4eca6e929 Jean*0011 
                0012 C     !DESCRIPTION: \bv
                0013 C     *==========================================================*
                0014 C     | SUBROUTINE THSICE_DO_ADVECT
                0015 C     | o wraper for pkg/thSIce advection-diffusion calls
                0016 C     *==========================================================*
                0017 C     \ev
                0018 C     !USES:
                0019       IMPLICIT NONE
                0020 
                0021 C     === Global variables ===
                0022 #include "SIZE.h"
                0023 #include "EEPARAMS.h"
                0024 #include "PARAMS.h"
28f449a461 Jean*0025 #include "FFIELDS.h"
                0026 #include "THSICE_SIZE.h"
a4eca6e929 Jean*0027 #include "THSICE_PARAMS.h"
28f449a461 Jean*0028 #include "THSICE_VARS.h"
4ce71c0bf5 Jean*0029 #ifdef ALLOW_AUTODIFF_TAMC
                0030 # include "tamc.h"
                0031 #endif
a4eca6e929 Jean*0032 
                0033 C     !INPUT/OUTPUT PARAMETERS:
                0034 C     === Routine arguments ===
28f449a461 Jean*0035 C     biArg     :: Tile 1rst index argument
                0036 C     bjArg     :: Tile 2nd  index argument
a4eca6e929 Jean*0037 C     myTime    :: Current time in simulation (s)
                0038 C     myIter    :: Current iteration number
                0039 C     myThid    :: My Thread Id. number
28f449a461 Jean*0040       INTEGER biArg, bjArg
a4eca6e929 Jean*0041       _RL     myTime
                0042       INTEGER myIter
                0043       INTEGER myThid
                0044 CEOP
                0045 
                0046 C     !LOCAL VARIABLES:
                0047 C     === Local variables ===
28f449a461 Jean*0048 C     bi, bj    :: Tile indices
a4eca6e929 Jean*0049 C     uIce/vIce :: ice velocity on C-grid [m/s]
28f449a461 Jean*0050       INTEGER bi, bj
                0051       INTEGER i, j
                0052       INTEGER iMin, iMax, jMin, jMax
7c50f07931 Mart*0053 #ifdef ALLOW_AUTODIFF_TAMC
edb6656069 Mart*0054 C     tkey :: tape key (depends on tiles)
                0055       INTEGER tkey
7c50f07931 Mart*0056 #endif
a4eca6e929 Jean*0057       _RL  uIce(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
                0058       _RL  vIce(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
                0059 
28f449a461 Jean*0060       IF ( thSIceAdvScheme.GT.0 .AND. biArg.EQ.0 .AND. bjArg.EQ.0 ) THEN
                0061 c      iMin = 1
                0062 c      iMax = sNx
                0063 c      jMin = 1
                0064 c      jMax = sNy
                0065        iMin = 1-OLx
                0066        iMax = sNx+OLx-1
                0067        jMin = 1-OLy
                0068        jMax = sNy+OLy-1
                0069        DO bj = myByLo(myThid), myByHi(myThid)
                0070         DO bi = myBxLo(myThid), myBxHi(myThid)
68ae87c30f Patr*0071 #ifdef ALLOW_AUTODIFF_TAMC
edb6656069 Mart*0072          tkey = bi + (bj-1)*nSx + (ikey_dynamics-1)*nSx*nSy
68ae87c30f Patr*0073 #endif /* ALLOW_AUTODIFF_TAMC */
                0074 
28f449a461 Jean*0075          CALL THSICE_GET_VELOCITY(
                0076      O                        uIce, vIce,
                0077      I                        bi,bj, myTime, myIter, myThid )
68ae87c30f Patr*0078 #ifdef ALLOW_AUTODIFF_TAMC
edb6656069 Mart*0079 CADJ STORE icemask(:,:,bi,bj) = comlev1_bibj, key=tkey, byte=isbyte
                0080 CADJ STORE qice1(:,:,bi,bj)   = comlev1_bibj, key=tkey, byte=isbyte
                0081 CADJ STORE hOceMxL(:,:,bi,bj) = comlev1_bibj, key=tkey, byte=isbyte
68ae87c30f Patr*0082 #endif
28f449a461 Jean*0083          CALL THSICE_ADVDIFF(
                0084      U                        uIce, vIce,
                0085      I                        bi,bj, myTime, myIter, myThid )
68ae87c30f Patr*0086 #ifdef ALLOW_AUTODIFF_TAMC
edb6656069 Mart*0087 CADJ STORE hOceMxL(:,:,bi,bj)    = comlev1_bibj, key=tkey, byte=isbyte
                0088 CADJ STORE snowHeight(:,:,bi,bj) = comlev1_bibj, key=tkey, byte=isbyte
                0089 CADJ STORE iceHeight(:,:,bi,bj)  = comlev1_bibj, key=tkey, byte=isbyte
                0090 CADJ STORE iceMask(:,:,bi,bj)    = comlev1_bibj, key=tkey, byte=isbyte
68ae87c30f Patr*0091 #endif
28f449a461 Jean*0092          DO j = jMin, jMax
                0093           DO i = iMin, iMax
                0094            IF ( hOceMxL(i,j,bi,bj).GT.0. _d 0 ) THEN
                0095             Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj) - oceQnet(i,j,bi,bj)
                0096             EmPmR(i,j,bi,bj)= EmPmR(i,j,bi,bj)- oceFWfx(i,j,bi,bj)
                0097             saltFlux(i,j,bi,bj)=saltFlux(i,j,bi,bj) - oceSflx(i,j,bi,bj)
                0098            ENDIF
                0099 C--     Compute Sea-Ice Loading (= mass of sea-ice + snow / area unit)
                0100            sIceLoad(i,j,bi,bj) = ( snowHeight(i,j,bi,bj)*rhos
                0101      &                           + iceHeight(i,j,bi,bj)*rhoi
                0102      &                           )*iceMask(i,j,bi,bj)
                0103           ENDDO
                0104          ENDDO
                0105 
c9573f2063 Jean*0106 C--     cumulate time-averaged fields and also fill-up flux diagnostics
                0107          CALL THSICE_AVE(
                0108      I                     bi,bj, myTime, myIter, myThid )
                0109 
28f449a461 Jean*0110         ENDDO
                0111        ENDDO
                0112 
                0113        IF ( stressReduction.GT. 0. _d 0 )
                0114      &   _EXCH_XY_RL( iceMask, myThid )
                0115        IF ( useRealFreshWaterFlux )
                0116      &  _EXCH_XY_RS( sIceLoad, myThid )
                0117 
                0118 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0119 
a4eca6e929 Jean*0120       ENDIF
                0121 
                0122       RETURN
                0123       END