/[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.1 - (hide annotations) (download)
Fri Nov 29 13:38:37 2002 UTC (21 years, 5 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint47e_post, checkpoint47c_post, checkpoint50c_post, c49_ctrl, checkpoint48e_post, checkpoint50c_pre, checkpoint48i_post, checkpoint50d_pre, checkpoint50, checkpoint50d_post, checkpoint50b_pre, checkpoint48b_post, checkpoint48c_pre, checkpoint47d_pre, checkpoint48d_pre, checkpoint47i_post, checkpoint47d_post, checkpoint48d_post, checkpoint48f_post, checkpoint48h_post, checkpoint47g_post, checkpoint48a_post, checkpoint50f_post, checkpoint50a_post, checkpoint50f_pre, checkpoint47j_post, branch-exfmods-tag, checkpoint48c_post, checkpoint47b_post, checkpoint50g_post, checkpoint50h_post, checkpoint50e_pre, checkpoint50i_post, checkpoint47f_post, checkpoint50e_post, checkpoint48, checkpoint49, checkpoint48g_post, checkpoint47h_post, checkpoint50b_post
Branch point for: branch-exfmods-curt, ecco-branch
Controls of sst, sss, hfacc, bottomdrag.
(no ice climbing).

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

  ViewVC Help
Powered by ViewVC 1.1.22