/[MITgcm]/MITgcm/pkg/ctrl/ctrl_hfacc_ini.F
ViewVC logotype

Annotation of /MITgcm/pkg/ctrl/ctrl_hfacc_ini.F

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


Revision 1.5 - (hide annotations) (download)
Tue Oct 9 00:00:00 2007 UTC (16 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59k, checkpoint61f, checkpoint59j, checkpoint61e, checkpoint61g, checkpoint61d, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61l, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i
Changes since 1.4: +10 -9 lines
add missing cvs $Header:$ or $Name:$

1 jmc 1.5 C $Header: $
2     C $Name: $
3 heimbach 1.1
4     #include "CTRL_CPPOPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: ctrl_hfacc_ini
8     C !INTERFACE:
9     subroutine ctrl_hfacc_ini( mythid )
10    
11     C !DESCRIPTION: \bv
12     c *=================================================================
13 jmc 1.5 c | SUBROUTINE ctrl_hfacc_ini
14 heimbach 1.1 c | Add the hFacC part of the control vector to the model state
15 jmc 1.5 c | and update the tile halos.
16 heimbach 1.1 c | The control vector is defined in the header file "ctrl.h".
17     c *=================================================================
18     C \ev
19    
20     C !USES:
21     implicit none
22    
23     c == global variables ==
24     #include "EEPARAMS.h"
25     #include "SIZE.h"
26     #include "GRID.h"
27     #include "ctrl.h"
28     #include "ctrl_dummy.h"
29     #include "optim.h"
30    
31     C !INPUT/OUTPUT PARAMETERS:
32     c == routine arguments ==
33     integer mythid
34    
35     #ifdef ALLOW_HFACC_CONTROL
36     C !LOCAL VARIABLES:
37     c == local variables ==
38    
39     integer bi,bj
40     integer i,j,k
41     integer itlo,ithi
42     integer jtlo,jthi
43     integer jmin,jmax
44     integer imin,imax
45     integer il
46    
47     logical equal
48     logical doglobalread
49     logical ladinit
50    
51     character*( 80) fnamehfacc
52     character*(max_len_mbuf) msgbuf
53    
54     _RL fac
55    
56     c == external ==
57     integer ilnblnk
58     external ilnblnk
59    
60     c == end of interface ==
61     CEOP
62    
63     jtlo = mybylo(mythid)
64     jthi = mybyhi(mythid)
65     itlo = mybxlo(mythid)
66     ithi = mybxhi(mythid)
67     jmin = 1-oly
68     jmax = sny+oly
69     imin = 1-olx
70     imax = snx+olx
71    
72     doglobalread = .false.
73     ladinit = .false.
74    
75     equal = .true.
76    
77     if ( equal ) then
78     fac = 1. _d 0
79     else
80     fac = 0. _d 0
81     endif
82    
83 jmc 1.5 Cml write(msgbuf,'(a)')
84 heimbach 1.1 Cml & 'ctrl_hfacc_ini: Re-initialising hFacC,'
85     Cml call print_message( msgbuf, standardmessageunit,
86     Cml & SQUEEZE_RIGHT , mythid)
87 jmc 1.5 Cml write(msgbuf,'(a)')
88 heimbach 1.1 Cml & ' adding the control vector.'
89     Cml call print_message( msgbuf, standardmessageunit,
90     Cml & SQUEEZE_RIGHT , mythid)
91 jmc 1.5 write(standardmessageunit,'(21x,a)')
92 heimbach 1.1 & 'ctrl_hfacc_ini: Re-initialising hFacC,'
93 jmc 1.5 write(standardmessageunit,'(21x,a)')
94 heimbach 1.1 & ' adding the control vector.'
95    
96     C Re-initialize hFacC, so that TAMC/TAF can see it
97     C Once hFacC is the control variable, and not its anomaly
98     C this will be no longer necessary
99     do bj = jtlo,jthi
100     do bi = itlo,ithi
101     do k = 1,nr
102     do j = jmin,jmax
103     do i = imin,imax
104     hFacC(i,j,k,bi,bj) = 0.
105     tmpfld3d(i,j,k,bi,bj) = 0. _d 0
106     enddo
107     enddo
108     enddo
109     enddo
110     enddo
111     _BEGIN_MASTER( myThid )
112     CALL READ_FLD_XYZ_RL( 'hFacC', ' ', hFacC, 0, myThid )
113     _END_MASTER( myThid )
114     Cml _EXCH_XYZ_R8( hFacC ,myThid )
115     _EXCH_XYZ_R4( hFacC ,myThid )
116    
117 jmc 1.5 C--
118 heimbach 1.1 il=ilnblnk( xx_hfacc_file )
119     write(fnamehfacc(1:80),'(2a,i10.10)')
120     & xx_hfacc_file(1:il),'.',optimcycle
121     #ifdef ALLOW_HFACC3D_CONTROL
122 heimbach 1.4 call active_read_xyz( fnamehfacc, tmpfld3d, 1,
123 heimbach 1.1 & doglobalread, ladinit, optimcycle,
124     & mythid, xx_hfacc_dummy )
125     do bj = jtlo,jthi
126     do bi = itlo,ithi
127     do k = 1,nr
128     do j = jmin,jmax
129     do i = imin,imax
130     hFacC(i,j,k,bi,bj) = hFacC(i,j,k,bi,bj) +
131     & fac*tmpfld3d(i,j,k,bi,bj)
132     enddo
133     enddo
134     enddo
135     enddo
136     enddo
137     #else /* ALLOW_HFACC3D_CONTROL undefined */
138 heimbach 1.4 call active_read_xy( fnamehfacc, tmpfld2d, 1,
139 heimbach 1.1 & doglobalread, ladinit, optimcycle,
140     & mythid, xx_hfacc_dummy )
141     do bj = jtlo,jthi
142     do bi = itlo,ithi
143     do j = jmin,jmax
144     do i = imin,imax
145     k = k_lowC(i,j,bi,bj)
146     c if ( k .gt. 0 ) then
147 jmc 1.5 hFacC(i,j,k,bi,bj) = hFacC(i,j,k,bi,bj)
148 heimbach 1.1 & + fac*tmpfld2d(i,j,bi,bj)
149     c end if
150     enddo
151     enddo
152     enddo
153     enddo
154     #endif /* ALLOW_HFACC3D_CONTROL */
155    
156     c-- Update the tile edges.
157    
158     CALL dummy_in_hfac( 'C', 0, myThid )
159     Cml _EXCH_XYZ_R8( hFacC, myThid )
160     _EXCH_XYZ_R4( hFacC, myThid )
161     CALL dummy_in_hfac( 'C', 1, myThid )
162    
163     #endif /* ALLOW_HFACC_CONTROL */
164    
165     return
166     end
167    

  ViewVC Help
Powered by ViewVC 1.1.22