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

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

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

revision 1.2 by jmc, Thu May 31 15:19:49 2007 UTC revision 1.3 by jmc, Tue Apr 23 16:34:24 2013 UTC
# Line 10  CBOP Line 10  CBOP
10  C     !ROUTINE: THSICE_GET_PRECIP  C     !ROUTINE: THSICE_GET_PRECIP
11  C     !INTERFACE:  C     !INTERFACE:
12        SUBROUTINE THSICE_GET_PRECIP(        SUBROUTINE THSICE_GET_PRECIP(
13       I                  iceMsk,       I                  iceMsk, locSST,
14       O                  precip, snowPrc, flxSW,       O                  precip, snowPrc, qPrcRnO, flxSW,
15       I                  iMin,iMax,jMin,jMax, bi,bj, myThid )       I                  iMin,iMax,jMin,jMax, bi,bj, myThid )
16  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
17  C     *==========================================================*  C     *==========================================================*
# Line 29  C     !USES: Line 29  C     !USES:
29  C     == Global data ==  C     == Global data ==
30  #include "SIZE.h"  #include "SIZE.h"
31  #include "EEPARAMS.h"  #include "EEPARAMS.h"
32    #include "PARAMS.h"
33  #ifdef ALLOW_BULK_FORCE  #ifdef ALLOW_BULK_FORCE
34  #include "BULKF_PARAMS.h"  #include "BULKF_PARAMS.h"
35  #include "BULKF.h"  #include "BULKF.h"
# Line 37  C     == Global data == Line 38  C     == Global data ==
38  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
39  C     === Routine arguments ===  C     === Routine arguments ===
40  C     iceMsk    :: sea-ice fraction: no ice=0, grid all ice 1  []  C     iceMsk    :: sea-ice fraction: no ice=0, grid all ice 1  []
41    C     locSST    :: local Sea-Surface Temperature [deg.C]
42  C     precip    :: Total Precipitation (including run-off) [kg/m2/s]  C     precip    :: Total Precipitation (including run-off) [kg/m2/s]
43  C     snowPrc   :: Snow Precipitation [kg/m2/s]  C     snowPrc   :: Snow Precipitation [kg/m2/s]
44    C     qPrcRnO   :: Energy content of Precip+RunOff (+=down) [W/m2]
45  C     flxSW     :: Downward short-wave surface flux (+=down) [W/m2]  C     flxSW     :: Downward short-wave surface flux (+=down) [W/m2]
46  C     iMin,iMax :: range of indices of computation domain  C     iMin,iMax :: range of indices of computation domain
47  C     jMin,jMax :: range of indices of computation domain  C     jMin,jMax :: range of indices of computation domain
48  C     bi,bj     :: current tile indices  C     bi,bj     :: current tile indices
49  C     myThid      :: Thread no. that called this routine.  C     myThid      :: Thread no. that called this routine.
50        _RL iceMsk (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)        _RL iceMsk (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
51          _RL locSST (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
52        _RL precip (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL precip (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
53        _RL snowPrc(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL snowPrc(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
54          _RL qPrcRnO(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
55        _RL flxSW  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL flxSW  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56        INTEGER iMin,iMax        INTEGER iMin,iMax
57        INTEGER jMin,jMax        INTEGER jMin,jMax
# Line 64  C     i,j   :: current grid point indice Line 69  C     i,j   :: current grid point indice
69    
70        DO j = jMin, jMax        DO j = jMin, jMax
71          DO i = iMin, iMax          DO i = iMin, iMax
72             precip(i,j) = ( rain(i,j,bi,bj)+runoff(i,j,bi,bj) )*rhofw            precip(i,j) = ( rain(i,j,bi,bj)+runoff(i,j,bi,bj) )*rhofw
73             flxSW (i,j) = solar(i,j,bi,bj)            flxSW (i,j) = solar(i,j,bi,bj)
            IF ( iceMsk(i,j,bi,bj).GT.0. _d 0  
      &       .AND. Tair(i,j,bi,bj).LE.Tf0kel )  THEN  
              snowPrc(i,j) = rain(i,j,bi,bj)*rhofw  
            ENDIF  
74          ENDDO          ENDDO
75        ENDDO        ENDDO
76    
77    c     IF ( SnowFile .NE. ' ' ) THEN
78    c     ELSE
79    C     If specific snow precipitiation is not available, use
80    C     precipitation when ever the air temperature is below 0 degC
81            DO j = jMin, jMax
82             DO i = iMin, iMax
83              IF ( iceMsk(i,j,bi,bj).GT.0. _d 0
84         &      .AND. Tair(i,j,bi,bj).LE.Tf0kel )  THEN
85                 snowPrc(i,j) = rain(i,j,bi,bj)*rhofw
86              ENDIF
87             ENDDO
88            ENDDO
89    c     ENDIF
90    
91          IF ( temp_EvPrRn .NE. UNSET_RL ) THEN
92    C--   Account for energy content of Precip + RunOff :
93    C     assume 1) rain has same temp as Air (higher altitude, e.g., 850.mb would
94    C      be better); 2) Snow has no heat capacity (+ is counted separately)
95    C     3) no distinction between sea-water Cp and fresh-water Cp
96    C     4) Run-Off comes at the temp of surface water (with same Cp)
97           DO j = jMin, jMax
98            DO i = iMin, iMax
99             qPrcRnO(i,j) = HeatCapacity_Cp*(
100         &           ( Tair(i,j,bi,bj) - Tf0kel - temp_EvPrRn )
101         &          *( rain(i,j,bi,bj)*rhofw - snowPrc(i,j) )
102         &         + ( locSST(i,j,bi,bj) - temp_EvPrRn )
103         &          *runoff(i,j,bi,bj)*rhofw )
104            ENDDO
105           ENDDO
106          ENDIF
107    
108  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
109    
110  #endif /* ALLOW_BULK_FORCE */  #endif /* ALLOW_BULK_FORCE */

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

  ViewVC Help
Powered by ViewVC 1.1.22