Back to home page

MITgcm

 
 

    


File indexing completed on 2021-04-08 05:12:35 UTC

view on githubraw file Latest commit ba0b0470 on 2021-04-08 01:06:32 UTC
1ce64188ac Jean*0001 #include "TIMEAVE_OPTIONS.h"
                0002 
                0003       SUBROUTINE TIMEAVE_SURF_FLUX(
82b0aed211 Jean*0004      I     bi, bj, myTime, myIter, myThid )
1ce64188ac Jean*0005 C     *==========================================================*
                0006 C     | SUBROUTINE TIMEAVE_SURF_FLUX                             |
                0007 C     | o Time averaging routine for surface (forcing) fluxes    |
                0008 C     *==========================================================*
                0009       IMPLICIT NONE
                0010 
                0011 C     == Global variables ===
                0012 #include "SIZE.h"
                0013 #include "EEPARAMS.h"
                0014 #include "PARAMS.h"
                0015 #include "GRID.h"
                0016 #include "DYNVARS.h"
                0017 #include "SURFACE.h"
                0018 #include "FFIELDS.h"
                0019 #include "TIMEAVE_STATV.h"
                0020 
                0021 C     == Routine arguments ==
                0022 C     bi, bj :: current tile indices
                0023 C     myTime :: Current time of simulation ( s )
                0024 C     myIter :: Iteration number
                0025 C     myThid :: Thread number for this instance of the routine.
                0026       INTEGER bi, bj
                0027       _RL     myTime
                0028       INTEGER myIter
                0029       INTEGER myThid
                0030 
                0031 #ifdef ALLOW_TIMEAVE
                0032 
                0033 C     == Local variables ==
                0034       INTEGER I, J, K
                0035       _RL tmpFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
96af7ef6da Jean*0036 
1ce64188ac Jean*0037 C-    Time Averages of surface fluxes
9669509dca Jean*0038        IF ( usingPCoords ) THEN
1ce64188ac Jean*0039         k=Nr
                0040        ELSE
                0041         k=1
                0042        ENDIF
                0043 
                0044 C-    uFlux (surface momentum flux [Pa=N/m2], positive <-> increase u)
96af7ef6da Jean*0045        DO j=1,sNy
                0046         DO i=1,sNx
                0047          tmpFld(i,j)=fu(i,j,bi,bj)*foFacMom*_maskW(i,j,k,bi,bj)
                0048         ENDDO
                0049        ENDDO
                0050        CALL TIMEAVE_CUMUL_1T(uFluxtave,tmpFld,1,
16fe9e8e73 Jean*0051      &                                   deltaTClock, bi, bj, myThid)
1ce64188ac Jean*0052 
                0053 C-    vFlux (surface momentum flux [Pa=N/m2], positive <-> increase v)
96af7ef6da Jean*0054        DO j=1,sNy
                0055         DO i=1,sNx
                0056          tmpFld(i,j)=fv(i,j,bi,bj)*foFacMom*_maskS(i,j,k,bi,bj)
                0057         ENDDO
                0058        ENDDO
                0059        CALL TIMEAVE_CUMUL_1T(vFluxtave,tmpFld,1,
16fe9e8e73 Jean*0060      &                                   deltaTClock, bi, bj, myThid)
1ce64188ac Jean*0061 
                0062 C     tFlux (=Heat flux [W/m2], positive <-> increasing Theta)
                0063        DO j=1,sNy
                0064         DO i=1,sNx
                0065          tmpFld(i,j) =
                0066 #ifdef SHORTWAVE_HEATING
                0067      &    -Qsw(i,j,bi,bj)+
                0068 #endif
16fe9e8e73 Jean*0069      &    (surfaceForcingT(i,j,bi,bj)+adjustColdSST_diag(I,J,bi,bj))
0b1017b546 Jean*0070      &    *HeatCapacity_Cp*rUnit2mass
1ce64188ac Jean*0071         ENDDO
                0072        ENDDO
                0073 #ifdef NONLIN_FRSURF
9669509dca Jean*0074        IF ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
1ce64188ac Jean*0075      &     .AND. useRealFreshWaterFlux ) THEN
                0076         DO j=1,sNy
                0077          DO i=1,sNx
96af7ef6da Jean*0078            tmpFld(i,j) = tmpFld(i,j)
82b0aed211 Jean*0079      &      + PmEpR(i,j,bi,bj)*theta(i,j,k,bi,bj)*HeatCapacity_Cp
1ce64188ac Jean*0080          ENDDO
                0081         ENDDO
                0082        ENDIF
                0083 #endif /* NONLIN_FRSURF */
                0084        CALL TIMEAVE_CUMUL_1T( tFluxtave, tmpFld, 1,
16fe9e8e73 Jean*0085      &                                   deltaTClock, bi, bj, myThid)
1ce64188ac Jean*0086 
ba0b047096 Mart*0087 C     sFlux (=salt flux [g/m2/s], positive <-> increasing salinity)
1ce64188ac Jean*0088        DO j=1,sNy
                0089         DO i=1,sNx
                0090          tmpFld(i,j)=
0b1017b546 Jean*0091      &    surfaceForcingS(i,j,bi,bj)*rUnit2mass
1ce64188ac Jean*0092         ENDDO
                0093        ENDDO
                0094 #ifdef NONLIN_FRSURF
9669509dca Jean*0095        IF ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
1ce64188ac Jean*0096      &     .AND. useRealFreshWaterFlux ) THEN
                0097         DO j=1,sNy
                0098          DO i=1,sNx
96af7ef6da Jean*0099            tmpFld(i,j) = tmpFld(i,j)
82b0aed211 Jean*0100      &      + PmEpR(i,j,bi,bj)*salt(i,j,k,bi,bj)
1ce64188ac Jean*0101          ENDDO
                0102         ENDDO
                0103        ENDIF
                0104 #endif /* NONLIN_FRSURF */
                0105        CALL TIMEAVE_CUMUL_1T( sFluxtave, tmpFld, 1,
16fe9e8e73 Jean*0106      &                                   deltaTClock, bi, bj, myThid)
1ce64188ac Jean*0107 
96af7ef6da Jean*0108 #endif /* ALLOW_TIMEAVE */
1ce64188ac Jean*0109 
                0110       RETURN
                0111       END