/[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.6 - (show annotations) (download)
Fri Nov 7 20:43:16 2008 UTC (15 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint62, checkpoint63, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61f, checkpoint61g, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.5: +4 -4 lines
fix a comment

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_map_exf.F,v 1.5 2007/05/31 15:19:49 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 :: Downward 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 #ifdef ALLOW_DOWNWARD_RADIATION
76 flxSW (i,j) = swdown(i,j,bi,bj)
77 #else
78 STOP 'ABNORMAL END: S/R THSICE_MAP_EXF: DOWNWARD_RADIATION undef'
79 #endif
80 ENDDO
81 ENDDO
82
83 #ifdef ALLOW_ATM_TEMP
84 IF ( snowPrecipFile .NE. ' ' ) THEN
85 DO j = jMin, jMax
86 DO i = iMin, iMax
87 snowPrc(i,j) = snowPrecip(i,j,bi,bj)*rhoConstFresh
88 ENDDO
89 ENDDO
90 ELSE
91 C If specific snow precipitiation is not available, use
92 C precipitation when ever the air temperature is below 0 degC
93 DO j = jMin, jMax
94 DO i = iMin, iMax
95 IF ( iceMsk(i,j,bi,bj).GT.0. _d 0
96 & .AND. atemp(i,j,bi,bj).LE.cen2kel ) THEN
97 cML & .AND. atemp(i,j,bi,bj).LE.Tf0kel ) THEN
98 snowPrc(i,j) = precip(i,j,bi,bj)*rhoConstFresh
99 ENDIF
100 ENDDO
101 ENDDO
102 ENDIF
103 #else /* ALLOW_ATM_TEMP */
104 STOP 'ABNORMAL END: S/R THSICE_MAP_EXF: ATM_TEMP undef'
105 #endif /* ALLOW_ATM_TEMP */
106
107 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
108
109 #endif /* ALLOW_EXF */
110
111 RETURN
112 END

  ViewVC Help
Powered by ViewVC 1.1.22