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

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

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


Revision 1.2 - (show annotations) (download)
Thu Sep 11 19:54:57 2014 UTC (9 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.1: +6 -3 lines
same changes as in ../code_ad: Include explicitly CTRL_OPTIONS.h (for
  ALLOW_HFLUXM_CONTROL, in case we don't use ECCO_CPPOPTIONS.h)

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

  ViewVC Help
Powered by ViewVC 1.1.22