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

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

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


Revision 1.4 - (hide annotations) (download)
Tue Jun 11 01:48:22 2013 UTC (10 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.3: +76 -18 lines
allow precip from pkg/cheapaml to make snow over seaice

1 jmc 1.4 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_get_precip.F,v 1.3 2013/04/23 16:34:24 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "THSICE_OPTIONS.h"
5     #ifdef ALLOW_BULK_FORCE
6 jmc 1.4 # include "BULK_FORCE_OPTIONS.h"
7     #endif
8     #ifdef ALLOW_CHEAPAML
9     # include "CHEAPAML_OPTIONS.h"
10 jmc 1.1 #endif
11    
12     CBOP
13     C !ROUTINE: THSICE_GET_PRECIP
14     C !INTERFACE:
15     SUBROUTINE THSICE_GET_PRECIP(
16 jmc 1.3 I iceMsk, locSST,
17     O precip, snowPrc, qPrcRnO, flxSW,
18 jmc 1.1 I iMin,iMax,jMin,jMax, bi,bj, myThid )
19     C !DESCRIPTION: \bv
20     C *==========================================================*
21     C | S/R THSICE_GET_PRECIP
22 jmc 1.2 C | Interface S/R : get Precip, Snow-precip
23 jmc 1.4 C | and downward short-wave from pkg BULK_FORCE
24     C | - or - get Precip, Snow-precip from pkg cheapAML
25 jmc 1.1 C *==========================================================*
26     C \ev
27    
28     C !USES:
29     IMPLICIT NONE
30    
31     C == Global data ==
32     #include "SIZE.h"
33     #include "EEPARAMS.h"
34 jmc 1.3 #include "PARAMS.h"
35 jmc 1.1 #ifdef ALLOW_BULK_FORCE
36 jmc 1.4 # include "BULKF_PARAMS.h"
37     # include "BULKF.h"
38     #elif defined(ALLOW_CHEAPAML)
39     # include "CHEAPAML.h"
40 jmc 1.1 #endif
41    
42     C !INPUT/OUTPUT PARAMETERS:
43     C === Routine arguments ===
44     C iceMsk :: sea-ice fraction: no ice=0, grid all ice 1 []
45 jmc 1.3 C locSST :: local Sea-Surface Temperature [deg.C]
46 jmc 1.1 C precip :: Total Precipitation (including run-off) [kg/m2/s]
47     C snowPrc :: Snow Precipitation [kg/m2/s]
48 jmc 1.3 C qPrcRnO :: Energy content of Precip+RunOff (+=down) [W/m2]
49 jmc 1.2 C flxSW :: Downward short-wave surface flux (+=down) [W/m2]
50 jmc 1.1 C iMin,iMax :: range of indices of computation domain
51     C jMin,jMax :: range of indices of computation domain
52     C bi,bj :: current tile indices
53     C myThid :: Thread no. that called this routine.
54     _RL iceMsk (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
55 jmc 1.3 _RL locSST (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
56 jmc 1.1 _RL precip (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
57     _RL snowPrc(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
58 jmc 1.3 _RL qPrcRnO(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
59 jmc 1.1 _RL flxSW (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
60     INTEGER iMin,iMax
61     INTEGER jMin,jMax
62     INTEGER bi,bj
63     INTEGER myThid
64     CEOP
65    
66     #ifdef ALLOW_THSICE
67 jmc 1.4 #if defined(ALLOW_BULK_FORCE) || defined(ALLOW_CHEAPAML)
68 jmc 1.1
69     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
70     C === Local variables ===
71     C i,j :: current grid point indices
72     INTEGER i,j
73    
74 jmc 1.4 #ifdef ALLOW_BULK_FORCE
75     IF ( useBulkforce ) THEN
76    
77     DO j = jMin, jMax
78 jmc 1.1 DO i = iMin, iMax
79 jmc 1.3 precip(i,j) = ( rain(i,j,bi,bj)+runoff(i,j,bi,bj) )*rhofw
80     flxSW (i,j) = solar(i,j,bi,bj)
81     ENDDO
82 jmc 1.4 ENDDO
83 jmc 1.3
84 jmc 1.4 c IF ( SnowFile .NE. ' ' ) THEN
85     c ELSE
86 jmc 1.3 C If specific snow precipitiation is not available, use
87     C precipitation when ever the air temperature is below 0 degC
88     DO j = jMin, jMax
89     DO i = iMin, iMax
90     IF ( iceMsk(i,j,bi,bj).GT.0. _d 0
91     & .AND. Tair(i,j,bi,bj).LE.Tf0kel ) THEN
92 jmc 1.1 snowPrc(i,j) = rain(i,j,bi,bj)*rhofw
93 jmc 1.3 ENDIF
94     ENDDO
95 jmc 1.1 ENDDO
96 jmc 1.4 c ENDIF
97 jmc 1.3
98 jmc 1.4 IF ( temp_EvPrRn .NE. UNSET_RL ) THEN
99 jmc 1.3 C-- Account for energy content of Precip + RunOff :
100     C assume 1) rain has same temp as Air (higher altitude, e.g., 850.mb would
101     C be better); 2) Snow has no heat capacity (+ is counted separately)
102     C 3) no distinction between sea-water Cp and fresh-water Cp
103     C 4) Run-Off comes at the temp of surface water (with same Cp)
104 jmc 1.4 DO j = jMin, jMax
105     DO i = iMin, iMax
106     qPrcRnO(i,j) = HeatCapacity_Cp*(
107 jmc 1.3 & ( Tair(i,j,bi,bj) - Tf0kel - temp_EvPrRn )
108     & *( rain(i,j,bi,bj)*rhofw - snowPrc(i,j) )
109     & + ( locSST(i,j,bi,bj) - temp_EvPrRn )
110     & *runoff(i,j,bi,bj)*rhofw )
111 jmc 1.4 ENDDO
112     ENDDO
113     ENDIF
114    
115     C- end if useBulkforce
116     ENDIF
117    
118     IF ( useCheapAML )
119     & STOP 'cannot use thsIce and CheapAML with BULK_FORCE compiled'
120    
121     #elif defined(ALLOW_CHEAPAML)
122     IF ( useCheapAML ) THEN
123    
124     DO j = jMin, jMax
125     DO i = iMin, iMax
126     precip(i,j) = cheapPrecip(i,j,bi,bj)
127     c & + runoff(i,j,bi,bj)*rhofw
128 jmc 1.3 ENDDO
129     ENDDO
130 jmc 1.4
131     c IF ( SnowFile .NE. ' ' ) THEN
132     c ELSE
133     C If specific snow precipitiation is not available, use
134     C precipitation when ever the air temperature is below 0 degC
135     DO j = jMin, jMax
136     DO i = iMin, iMax
137     IF ( iceMsk(i,j,bi,bj).GT.0. _d 0
138     & .AND. Tair(i,j,bi,bj).LT.zeroRL ) THEN
139     snowPrc(i,j) = cheapPrecip(i,j,bi,bj)
140     ENDIF
141     ENDDO
142     ENDDO
143     c ENDIF
144    
145     IF ( temp_EvPrRn .NE. UNSET_RL ) THEN
146     C-- Account for energy content of Precip + RunOff :
147     C assume 1) rain has same temp as Air (higher altitude, e.g., 850.mb would
148     C be better); 2) Snow has no heat capacity (+ is counted separately)
149     C 3) no distinction between sea-water Cp and fresh-water Cp
150     DO j = jMin, jMax
151     DO i = iMin, iMax
152     qPrcRnO(i,j) = HeatCapacity_Cp*
153     & ( Tair(i,j,bi,bj) - temp_EvPrRn )
154     & *( cheapPrecip(i,j,bi,bj) - snowPrc(i,j) )
155     c + HeatCapacity_Cp*
156     c & ( locSST(i,j,bi,bj) - temp_EvPrRn )
157     c & *runoff(i,j,bi,bj)*rhofw
158     ENDDO
159     ENDDO
160     ENDIF
161    
162     C- end if useCheapAML
163 jmc 1.3 ENDIF
164 jmc 1.4 #endif /* if ALLOW_BULK_FORCE elif ALLOW_CHEAPAML */
165 jmc 1.1
166     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
167    
168 jmc 1.4 #endif /* ALLOW_BULK_FORCE or ALLOW_CHEAPAML */
169 jmc 1.1 #endif /* ALLOW_THSICE */
170    
171     RETURN
172     END

  ViewVC Help
Powered by ViewVC 1.1.22