/[MITgcm]/MITgcm/pkg/ecco/cost_mean_saltflux.F
ViewVC logotype

Annotation of /MITgcm/pkg/ecco/cost_mean_saltflux.F

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


Revision 1.6 - (hide annotations) (download)
Mon Oct 30 17:01:21 2006 UTC (17 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58r_post, checkpoint58s_post
Changes since 1.5: +7 -5 lines
o Yet another change to suppress recomp. loop for DIVA
  while keeping monitor and diagnostics (but suppress checkpointing)
o Catch a few divisions by zero for non-used cost terms (weights=0)

1 heimbach 1.1
2     #include "COST_CPPOPTIONS.h"
3    
4    
5     subroutine cost_mean_saltflux(
6     I myiter,
7     I mytime,
8     I mythid
9     & )
10    
11     c ==================================================================
12     c SUBROUTINE cost_mean_saltflux
13     c ==================================================================
14     c
15     c o Evaluate cost function contribution of sea surface salinity.
16     c
17     c started: Elisabeth Remy 19-mar-2001 copy from cost_sst.F
18     c
19     c ==================================================================
20     c SUBROUTINE cost_mean_saltflux
21     c ==================================================================
22    
23     implicit none
24    
25     c == global variables ==
26    
27     #include "EEPARAMS.h"
28     #include "SIZE.h"
29     #include "GRID.h"
30     #include "DYNVARS.h"
31     #include "PARAMS.h"
32    
33     #include "cal.h"
34     #include "ecco_cost.h"
35     #include "ctrl.h"
36     #include "ctrl_dummy.h"
37     #include "optim.h"
38    
39     c == routine arguments ==
40    
41     integer myiter
42     _RL mytime
43     integer mythid
44    
45     c == local variables ==
46    
47     integer bi,bj
48 heimbach 1.2 integer i,j,kk
49 heimbach 1.1 integer itlo,ithi
50     integer jtlo,jthi
51     integer jmin,jmax
52     integer imin,imax
53     integer irec
54     integer levmon
55     integer levoff
56     integer ilsalt
57    
58 heimbach 1.5 _RL tmpx, tmpx2
59     _RL fctilemm(nSx,nSy)
60     _RL sumcos(nSx,nSy)
61     _RL sumtot
62     _RL fctiletot
63 heimbach 1.1
64    
65     character*(80) fnamesflux
66    
67     logical doglobalread
68     logical ladinit
69    
70     character*(MAX_LEN_MBUF) msgbuf
71    
72     c == external functions ==
73    
74     integer ilnblnk
75     external ilnblnk
76    
77     c == end of interface ==
78    
79     jtlo = mybylo(mythid)
80     jthi = mybyhi(mythid)
81     itlo = mybxlo(mythid)
82     ithi = mybxhi(mythid)
83     jmin = 1
84     jmax = sny
85     imin = 1
86     imax = snx
87    
88     c-- Read tiled data.
89     doglobalread = .false.
90     ladinit = .false.
91    
92     #ifdef ALLOW_MEAN_SFLUX_COST_CONTRIBUTION
93    
94     if (optimcycle .ge. 0) then
95     ilsalt = ilnblnk( sfluxbarfile )
96     write(fnamesflux(1:80),'(2a,i10.10)')
97     & sfluxbarfile(1:ilsalt),'.',optimcycle
98     endif
99    
100 heimbach 1.5 do irec = 1, MAX(1,nyearsrec)
101 heimbach 1.1
102     c-- Read time averages and the monthly mean data.
103     call active_read_xy( fnamesflux, tmpfld2d, irec,
104     & doglobalread, ladinit,
105     & optimcycle, mythid,
106     & xx_sflux_mean_dummy )
107    
108     do bj = jtlo,jthi
109     do bi = itlo,ithi
110     kk = 1
111 heimbach 1.5 fctilemm(bi,bj) = 0. _d 0
112     sumcos(bi,bj) = 0. _d 0
113 heimbach 1.1 do j = jmin,jmax
114     do i = imin,imax
115     tmpx=tmpfld2d(i,j,bi,bj)
116 heimbach 1.2 if (maskC(i,j,kk,bi,bj) .ne. 0.) then
117 heimbach 1.5 fctilemm(bi,bj) = fctilemm(bi,bj) + tmpx
118 heimbach 1.4 & *cos(yc(i,j,bi,bj)*deg2rad)
119 heimbach 1.5 sumcos(bi,bj) = sumcos(bi,bj)
120     & + cos(yc(i,j,bi,bj)*deg2rad)
121 heimbach 1.4 num_sfluxmm(bi,bj) = num_sfluxmm(bi,bj) + 1
122 heimbach 1.1 endif
123     enddo
124     enddo
125 heimbach 1.5 enddo
126     enddo
127 heimbach 1.1
128 heimbach 1.5 sumtot = 0.
129     fctiletot = 0.
130     do bj = jtlo,jthi
131     do bi = itlo,ithi
132     sumtot = sumtot + sumcos(bi,bj)
133     fctiletot = fctiletot + fctilemm(bi,bj)
134     enddo
135     enddo
136     _GLOBAL_SUM_R8( sumtot , myThid )
137     _GLOBAL_SUM_R8( fctiletot , myThid )
138    
139     if (sumtot.eq.0.) sumtot = 1.
140 heimbach 1.1
141 heimbach 1.6 if ( wmean_sflux .NE. 0. ) then
142     do bj = jtlo,jthi
143     do bi = itlo,ithi
144 heimbach 1.5 fctilemm(bi,bj) = fctilemm(bi,bj) / sumtot
145     objf_sfluxmm(bi,bj) = objf_sfluxmm(bi,bj)
146 heimbach 1.6 & + (fctilemm(bi,bj)/wmean_sflux/nyearsrec)**2
147     enddo
148     enddo
149     endif
150 heimbach 1.5
151     c-- diagnostic: imbalance per year:
152     tmpx2 = wsfluxmm(1,1) * fctiletot / sumtot
153     write(standardmessageunit,'(A,I5,D22.15)')
154     & ' --> bal_sfluxmm =', irec, tmpx2
155 heimbach 1.1
156 heimbach 1.5 enddo
157 heimbach 1.1
158     #endif
159    
160     return
161     end
162    

  ViewVC Help
Powered by ViewVC 1.1.22