/[MITgcm]/MITgcm/verification/bottom_ctrl_5x5/code_ad/cost_test.F
ViewVC logotype

Annotation of /MITgcm/verification/bottom_ctrl_5x5/code_ad/cost_test.F

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


Revision 1.1 - (hide annotations) (download)
Wed Jun 7 02:00:01 2006 UTC (17 years, 10 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint58q_post, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59h, checkpoint59, checkpoint58i_post, checkpoint58o_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint58m_post
Adding verification for 5x5 box (4-layer) bottom topography control

1 heimbach 1.1 C $Header: /u/gcmpack/development/heimbach/ctrl_bottom_topo/5x5/code/cost_test.F,v 1.1.1.1 2004/04/23 18:19:48 mlosch Exp $
2    
3     #include "CPP_OPTIONS.h"
4    
5     subroutine cost_test( myThid )
6     C /==========================================================\
7     C | subroutine cost_test |
8     C | o this routine computes the cost function for the tiles |
9     C | of this processor |
10     C |==========================================================|
11     C | |
12     C | Notes |
13     C | ===== |
14     C \==========================================================/
15     IMPLICIT NONE
16    
17     C == Global variables ===
18     #include "SIZE.h"
19     #include "EEPARAMS.h"
20     #include "PARAMS.h"
21     #include "DYNVARS.h"
22     #include "GRID.h"
23    
24     #include "cost.h"
25    
26     C == Routine arguments ==
27     C myThid - Thread number for this instance of the routine.
28     integer bi, bj
29     integer myThid
30    
31     #ifdef ALLOW_COST_TEST
32     C == Local variables
33     integer i, j, k
34     integer ig, jg
35     integer itlo,ithi
36     integer jtlo,jthi
37    
38     _RL vol_trans
39     C-- index values at which the transport is to be calculated
40     INTEGER iysecmin, iysecmax, ixsec
41     PARAMETER (ixsec = 4, iysecmin = 3, iysecmax = 3)
42    
43     C
44     jtlo = mybylo(mythid)
45     jthi = mybyhi(mythid)
46     itlo = mybxlo(mythid)
47     ithi = mybxhi(mythid)
48    
49     DO bj=jtlo,jthi
50     DO bi=itlo,ithi
51     vol_trans = 0.
52     DO J=1,sNy
53     jg = myYGlobalLo-1+(bj-1)*sNy+J
54     IF ( jg .ge. iysecmin .and. jg .le. iysecmax ) THEN
55     DO I=1,sNx
56     ig = myXGlobalLo-1+(bi-1)*sNx+I
57     IF ( ig .eq. ixsec ) THEN
58     DO K=1,Nr
59     IF ( maskW(I,J,K,BI,BJ) .NE. 0. ) THEN
60     vol_trans = vol_trans
61     & + uVel(I,J,K,BI,BJ)
62     & *_hFacW(I,J,K,BI,BJ)
63     & *dyG(I,J,BI,BJ)*drF(K)
64     ENDIF
65     ENDDO
66     ENDIF
67     ENDDO
68     ENDIF
69     ENDDO
70     objf_test(bi,bj) = vol_trans*1.0e-06
71     END DO
72     END DO
73     CML objf_test(1,1) = vVel(3,3,1,1,1)* _hFacS(3,3,1,1,1)
74     Cml iLocOut = 6
75     Cml jLocOut = 35
76     Cml kLocOut = 1
77     Cml
78     Cmlce some reference temperature
79     Cml thetaRef = 24.0D0
80     Cml
81     CmlC-- Calculate cost function on tile of this instance
82     Cml do bj = jtlo,jthi
83     Cml do bi = itlo,ithi
84     Cml do j=1,sNy
85     Cml jg = myYGlobalLo-1+(bj-1)*sNy+j
86     Cml do i=1,sNx
87     Cml ig = myXGlobalLo-1+(bi-1)*sNx+i
88     Cml
89     Cml if ((ig .eq. iLocOut) .and. (jg .eq. jLocOut)) then
90     Cml write(*,'(a,3(x,i4),a,4(x,i4))')
91     Cml & 'COST ',ig,jg,kLocOut,' TILE ',i,j,bi,bj
92     Cml objf_test(bi,bj) = theta(i,j,kLocOut,bi,bj)
93     Cml endif
94     Cml
95     Cml end do
96     Cml end do
97     Cml end do
98     Cml end do
99    
100     #endif
101    
102     END

  ViewVC Help
Powered by ViewVC 1.1.22