/[MITgcm]/MITgcm/pkg/seaice/seaice_budget_ocean.F
ViewVC logotype

Annotation of /MITgcm/pkg/seaice/seaice_budget_ocean.F

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


Revision 1.11 - (hide annotations) (download)
Fri Nov 19 16:21:08 2010 UTC (13 years, 6 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62o, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.10: +3 -3 lines
  - replace irritating parameters SEAICE_latentWater/Ice and SEAICE_sensHeat
    by something more sensible (parameters that are what their name implies)
  - change some defaults, so that by default exf-parameters are used for
    things like rhoAir, cpAir,latent/sensible heat parameters

1 mlosch 1.11 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_budget_ocean.F,v 1.10 2010/01/20 00:44:08 dimitri Exp $
2 mlosch 1.2 C $Name: $
3 mlosch 1.1
4     #include "SEAICE_OPTIONS.h"
5    
6     CStartOfInterface
7     SUBROUTINE SEAICE_BUDGET_OCEAN(
8     I UG,
9     U TSURF,
10     O netHeatFlux, SWHeatFlux,
11 dimitri 1.7 I bi, bj, myTime, myIter, myThid )
12 mlosch 1.1 C /================================================================\
13     C | SUBROUTINE seaice_budget_ocean |
14     C | o Calculate surface heat fluxes over open ocean |
15     C | see Hibler, MWR, 108, 1943-1973, 1980 |
16     C | If SEAICE_EXTERNAL_FLUXES is defined this routine simply |
17     C | simply copies the global fields to the seaice-local fields. |
18     C |================================================================|
19     C \================================================================/
20     IMPLICIT NONE
21    
22     C === Global variables ===
23     #include "SIZE.h"
24     #include "EEPARAMS.h"
25     #include "FFIELDS.h"
26     #include "SEAICE_PARAMS.h"
27 dimitri 1.5 #ifdef ALLOW_EXF
28     # include "EXF_OPTIONS.h"
29     # include "EXF_FIELDS.h"
30     #endif
31 mlosch 1.1
32     C === Routine arguments ===
33     C INPUT:
34     C UG :: thermal wind of atmosphere
35     C TSURF :: surface temperature of ocean in Kelvin
36     C bi,bj :: loop indices
37 dimitri 1.7 C myTime :: Simulation time
38     C myIter :: Simulation timestep number
39 mlosch 1.3 C myThid :: Thread no. that called this routine.
40 mlosch 1.1 C OUTPUT:
41     C netHeatFlux :: net surface heat flux over open water or under ice
42     C SWHeatFlux :: short wave heat flux over open water or under ice
43 dimitri 1.6 _RL UG (1:sNx,1:sNy)
44 mlosch 1.1 _RL TSURF (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
45 dimitri 1.6 _RL netHeatFlux(1:sNx,1:sNy)
46     _RL SWHeatFlux (1:sNx,1:sNy)
47 dimitri 1.7 _RL myTime
48     INTEGER bi, bj, myIter, myThid
49 mlosch 1.1 CEndOfInterface
50    
51     C === Local variables ===
52     C i,j - Loop counters
53     INTEGER i, j
54     #ifndef SEAICE_EXTERNAL_FLUXES
55 dimitri 1.10 _RL QS1, D1, D1W, D3, TMELT
56 mlosch 1.1
57     C local copies of global variables
58 dimitri 1.6 _RL tsurfLoc (1:sNx,1:sNy)
59     _RL atempLoc (1:sNx,1:sNy)
60     _RL lwdownLoc (1:sNx,1:sNy)
61     _RL ALB (1:sNx,1:sNy)
62 mlosch 1.1 C coefficients of Hibler (1980), appendix B
63 dimitri 1.6 _RL A1 (1:sNx,1:sNy)
64     _RL A2 (1:sNx,1:sNy)
65 mlosch 1.1 C auxiliary variable
66 dimitri 1.6 _RL B (1:sNx,1:sNy)
67 mlosch 1.1
68     C NOW DEFINE ASSORTED CONSTANTS
69     C SATURATION VAPOR PRESSURE CONSTANT
70     QS1=0.622 _d +00/1013.0 _d +00
71     C SENSIBLE HEAT CONSTANT
72 mlosch 1.11 D1=SEAICE_dalton*SEAICE_cpAir*SEAICE_rhoAir
73 mlosch 1.1 C WATER LATENT HEAT CONSTANT
74 mlosch 1.11 D1W=SEAICE_dalton*SEAICE_lhEvap*SEAICE_rhoAir
75 mlosch 1.1 C STEFAN BOLTZMAN CONSTANT TIMES 0.97 EMISSIVITY
76     D3=SEAICE_emissivity
77     C MELTING TEMPERATURE OF ICE
78     TMELT=273.16 _d +00
79    
80     DO J=1,sNy
81     DO I=1,sNx
82     netHeatFlux(I,J) = 0. _d 0
83     SWHeatFlux (I,J) = 0. _d 0
84     C
85     tsurfLoc (I,J) = MIN(273.16 _d 0+MAX_TICE,TSURF(I,J,bi,bj))
86 dimitri 1.7 # ifdef ALLOW_ATM_TEMP
87 mlosch 1.1 C Is this necessary?
88     atempLoc (I,J) = MAX(273.16 _d 0+MIN_ATEMP,ATEMP(I,J,bi,bj))
89 dimitri 1.7 # endif
90     # ifdef ALLOW_DOWNWARD_RADIATION
91 mlosch 1.1 lwdownLoc(I,J) = MAX(MIN_LWDOWN,LWDOWN(I,J,bi,bj))
92 dimitri 1.7 # endif
93 mlosch 1.1 ENDDO
94     ENDDO
95     #endif /* SEAICE_EXTERNAL_FLUXES */
96    
97     C NOW DETERMINE OPEN WATER HEAT BUD. ASSUMING TSURF=WATER TEMP.
98     C WATER ALBEDO IS ASSUMED TO BE THE CONSTANT SEAICE_waterAlbedo
99     DO J=1,sNy
100     DO I=1,sNx
101     #ifdef SEAICE_EXTERNAL_FLUXES
102     netHeatFlux(I,J) = Qnet(I,J,bi,bj)
103     SWHeatFlux (I,J) = Qsw(I,J,bi,bj)
104     #else /* SEAICE_EXTERNAL_FLUXES undefined */
105     ALB(I,J)=SEAICE_waterAlbedo
106 dimitri 1.7 # ifdef ALLOW_DOWNWARD_RADIATION
107 mlosch 1.1 A1(I,J)=(ONE-ALB(I,J))*SWDOWN(I,J,bi,bj)
108     & +lwdownLoc(I,J)*0.97 _d 0
109     & +D1*UG(I,J)*atempLoc(I,J)+D1W*UG(I,J)*AQH(I,J,bi,bj)
110     B(I,J)=QS1*6.11 _d +00*EXP(17.2694 _d +00
111     & *(tsurfLoc(I,J)-TMELT)
112     & /(tsurfLoc(I,J)-TMELT+237.3 _d +00))
113     A2(I,J)=-D1*UG(I,J)*tsurfLoc(I,J)-D1W*UG(I,J)*B(I,J)
114     & -D3*(tsurfLoc(I,J)**4)
115     netHeatFlux(I,J)=-A1(I,J)-A2(I,J)
116     SWHeatFlux (I,J)=-(ONE-ALB(I,J))*SWDOWN(I,J,bi,bj)
117 dimitri 1.7 # endif /* ALLOW_DOWNWARD_RADIATION */
118 mlosch 1.1 #endif /* SEAICE_EXTERNAL_FLUXES */
119     ENDDO
120     ENDDO
121    
122     RETURN
123     END

  ViewVC Help
Powered by ViewVC 1.1.22