/[MITgcm]/MITgcm/pkg/exf/exf_radiation.F
ViewVC logotype

Contents of /MITgcm/pkg/exf/exf_radiation.F

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


Revision 1.7 - (show annotations) (download)
Wed Apr 14 23:02:18 2010 UTC (14 years, 2 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.6: +3 -3 lines
improving readability of ALLOW_ZENITHANGLE related code
- remove nSx,nSy dims from zen_albedo_table
- rename useExfZenithAngle to useExfZenIncoming/useExfZenAlbedo
  and document them in EXF_PARAM.h
- document ALLOW_ZENITHANGLE in EXF_OPTIONS.h and set it to false
- document variables in EXF_FIELDS.h

1 C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_radiation.F,v 1.6 2010/04/13 06:57:34 gforget Exp $
2 C $Name: $
3
4 #include "EXF_OPTIONS.h"
5
6 SUBROUTINE EXF_RADIATION(myTime, myIter, myThid)
7
8 C ==================================================================
9 C SUBROUTINE exf_radiation
10 C ==================================================================
11 C
12 C o Set radiative fluxes at the surface.
13 C
14 C ==================================================================
15 C SUBROUTINE exf_radiation
16 C ==================================================================
17
18 IMPLICIT NONE
19
20 C == global variables ==
21
22 #include "EEPARAMS.h"
23 #include "SIZE.h"
24 #include "PARAMS.h"
25 #include "DYNVARS.h"
26 #include "GRID.h"
27
28 #include "EXF_PARAM.h"
29 #include "EXF_FIELDS.h"
30 #include "EXF_CONSTANTS.h"
31
32 C == routine arguments ==
33
34 _RL myTime
35 INTEGER myIter
36 INTEGER myThid
37
38 #ifdef ALLOW_DOWNWARD_RADIATION
39 C == local variables ==
40
41 INTEGER bi,bj
42 INTEGER i,j
43 #ifdef ALLOW_ATM_TEMP
44 INTEGER k
45 _RL Tsf, SSTtmp, TsfSq
46 #endif
47
48 C == end of interface ==
49
50 C-- Use atmospheric state to compute surface fluxes.
51
52 C-- Compute net from downward and downward from net longwave and
53 C shortwave radiation, IF needed.
54 C lwflux = Stefan-Boltzmann constant * emissivity * SST - lwdown
55 C swflux = - ( 1 - albedo ) * swdown
56
57 #ifdef ALLOW_ATM_TEMP
58 k = 1
59
60 IF ( lwfluxfile .EQ. ' ' .AND. lwdownfile .NE. ' ' ) THEN
61 C Loop over tiles.
62 DO bj = myByLo(myThid),myByHi(myThid)
63 DO bi = myBxLo(myThid),myBxHi(myThid)
64
65 IF ( sstExtrapol.GT.0. _d 0 ) THEN
66 DO j = 1,sNy
67 DO i = 1,sNx
68 Tsf = theta(i,j,1,bi,bj) + cen2kel
69 SSTtmp = sstExtrapol
70 & *( theta(i,j,1,bi,bj)-theta(i,j,2,bi,bj) )
71 & * maskC(i,j,2,bi,bj)
72 Tsf = Tsf + MAX( SSTtmp, 0. _d 0 )
73 TsfSq = Tsf*Tsf
74 lwflux(i,j,bi,bj) =
75 & ocean_emissivity*stefanBoltzmann*TsfSq*TsfSq
76 & - lwdown(i,j,bi,bj)
77 ENDDO
78 ENDDO
79 ELSE
80 DO j = 1,sNy
81 DO i = 1,sNx
82 lwflux(i,j,bi,bj) =
83 & ocean_emissivity*stefanBoltzmann*
84 & ((theta(i,j,k,bi,bj)+cen2kel)**4)
85 & - lwdown(i,j,bi,bj)
86 ENDDO
87 ENDDO
88 ENDIF
89
90 C-- end bi,bj loops
91 ENDDO
92 ENDDO
93 ENDIF
94
95 C-jmc: commented out: no need to compute Downward-LW (not used) from Net-LW
96 c IF ( lwfluxfile .NE. ' ' .AND. lwdownfile .EQ. ' ' ) THEN
97 C Loop over tiles.
98 c DO bj = myByLo(myThid),myByHi(myThid)
99 c DO bi = myBxLo(myThid),myBxHi(myThid)
100 c DO j = 1,sNy
101 c DO i = 1,sNx
102 c lwdown(i,j,bi,bj) =
103 c & ocean_emissivity*stefanBoltzmann*
104 c & ((theta(i,j,k,bi,bj)+cen2kel)**4)
105 c & - lwflux(i,j,bi,bj)
106 c ENDDO
107 c ENDDO
108 c ENDDO
109 c ENDDO
110 c ENDIF
111 #endif /* ALLOW_ATM_TEMP */
112
113 #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)
114 IF ( swfluxfile .EQ. ' ' .AND. swdownfile .NE. ' ' ) THEN
115 #ifdef ALLOW_ZENITHANGLE
116 IF ( useExfZenAlbedo .OR. useExfZenIncoming ) THEN
117 CALL EXF_ZENITHANGLE(myTime, myIter, myThid)
118 ENDIF
119 #endif
120 DO bj = myByLo(myThid),myByHi(myThid)
121 DO bi = myBxLo(myThid),myBxHi(myThid)
122 DO j = 1,sNy
123 DO i = 1,sNx
124 #ifdef ALLOW_ZENITHANGLE
125 IF ( useExfZenAlbedo ) THEN
126 swflux(i,j,bi,bj) = - swdown(i,j,bi,bj) *
127 & (1.0-zen_albedo(i,j,bi,bj))
128 ELSE
129 swflux(i,j,bi,bj) = - swdown(i,j,bi,bj) *
130 & (1.0-exf_albedo)
131 ENDIF
132 #else
133 swflux(i,j,bi,bj) = - swdown(i,j,bi,bj) *
134 & (1.0-exf_albedo)
135 #endif
136 ENDDO
137 ENDDO
138 ENDDO
139 ENDDO
140 ENDIF
141 C-jmc: commented out: no need to compute Downward-SW (not used) from Net-SW
142 c IF ( swfluxfile .NE. ' ' .AND. swdownfile .EQ. ' ' ) THEN
143 c DO bj = myByLo(myThid),myByHi(myThid)
144 c DO bi = myBxLo(myThid),myBxHi(myThid)
145 c DO j = 1,sNy
146 c DO i = 1,sNx
147 c swdown(i,j,bi,bj) = -swflux(i,j,bi,bj) / (1.0-exf_albedo)
148 c ENDDO
149 c ENDDO
150 c ENDDO
151 c ENDDO
152 c ENDIF
153 #endif
154
155 #endif /* ALLOW_DOWNWARD_RADIATION */
156
157 RETURN
158 END

  ViewVC Help
Powered by ViewVC 1.1.22