/[MITgcm]/MITgcm/verification/tutorial_global_oce_optim/code_ad/cost_weights.F
ViewVC logotype

Contents of /MITgcm/verification/tutorial_global_oce_optim/code_ad/cost_weights.F

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


Revision 1.5 - (show annotations) (download)
Fri Aug 10 19:31:56 2012 UTC (11 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63r, checkpoint63s, checkpoint64, checkpoint65, checkpoint65b, checkpoint65c, checkpoint65a
Changes since 1.4: +2 -2 lines
rename COST_CPPOPTIONS.h to COST_OPTIONS.h

1 C $Header: /u/gcmpack/MITgcm/verification/tutorial_global_oce_optim/code_ad/cost_weights.F,v 1.4 2009/10/09 01:26:52 jmc Exp $
2 C $Name: $
3
4 #include "COST_OPTIONS.h"
5
6 SUBROUTINE COST_WEIGHTS( myThid )
7
8 C ==================================================================
9 C SUBROUTINE COST_WEIGHTS
10 C ==================================================================
11 C
12 C o Set weights used in the cost function and in the
13 C normalization of the sensitivities when ALLOW_NON_DIMENSIONAL
14
15 IMPLICIT NONE
16
17 C == global variables ==
18 #include "EEPARAMS.h"
19 #include "SIZE.h"
20 #include "PARAMS.h"
21 #include "GRID.h"
22
23 #include "ctrl.h"
24 #include "ctrl_weights.h"
25 #include "cost.h"
26
27 C == routine arguments ==
28 INTEGER myThid
29
30 C == Functions ==
31 INTEGER MDS_RECLEN
32 EXTERNAL MDS_RECLEN
33
34 C == local variables ==
35 INTEGER bi,bj
36 INTEGER i,j,k
37 INTEGER itlo,ithi,jtlo,jthi
38 INTEGER jMin,jMax,iMin,iMax
39 INTEGER iUnit, length_of_rec
40
41 _RL dummy
42 _RL wti(Nr)
43 REAL*8 tmpwti(Nr)
44 CHARACTER*(MAX_LEN_MBUF) msgBuf
45
46 C == end of interface ==
47
48 jtlo = myByLo(myThid)
49 jthi = myByHi(myThid)
50 itlo = myBxLo(myThid)
51 ithi = myBxHi(myThid)
52 iMin = 1-OLx
53 iMax = sNx+OLx
54 jMin = 1-OLy
55 jMax = sNy+OLy
56
57 C-- Initialize variance (weight) fields.
58 DO k = 1,Nr
59 wti(k) = 0. _d 0
60 ENDDO
61 DO bj = jtlo,jthi
62 DO bi = itlo,ithi
63 DO j = jMin,jMax
64 DO i = iMin,iMax
65 whfluxm(i,j,bi,bj)= 0. _d 0
66 ENDDO
67 ENDDO
68 DO k = 1,Nr
69 wunit(k,bi,bj) = 1. _d 0
70 wtheta(k,bi,bj) = 0. _d 0
71 wsalt(k,bi,bj) = 0. _d 0
72 ENDDO
73 ENDDO
74 ENDDO
75
76 C-- Read error information and set up weight matrices.
77
78 #ifdef ALLOW_COST_TEMP
79 C Temperature weights for cost function
80 _BEGIN_MASTER(myThid)
81 CALL MDSFINDUNIT( iUnit, myThid )
82 length_of_rec = MDS_RECLEN( precFloat64, Nr, myThid )
83 OPEN( iUnit, FILE='Err_levitus_15layer.bin', STATUS='OLD',
84 & FORM='UNFORMATTED',ACCESS='DIRECT',RECL=length_of_rec )
85 READ(iUnit,rec=1) tmpwti
86 CLOSE(iUnit)
87 #ifdef _BYTESWAPIO
88 CALL MDS_BYTESWAPR8( Nr, tmpwti )
89 #endif
90 _END_MASTER(myThid)
91 _BARRIER
92
93 DO k=1,Nr
94 wti(k) = tmpwti(k)
95 ENDDO
96 WRITE(msgBuf,'(3A)') 'S/R COST_WEIGHTS:',
97 & ' Temperature weights loaded from: ','Err_levitus_15layer.bin'
98 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
99 & SQUEEZE_RIGHT , myThid )
100
101 c print*,'Weights for temperature: wti', (wti(k),k=1,nr)
102
103 DO bj = jtlo,jthi
104 DO bi = itlo,ithi
105 DO k = 1, Nr
106 wtheta(k,bi,bj) = 1. _d 0/wti(k)/wti(k)
107 ENDDO
108 ENDDO
109 ENDDO
110 #endif
111
112 C-- Then the hflux weights :
113
114 #if (defined (ALLOW_COST_HFLUXM) || defined (ALLOW_HFLUXM_CONTROL))
115 CALL READ_REC_3D_RL( 'Err_hflux.bin', precFloat64, 1,
116 & whfluxm, 1, 0, myThid )
117 _EXCH_XY_RL(whfluxm , myThid )
118 DO bj = jtlo,jthi
119 DO bi = itlo,ithi
120 DO j = jMin,jMax
121 DO i = iMin,iMax
122 c print*,'Uncertainties for Heat Flux',i,j,whfluxm(i,j,bi,bj)
123 IF (whfluxm(i,j,bi,bj) .NE. 0. _d 0) THEN
124 whfluxm(i,j,bi,bj) = 1. _d 0 /whfluxm(i,j,bi,bj)
125 & /whfluxm(i,j,bi,bj)
126 ELSE
127 whfluxm(i,j,bi,bj) = 1. _d 0
128 ENDIF
129 ENDDO
130 ENDDO
131 ENDDO
132 ENDDO
133 #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
134 CALL ACTIVE_WRITE_XY('whfluxm',whfluxm,1,0,myThid,dummy)
135 #endif
136 #endif
137 RETURN
138 END

  ViewVC Help
Powered by ViewVC 1.1.22