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

Contents of /MITgcm/pkg/thsice/thsice_map_exf.F

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


Revision 1.4 - (show annotations) (download)
Fri May 18 02:45:43 2007 UTC (17 years ago) by jmc
Branch: MAIN
Changes since 1.3: +4 -2 lines
remove ALLOW_SEAICE from exf pkg files

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_map_exf.F,v 1.3 2007/04/27 15:51:28 jmc Exp $
2 C $Name: $
3
4 #include "THSICE_OPTIONS.h"
5 #ifdef ALLOW_EXF
6 #include "EXF_OPTIONS.h"
7 #endif
8
9 CBOP
10 C !ROUTINE: THSICE_MAP_EXF
11 C !INTERFACE:
12 SUBROUTINE THSICE_MAP_EXF(
13 I iceMsk,
14 O totPrc, snowPrc, flxSW,
15 I iMin,iMax,jMin,jMax, bi,bj, myThid )
16 C !DESCRIPTION: \bv
17 C *==========================================================*
18 C | S/R THSICE_MAP_EXF
19 C | Interface S/R : map Precip, Snow and shortwave fluxes
20 C | from pkg EXF to thsice variables
21 C *==========================================================*
22 C \ev
23
24 C !USES:
25 IMPLICIT NONE
26
27 C == Global data ==
28 #include "SIZE.h"
29 #include "EEPARAMS.h"
30 #include "PARAMS.h"
31 #include "FFIELDS.h"
32 #ifdef ALLOW_EXF
33 # include "EXF_CONSTANTS.h"
34 # include "EXF_PARAM.h"
35 # include "EXF_FIELDS.h"
36 #endif
37
38 C !INPUT/OUTPUT PARAMETERS:
39 C === Routine arguments ===
40 C iceMsk :: sea-ice fraction: no ice=0, grid all ice 1 []
41 C totPrc :: Total Precipitation (including run-off) [kg/m2/s]
42 C snowPrc :: Snow Precipitation [kg/m2/s]
43 C flxSW :: Net short-wave surface flux (+=down) [W/m2]
44 C iMin,iMax :: range of indices of computation domain
45 C jMin,jMax :: range of indices of computation domain
46 C bi,bj :: current tile indices
47 C myThid :: Thread no. that called this routine.
48 _RL iceMsk (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
49 _RL totPrc (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
50 _RL snowPrc(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
51 _RL flxSW (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
52 INTEGER iMin,iMax
53 INTEGER jMin,jMax
54 INTEGER bi,bj
55 INTEGER myThid
56 CEOP
57
58 #ifdef ALLOW_EXF
59
60 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
61 C === Local variables ===
62 C i,j :: current grid point indices
63 INTEGER i,j
64
65 DO j = jMin, jMax
66 DO i = iMin, iMax
67 #ifdef ALLOW_ATM_TEMP
68 totPrc(i,j) = precip(i,j,bi,bj)*rhoConstFresh
69 #endif
70 #ifdef ALLOW_RUNOFF
71 totPrc(i,j) = totPrc(i,j) + runoff(i,j,bi,bj)*rhoConstFresh
72 #else
73 STOP 'ABNORMAL END: S/R THSICE_MAP_EXF: ALLOW_RUNOFF undef'
74 #endif
75 CML flxSW (i,j) = -Qsw(i,j,bi,bj)
76 #ifdef ALLOW_DOWNWARD_RADIATION
77 flxSW (i,j) = swdown(i,j,bi,bj)
78 #else
79 STOP 'ABNORMAL END: S/R THSICE_MAP_EXF: DOWNWARD_RADIATION undef'
80 #endif
81 ENDDO
82 ENDDO
83
84 #ifdef ALLOW_ATM_TEMP
85 IF ( snowPrecipFile .NE. ' ' ) THEN
86 DO j = jMin, jMax
87 DO i = iMin, iMax
88 snowPrc(i,j) = snowPrecip(i,j,bi,bj)*rhoConstFresh
89 ENDDO
90 ENDDO
91 ELSE
92 C If specific snow precipitiation is now available, use
93 C precipitation when ever the air temperature is below 0 degC
94 DO j = jMin, jMax
95 DO i = iMin, iMax
96 IF ( iceMsk(i,j,bi,bj).GT.0. _d 0
97 & .AND. atemp(i,j,bi,bj).LE.cen2kel ) THEN
98 CML & .AND. atemp(i,j,bi,bj).LE.Tf0kel ) THEN
99 snowPrc(i,j) = precip(i,j,bi,bj)*rhoConstFresh
100 ENDIF
101 ENDDO
102 ENDDO
103 ENDIF
104 #else /* ALLOW_ATM_TEMP */
105 STOP 'ABNORMAL END: S/R THSICE_MAP_EXF: ATM_TEMP undef'
106 #endif /* ALLOW_ATM_TEMP */
107
108 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
109
110 #endif /* ALLOW_EXF */
111
112 RETURN
113 END

  ViewVC Help
Powered by ViewVC 1.1.22