/[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.2 - (hide annotations) (download)
Thu Jun 15 17:01:09 2006 UTC (17 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58r_post, checkpoint58n_post, checkpoint58q_post, checkpoint58j_post, checkpoint58o_post, checkpoint58k_post, checkpoint58s_post, checkpoint58p_post, checkpoint58m_post
Changes since 1.1: +7 -3 lines
o Ported new load_fields_driver structure over to ECCO
o adjusted exf and seaice store directives accordingly

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

  ViewVC Help
Powered by ViewVC 1.1.22