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

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

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


Revision 1.9 - (hide annotations) (download)
Wed Jun 24 08:55:43 2009 UTC (14 years, 10 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62d, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.8: +8 -7 lines
third step of cleaning up the 3-time levels of UICE,VICE,HEFF,AREA:
missed another two instances of HEFF(i,j,1,bi,bj)

1 mlosch 1.9 C $Header: /u/gcmpack/MITgcm/pkg/seaice/cost_ice_test.F,v 1.8 2009/06/24 08:42:22 mlosch Exp $
2 jmc 1.4 C $Name: $
3 heimbach 1.1
4     #include "SEAICE_OPTIONS.h"
5    
6     subroutine cost_ice_test( mytime, myiter, mythid )
7    
8     c ==================================================================
9     c SUBROUTINE cost_ice_test
10     c ==================================================================
11     c
12 dimitri 1.6 c o Compute sea-ice cost function. The following options can be
13     c selected with data.seaice (SEAICE_PARM02) variable cost_ice_flag
14 heimbach 1.1 c
15     c cost_ice_flag = 1
16     c - compute mean sea-ice volume
17     c costIceStart < mytime < costIceEnd
18     c
19     c cost_ice_flag = 2
20     c - compute mean sea-ice area
21     c costIceStart < mytime < costIceEnd
22     c
23     c cost_ice_flag = 3
24     c - heat content of top level plus latent heat of sea-ice
25     c costIceStart < mytime < costIceEnd
26     c
27     c cost_ice_flag = 4
28     c - heat content of top level
29     c costIceStart < mytime < costIceEnd
30     c
31     c cost_ice_flag = 5
32     c - heat content of top level plus sea-ice plus latent heat of snow
33     c costIceStart < mytime < costIceEnd
34     c
35     c cost_ice_flag = 6
36     c - quadratic cost function measuring difference between pkg/seaice
37     c AREA variable and simulated sea-ice measurements at every time
38     c step.
39     c
40     c ==================================================================
41     c
42     c started: menemenlis@jpl.nasa.gov 26-Feb-2003
43     c
44     c ==================================================================
45     c SUBROUTINE cost_ice_test
46     c ==================================================================
47    
48     implicit none
49    
50     c == global variables ==
51     #ifdef ALLOW_COST_ICE
52     #include "EEPARAMS.h"
53     #include "SIZE.h"
54     #include "GRID.h"
55     #include "PARAMS.h"
56     #include "SEAICE_COST.h"
57     #include "SEAICE.h"
58     #include "DYNVARS.h"
59     #include "cost.h"
60     #endif /* ALLOW_COST_ICE */
61    
62     c == routine arguments ==
63    
64     _RL mytime
65     integer myiter
66     integer mythid
67    
68 dimitri 1.5 #ifdef ALLOW_COST_ICE
69 heimbach 1.1
70     c == local variables ==
71    
72     c msgBuf - Informational/error message buffer
73     CHARACTER*(MAX_LEN_MBUF) msgBuf
74 mlosch 1.9 integer bi,bj,i,j,kSrf
75 heimbach 1.1 _RL tempVar
76    
77     c == external functions ==
78    
79     integer ilnblnk
80     external ilnblnk
81    
82     c == end of interface ==
83    
84     if ( myTime .GT. (endTime - lastinterval) ) then
85 jmc 1.4 tempVar = 1. /
86 heimbach 1.1 & ( ( 1. + min(endTime-startTime,lastinterval) )
87 jmc 1.4 & / deltaTClock )
88 heimbach 1.1
89 mlosch 1.9 kSrf = 1
90 heimbach 1.1 cph(
91 mlosch 1.9 print *, 'ph-ice B ', myiter, theta(4,4,kSrf,1,1),
92     & area(4,4,1,1), heff(4,4,1,1)
93 heimbach 1.1 cph)
94     if ( cost_ice_flag .eq. 1 ) then
95     c sea-ice volume
96     do bj=myByLo(myThid),myByHi(myThid)
97     do bi=myBxLo(myThid),myBxHi(myThid)
98     do j = 1,sny
99     do i = 1,snx
100     objf_ice(bi,bj) = objf_ice(bi,bj) +
101 mlosch 1.8 & tempVar * rA(i,j,bi,bj) * HEFF(i,j,bi,bj)
102 heimbach 1.1 enddo
103     enddo
104     enddo
105     enddo
106    
107     elseif ( cost_ice_flag .eq. 2 ) then
108     c sea-ice area
109     do bj=myByLo(myThid),myByHi(myThid)
110     do bi=myBxLo(myThid),myBxHi(myThid)
111     do j = 1,sny
112     do i = 1,snx
113     objf_ice(bi,bj) = objf_ice(bi,bj) +
114 mlosch 1.8 & tempVar * rA(i,j,bi,bj) * AREA(i,j,bi,bj)
115 heimbach 1.1 enddo
116     enddo
117     enddo
118     enddo
119    
120     c heat content of top level:
121     c theta * delZ * (sea water heat capacity = 3996 J/kg/K)
122     c * (density of sea-water = 1026 kg/m^3)
123     c
124     c heat content of sea-ice:
125     c tice * heff * (sea ice heat capacity = 2090 J/kg/K)
126     c * (density of sea-ice = 910 kg/m^3)
127     c
128     c note: to remove mass contribution to heat content,
129     c which is not properly accounted for by volume converving
130     c ocean model, theta and tice are referenced to freezing
131     c temperature of sea-ice, here -1.96 deg C
132     c
133     c latent heat content of sea-ice:
134     c - heff * (latent heat of fusion = 334000 J/kg)
135     c * (density of sea-ice = 910 kg/m^3)
136     c
137     c latent heat content of snow:
138     c - hsnow * (latent heat of fusion = 334000 J/kg)
139     c * (density of snow = 330 kg/m^3)
140    
141     elseif ( cost_ice_flag .eq. 3 ) then
142     c heat content of top level plus latent heat of sea-ice
143     do bj=myByLo(myThid),myByHi(myThid)
144     do bi=myBxLo(myThid),myBxHi(myThid)
145     do j = 1,sny
146     do i = 1,snx
147     objf_ice(bi,bj) = objf_ice(bi,bj) +
148     & tempVar * rA(i,j,bi,bj) * (
149 mlosch 1.9 & (THETA(i,j,kSrf,bi,bj) + 1.96 ) *
150 heimbach 1.1 & drF(1) * 3996 * 1026 -
151 mlosch 1.7 & HEFF(i,j,bi,bj) * 334000 * 910 )
152 heimbach 1.1 enddo
153     enddo
154     enddo
155     enddo
156    
157     elseif ( cost_ice_flag .eq. 4 ) then
158     c heat content of top level
159     do bj=myByLo(myThid),myByHi(myThid)
160     do bi=myBxLo(myThid),myBxHi(myThid)
161     do j = 1,sny
162     do i = 1,snx
163     objf_ice(bi,bj) = objf_ice(bi,bj) +
164     & tempVar * rA(i,j,bi,bj) * (
165 mlosch 1.9 & (THETA(i,j,kSrf,bi,bj) + 1.96 ) *
166 heimbach 1.1 & drF(1) * 3996 * 1026 )
167     enddo
168     enddo
169     enddo
170     enddo
171    
172     elseif ( cost_ice_flag .eq. 5 ) then
173     c heat content of top level plus sea-ice plus latent heat of snow
174     do bj=myByLo(myThid),myByHi(myThid)
175     do bi=myBxLo(myThid),myBxHi(myThid)
176     do j = 1,sny
177     do i = 1,snx
178     objf_ice(bi,bj) = objf_ice(bi,bj) +
179     & tempVar * rA(i,j,bi,bj) * (
180 mlosch 1.9 & (THETA(i,j,kSrf,bi,bj) + 1.96 ) *
181 heimbach 1.1 & drF(1) * 3996 * 1026 +
182     & (TICE(i,j,bi,bj) - 273.15 + 1.96 ) *
183 mlosch 1.7 & HEFF(i,j,bi,bj) * 2090 * 910 -
184     & HEFF(i,j,bi,bj) * 334000 * 910 -
185     & HSNOW(i,j,bi,bj) * 334000 * 330 )
186 heimbach 1.1 enddo
187     enddo
188     enddo
189     enddo
190    
191     elseif ( cost_ice_flag .eq. 6 ) then
192     c Qadratic cost function measuring difference between pkg/seaice
193     c AREA variable and simulated sea-ice measurements at every time
194     c step. For time being no measurements are read-in. It is
195     c assumed that measurements are AREA=0.5 at all times everywhere.
196     do bj=myByLo(myThid),myByHi(myThid)
197     do bi=myBxLo(myThid),myBxHi(myThid)
198     do j = 1,sny
199     do i = 1,snx
200     objf_ice(bi,bj) = objf_ice(bi,bj) +
201 mlosch 1.7 & ( AREA(i,j,bi,bj) - 0.5 ) *
202     & ( AREA(i,j,bi,bj) - 0.5 )
203 heimbach 1.1 enddo
204     enddo
205     enddo
206     enddo
207    
208     else
209     WRITE(msgBuf,'(A)')
210     & 'COST_ICE: invalid cost_ice_flag'
211     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
212     & SQUEEZE_RIGHT , myThid )
213     STOP 'ABNORMAL END: S/R COST_ICE'
214     endif
215     endif
216    
217 heimbach 1.2 cph(
218     print *, 'ph-ice C ', myiter, objf_ice(1,1)
219     cph)
220    
221 heimbach 1.1 #endif /* ALLOW_COST_ICE */
222    
223     end

  ViewVC Help
Powered by ViewVC 1.1.22